{-# LANGUAGE CPP, JavaScriptFFI, ForeignFunctionInterface, ConstraintKinds, FlexibleInstances, RankNTypes, FlexibleContexts, ScopedTypeVariables #-} -- For HasCallStack compatibility {-# LANGUAGE ImplicitParams, KindSignatures #-} module GHCJS.DOM.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(..) -- * JavaScript String , JSString(..), ToJSString(..), FromJSString(..) , toJSString, fromJSString, toMaybeJSString, fromMaybeJSString , noJSString -- * Nullable , Nullable(..), nullableToMaybe, maybeToNullable -- * Optional , Optional(..), maybeToOptional, toOptionalJSString -- * DOM String , DOMString(..), ToDOMString(..), FromDOMString(..), IsDOMString, noDOMString , USVString(..), IsUSVString, noUSVString , ByteString(..), IsByteString, noByteString , CSSOMString(..), IsCSSOMString, noCSSOMString -- * Object , maybeJSNullOrUndefined, GType(..) , GObject(..), noGObject, IsGObject, toGObject, gTypeGObject, isA, objectToString , castTo, unsafeCastTo, uncheckedCastTo , js_eq, strictEqual -- * TypedArray , RawTypedArray(RawTypedArray), unRawTypedArray, IsRawTypedArray, toRawTypedArray, noRawTypedArray , Function(Function), unFunction, IsFunction, toFunction, noFunction , PromiseRejected(..), noPromiseRejected, maybeThrowPromiseRejected, checkPromiseResult -- * Callbacks , 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 -- * 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 Control.Applicative ((<$>)) import qualified Data.Text as T (unpack, Text) import qualified Data.Text.Lazy as LT (Text) import Data.JSString (pack, unpack) import Data.JSString.Text (textToJSString, textFromJSString, lazyTextToJSString, lazyTextFromJSString) import GHCJS.Types (JSVal(..), nullRef, isNull, isUndefined, JSString(..)) import GHCJS.Marshal (ToJSVal(..), FromJSVal(..)) import GHCJS.Marshal.Pure (PToJSVal(..), PFromJSVal(..)) import GHCJS.Nullable (Nullable(..), nullableToMaybe, maybeToNullable) import GHCJS.Foreign (jsUndefined) import GHCJS.Foreign.Callback.Internal (Callback(..)) import Control.Monad.IO.Class (MonadIO(..)) import Data.Int (Int8, Int16, Int32, Int64) import Data.Word (Word8, Word16, Word32, Word64) import Data.Coerce (coerce, Coercible) import Data.Monoid ((<>)) import Data.Typeable (Typeable) import Control.Monad (unless) import Control.Exception (throwIO, Exception(..)) #if MIN_VERSION_base(4,9,0) import GHC.Stack (HasCallStack) #else import GHC.Exts (Constraint) type HasCallStack = (() :: Constraint) #endif -- | Identifies a JavaScript execution context. -- When using GHCJS this is just '()' since their is only one context. -- When using GHC it includes the functions JSaddle needs to communicate -- with the JavaScript context. type JSContextRef = () -- | This is the same as 'JSContextRef' except when using ghcjs-dom-webkit with GHC (instead of ghcjs-dom-jsaddle) type DOMContext = () -- | The 'JSM' monad keeps track of the JavaScript execution context. -- -- When using GHCJS it is `IO`. -- -- Given a 'JSM' function and a 'JSContextRef' you can run the -- function like this... -- -- > runJSM jsmFunction javaScriptContext type JSM = IO -- | This is the same as 'JSM' except when using ghcjs-dom-webkit with GHC (instead of ghcjs-dom-jsaddle) type DOM = IO -- | The 'MonadJSM' is to 'JSM' what 'MonadIO' is to 'IO'. -- When using GHCJS it is 'MonadIO'. type MonadJSM = MonadIO -- | This is the same as 'MonadJSM' except when using ghcjs-dom-webkit with GHC (instead of ghcjs-dom-jsaddle) type MonadDOM = MonadIO -- | The 'liftJSM' is to 'JSM' what 'liftIO' is to 'IO'. -- When using GHCJS it is 'liftIO'. liftJSM :: MonadJSM m => JSM a -> m a liftJSM = liftIO -- | 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 = liftIO -- | Gets the JavaScript context from the monad askJSM :: MonadJSM m => m JSContextRef askJSM = return () -- | 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 = return () -- | Runs a 'JSM' JavaScript function in a given JavaScript context. runJSM :: MonadIO m => JSM a -> JSContextRef -> m a runJSM f = liftIO . const f -- | 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 f = liftIO . const f maybeJSNullOrUndefined :: JSVal -> Maybe JSVal maybeJSNullOrUndefined r | isNull r || isUndefined r = Nothing maybeJSNullOrUndefined r = Just r -- | Like `Nullabble` but `maybeToOptional` converts `Nothing` to `jsUndefined`. newtype Optional a = Optional JSVal maybeToOptional :: PToJSVal a => Maybe a -> Optional a maybeToOptional Nothing = Optional jsUndefined maybeToOptional (Just x) = Optional (pToJSVal x) {-# INLINE maybeToOptional #-} propagateGError = id newtype GType = GType JSVal foreign import javascript unsafe "$r = $1.name;" gTypeToString :: GType -> JSString foreign import javascript unsafe "$1===$2" js_eq :: JSVal -> JSVal -> Bool strictEqual :: (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool strictEqual a b = do aval <- toJSVal a bval <- toJSVal b return $ js_eq aval bval foreign import javascript unsafe "h$isInstanceOf $1 $2" typeInstanceIsA' :: JSVal -> JSVal -> Bool typeInstanceIsA o (GType t) = typeInstanceIsA' o 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 constructor obj = liftJSM $ do let gtype = typeGType (undefined :: obj') jsval = coerce obj if typeInstanceIsA jsval gtype then return . Just $ constructor jsval else return 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 constructor obj = liftJSM $ do let gtype = typeGType (undefined :: obj') jsval = coerce obj if typeInstanceIsA jsval gtype then return $ constructor jsval else do let destType = textFromJSString . gTypeToString $ typeGType (undefined :: obj') error $ "unsafeCastTo :: invalid conversion to " <> T.unpack destType <> " requested." -- | Unsafe way to cast, super fast but if it fails you program -- will probably crash later on in some unpredictable way. -- -- > element <- uncheckedCastTo Element x uncheckedCastTo :: (IsGObject obj, IsGObject obj') => (JSVal -> obj') -> obj -> obj' uncheckedCastTo constructor = constructor . coerce -- | Determine if this is an instance of a particular type -- isA :: IsGObject o => o -> GType -> Bool isA obj = typeInstanceIsA (unGObject $ toGObject obj) newtype GObject = GObject { unGObject :: JSVal } noGObject :: Maybe GObject noGObject = Nothing {-# INLINE noGObject #-} class (ToJSVal o, FromJSVal o, Coercible o JSVal) => IsGObject o where -- | Given object get the GType of the type. The actual argument -- passed in is ignored. typeGType :: o -> GType -- | Safe upcast. toGObject :: IsGObject o => o -> GObject toGObject = GObject . coerce instance PToJSVal GObject where pToJSVal = unGObject {-# INLINE pToJSVal #-} instance PFromJSVal GObject where pFromJSVal = GObject {-# INLINE pFromJSVal #-} instance ToJSVal GObject where toJSVal = return . unGObject {-# INLINE toJSVal #-} instance FromJSVal GObject where fromJSVal = return . fmap GObject . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} --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 _ = gTypeGObject {-# INLINE typeGType #-} castToGObject :: IsGObject obj => obj -> IO obj castToGObject = return foreign import javascript unsafe "Object" gTypeGObject :: GType foreign import javascript unsafe "$1[\"toString\"]()" js_objectToString :: GObject -> IO JSString objectToString :: (MonadIO m, IsGObject self, FromJSString result) => self -> m result objectToString self = liftIO (fromJSString <$> js_objectToString (toGObject 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 = Nothing {-# INLINE noDOMString #-} type CSSOMString = JSString noCSSOMString :: Maybe CSSOMString noCSSOMString = Nothing {-# INLINE noCSSOMString #-} type USVString = JSString noUSVString :: Maybe USVString noUSVString = Nothing {-# INLINE noUSVString #-} type ByteString = JSString noByteString :: Maybe ByteString noByteString = Nothing {-# INLINE noByteString #-} class (PToJSVal a, ToJSVal a) => ToJSString a class (PFromJSVal a, FromJSVal a) => FromJSString a toJSString :: ToJSString a => a -> JSString toJSString = pFromJSVal . pToJSVal {-# INLINE toJSString #-} fromJSString :: FromJSString a => JSString -> a fromJSString = pFromJSVal . pToJSVal {-# INLINE fromJSString #-} toMaybeJSString :: ToJSString a => Maybe a -> Nullable JSString toMaybeJSString = Nullable . pToJSVal {-# INLINE toMaybeJSString #-} toOptionalJSString :: ToJSString a => Maybe a -> Optional JSString toOptionalJSString Nothing = Optional jsUndefined toOptionalJSString (Just a) = Optional (pToJSVal a) {-# INLINE toOptionalJSString #-} fromMaybeJSString :: FromJSString a => Nullable JSString -> Maybe a fromMaybeJSString (Nullable r) = pFromJSVal r {-# INLINE fromMaybeJSString #-} instance ToJSString [Char] instance FromJSString [Char] instance ToJSString T.Text instance FromJSString T.Text instance ToJSString JSString instance FromJSString JSString noJSString :: Maybe JSString noJSString = Nothing {-# INLINE noJSString #-} type ToDOMString s = ToJSString s type FromDOMString s = FromJSString s type IsDOMString s = (ToDOMString s, FromDOMString s) type IsCSSOMString s = (ToDOMString s, FromDOMString s) type IsUSVString s = (ToDOMString s, FromDOMString s) type IsByteString s = (ToDOMString s, FromDOMString s) newtype RawTypedArray = RawTypedArray { unRawTypedArray :: JSVal } noRawTypedArray :: Maybe RawTypedArray noRawTypedArray = Nothing {-# INLINE noRawTypedArray #-} instance PToJSVal RawTypedArray where pToJSVal = unRawTypedArray {-# INLINE pToJSVal #-} instance PFromJSVal RawTypedArray where pFromJSVal = RawTypedArray {-# INLINE pFromJSVal #-} instance ToJSVal RawTypedArray where toJSVal = return . unRawTypedArray {-# INLINE toJSVal #-} instance FromJSVal RawTypedArray where fromJSVal = return . fmap RawTypedArray . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsRawTypedArray o toRawTypedArray :: IsRawTypedArray o => o -> RawTypedArray toRawTypedArray = RawTypedArray . coerce newtype Function = Function { unFunction :: JSVal } noFunction :: Maybe Function noFunction = Nothing {-# INLINE noFunction #-} instance PToJSVal Function where pToJSVal = unFunction {-# INLINE pToJSVal #-} instance PFromJSVal Function where pFromJSVal = Function {-# INLINE pFromJSVal #-} instance ToJSVal Function where toJSVal = return . unFunction {-# INLINE toJSVal #-} instance FromJSVal Function where fromJSVal = return . fmap Function . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsFunction o toFunction :: IsFunction o => o -> Function toFunction = Function . coerce instance IsFunction Function -- Promise newtype PromiseRejected = PromiseRejected { rejectionReason :: JSVal } deriving (Typeable) noPromiseRejected :: Maybe PromiseRejected noPromiseRejected = Nothing {-# INLINE noPromiseRejected #-} maybeThrowPromiseRejected :: JSVal -> IO () maybeThrowPromiseRejected e = unless (isNull e) $ throwIO (PromiseRejected e) {-# INLINE maybeThrowPromiseRejected #-} checkPromiseResult :: (JSVal, a) -> IO a checkPromiseResult (e, a) = maybeThrowPromiseRejected e >> return a {-# INLINE checkPromiseResult #-} instance Show PromiseRejected where show _ = "A promise was rejected" instance Exception PromiseRejected -- Callbacks newtype AudioBufferCallback = AudioBufferCallback (Callback (JSVal -> IO ())) noAudioBufferCallback :: Maybe AudioBufferCallback noAudioBufferCallback = Nothing {-# INLINE noAudioBufferCallback #-} instance PToJSVal AudioBufferCallback where pToJSVal (AudioBufferCallback (Callback r)) = r newtype BlobCallback = BlobCallback (Callback (JSVal -> IO ())) noBlobCallback :: Maybe BlobCallback noBlobCallback = Nothing {-# INLINE noBlobCallback #-} instance ToJSVal BlobCallback where toJSVal (BlobCallback (Callback r)) = toJSVal r newtype DatabaseCallback = DatabaseCallback (Callback (JSVal -> IO ())) noDatabaseCallback :: Maybe DatabaseCallback noDatabaseCallback = Nothing {-# INLINE noDatabaseCallback #-} instance PToJSVal DatabaseCallback where pToJSVal (DatabaseCallback (Callback r)) = r newtype IntersectionObserverCallback = IntersectionObserverCallback (Callback (JSVal -> JSVal -> IO ())) noIntersectionObserverCallback :: Maybe IntersectionObserverCallback noIntersectionObserverCallback = Nothing {-# INLINE noIntersectionObserverCallback #-} instance PToJSVal IntersectionObserverCallback where pToJSVal (IntersectionObserverCallback (Callback r)) = r newtype MediaQueryListListener = MediaQueryListListener (Callback (JSVal -> IO ())) noMediaQueryListListener :: Maybe MediaQueryListListener noMediaQueryListListener = Nothing {-# INLINE noMediaQueryListListener #-} instance PToJSVal MediaQueryListListener where pToJSVal (MediaQueryListListener (Callback r)) = r newtype MediaStreamTrackSourcesCallback = MediaStreamTrackSourcesCallback (Callback (JSVal -> IO ())) noMediaStreamTrackSourcesCallback :: Maybe MediaStreamTrackSourcesCallback noMediaStreamTrackSourcesCallback = Nothing {-# INLINE noMediaStreamTrackSourcesCallback #-} instance PToJSVal MediaStreamTrackSourcesCallback where pToJSVal (MediaStreamTrackSourcesCallback (Callback r)) = r newtype NavigatorUserMediaErrorCallback = NavigatorUserMediaErrorCallback (Callback (JSVal -> IO ())) noNavigatorUserMediaErrorCallback :: Maybe NavigatorUserMediaErrorCallback noNavigatorUserMediaErrorCallback = Nothing {-# INLINE noNavigatorUserMediaErrorCallback #-} instance PToJSVal NavigatorUserMediaErrorCallback where pToJSVal (NavigatorUserMediaErrorCallback (Callback r)) = r newtype NavigatorUserMediaSuccessCallback = NavigatorUserMediaSuccessCallback (Callback (JSVal -> IO ())) noNavigatorUserMediaSuccessCallback :: Maybe NavigatorUserMediaSuccessCallback noNavigatorUserMediaSuccessCallback = Nothing {-# INLINE noNavigatorUserMediaSuccessCallback #-} instance PToJSVal NavigatorUserMediaSuccessCallback where pToJSVal (NavigatorUserMediaSuccessCallback (Callback r)) = r newtype NotificationPermissionCallback permissions = NotificationPermissionCallback (Callback (JSVal -> IO ())) instance PToJSVal (NotificationPermissionCallback permissions) where pToJSVal (NotificationPermissionCallback (Callback r)) = r newtype NodeFilter = NodeFilter (Callback (JSVal -> IO ())) noNodeFilter :: Maybe NodeFilter noNodeFilter = Nothing {-# INLINE noNodeFilter #-} instance PToJSVal NodeFilter where pToJSVal (NodeFilter (Callback r)) = r newtype PositionCallback = PositionCallback (Callback (JSVal -> IO ())) noPositionCallback :: Maybe PositionCallback noPositionCallback = Nothing {-# INLINE noPositionCallback #-} instance PToJSVal PositionCallback where pToJSVal (PositionCallback (Callback r)) = r newtype PositionErrorCallback = PositionErrorCallback (Callback (JSVal -> IO ())) noPositionErrorCallback :: Maybe PositionErrorCallback noPositionErrorCallback = Nothing {-# INLINE noPositionErrorCallback #-} instance PToJSVal PositionErrorCallback where pToJSVal (PositionErrorCallback (Callback r)) = r newtype PerformanceObserverCallback = PerformanceObserverCallback (Callback (JSVal -> JSVal -> IO ())) noPerformanceObserverCallback :: Maybe PerformanceObserverCallback noPerformanceObserverCallback = Nothing {-# INLINE noPerformanceObserverCallback #-} instance PToJSVal PerformanceObserverCallback where pToJSVal (PerformanceObserverCallback (Callback r)) = r newtype RequestAnimationFrameCallback = RequestAnimationFrameCallback (Callback (JSVal -> IO ())) noRequestAnimationFrameCallback :: Maybe RequestAnimationFrameCallback noRequestAnimationFrameCallback = Nothing {-# INLINE noRequestAnimationFrameCallback #-} instance PToJSVal RequestAnimationFrameCallback where pToJSVal (RequestAnimationFrameCallback (Callback r)) = r newtype RTCPeerConnectionErrorCallback = RTCPeerConnectionErrorCallback (Callback (JSVal -> IO ())) noRTCPeerConnectionErrorCallback :: Maybe RTCPeerConnectionErrorCallback noRTCPeerConnectionErrorCallback = Nothing {-# INLINE noRTCPeerConnectionErrorCallback #-} instance PToJSVal RTCPeerConnectionErrorCallback where pToJSVal (RTCPeerConnectionErrorCallback (Callback r)) = r newtype RTCSessionDescriptionCallback = RTCSessionDescriptionCallback (Callback (JSVal -> IO ())) noRTCSessionDescriptionCallback :: Maybe RTCSessionDescriptionCallback noRTCSessionDescriptionCallback = Nothing {-# INLINE noRTCSessionDescriptionCallback #-} instance PToJSVal RTCSessionDescriptionCallback where pToJSVal (RTCSessionDescriptionCallback (Callback r)) = r newtype RTCStatsCallback = RTCStatsCallback (Callback (JSVal -> IO ())) noRTCStatsCallback :: Maybe RTCStatsCallback noRTCStatsCallback = Nothing {-# INLINE noRTCStatsCallback #-} instance PToJSVal RTCStatsCallback where pToJSVal (RTCStatsCallback (Callback r)) = r newtype SQLStatementCallback = SQLStatementCallback (Callback (JSVal -> JSVal -> IO ())) noSQLStatementCallback :: Maybe SQLStatementCallback noSQLStatementCallback = Nothing {-# INLINE noSQLStatementCallback #-} instance PToJSVal SQLStatementCallback where pToJSVal (SQLStatementCallback (Callback r)) = r newtype SQLStatementErrorCallback = SQLStatementErrorCallback (Callback (JSVal -> JSVal -> IO ())) noSQLStatementErrorCallback :: Maybe SQLStatementErrorCallback noSQLStatementErrorCallback = Nothing {-# INLINE noSQLStatementErrorCallback #-} instance PToJSVal SQLStatementErrorCallback where pToJSVal (SQLStatementErrorCallback (Callback r)) = r newtype SQLTransactionCallback = SQLTransactionCallback (Callback (JSVal -> IO ())) noSQLTransactionCallback :: Maybe SQLTransactionCallback noSQLTransactionCallback = Nothing {-# INLINE noSQLTransactionCallback #-} instance PToJSVal SQLTransactionCallback where pToJSVal (SQLTransactionCallback (Callback r)) = r newtype SQLTransactionErrorCallback = SQLTransactionErrorCallback (Callback (JSVal -> IO ())) noSQLTransactionErrorCallback :: Maybe SQLTransactionErrorCallback noSQLTransactionErrorCallback = Nothing {-# INLINE noSQLTransactionErrorCallback #-} instance PToJSVal SQLTransactionErrorCallback where pToJSVal (SQLTransactionErrorCallback (Callback r)) = r newtype StorageErrorCallback = StorageErrorCallback (Callback (JSVal -> IO ())) noStorageErrorCallback :: Maybe StorageErrorCallback noStorageErrorCallback = Nothing {-# INLINE noStorageErrorCallback #-} instance PToJSVal StorageErrorCallback where pToJSVal (StorageErrorCallback (Callback r)) = r newtype StorageQuotaCallback = StorageQuotaCallback (Callback (JSVal -> IO ())) noStorageQuotaCallback :: Maybe StorageQuotaCallback noStorageQuotaCallback = Nothing {-# INLINE noStorageQuotaCallback #-} instance PToJSVal StorageQuotaCallback where pToJSVal (StorageQuotaCallback (Callback r)) = r newtype StorageUsageCallback = StorageUsageCallback (Callback (JSVal -> JSVal -> IO ())) noStorageUsageCallback :: Maybe StorageUsageCallback noStorageUsageCallback = Nothing {-# INLINE noStorageUsageCallback #-} instance PToJSVal StorageUsageCallback where pToJSVal (StorageUsageCallback (Callback r)) = r newtype StringCallback s = StringCallback (Callback (JSVal -> IO ())) instance PToJSVal (StringCallback s) where pToJSVal (StringCallback (Callback r)) = r newtype VoidCallback = VoidCallback (Callback (IO ())) noVoidCallback :: Maybe VoidCallback noVoidCallback = Nothing {-# INLINE noVoidCallback #-} instance PToJSVal VoidCallback where pToJSVal (VoidCallback (Callback r)) = r -- Custom types type DOMHighResTimeStamp = Double noDOMHighResTimeStamp :: Maybe DOMHighResTimeStamp noDOMHighResTimeStamp = Nothing {-# INLINE noDOMHighResTimeStamp #-} type PerformanceEntryList = [PerformanceEntry] noPerformanceEntryList :: Maybe PerformanceEntryList noPerformanceEntryList = Nothing {-# INLINE noPerformanceEntryList #-} -- Record Type newtype Record key value = Record { unRecord :: JSVal } instance PToJSVal (Record key value) where pToJSVal = unRecord {-# INLINE pToJSVal #-} instance PFromJSVal (Record key value) where pFromJSVal = Record {-# INLINE pFromJSVal #-} instance ToJSVal (Record key value) where toJSVal = return . unRecord {-# INLINE toJSVal #-} instance FromJSVal (Record key value) where fromJSVal = return . fmap Record . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} newtype SerializedScriptValue = SerializedScriptValue { unSerializedScriptValue :: JSVal } noSerializedScriptValue :: Maybe SerializedScriptValue noSerializedScriptValue = Nothing {-# INLINE noSerializedScriptValue #-} instance Eq SerializedScriptValue where (SerializedScriptValue a) == (SerializedScriptValue b) = js_eq a b instance PToJSVal SerializedScriptValue where pToJSVal = unSerializedScriptValue {-# INLINE pToJSVal #-} instance PFromJSVal SerializedScriptValue where pFromJSVal = SerializedScriptValue {-# INLINE pFromJSVal #-} instance ToJSVal SerializedScriptValue where toJSVal = return . unSerializedScriptValue {-# INLINE toJSVal #-} instance FromJSVal SerializedScriptValue where fromJSVal = return . fmap SerializedScriptValue . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class IsGObject o => IsSerializedScriptValue o toSerializedScriptValue :: IsSerializedScriptValue o => o -> SerializedScriptValue toSerializedScriptValue = SerializedScriptValue . coerce instance IsSerializedScriptValue SerializedScriptValue instance IsGObject SerializedScriptValue where typeGType _ = error "Unable to get the JavaScript type of SerializedScriptValue" newtype Dictionary = Dictionary { unDictionary :: JSVal } noDictionary :: Maybe Dictionary noDictionary = Nothing {-# INLINE noDictionary #-} instance Eq Dictionary where (Dictionary a) == (Dictionary b) = js_eq a b instance PToJSVal Dictionary where pToJSVal = unDictionary {-# INLINE pToJSVal #-} instance PFromJSVal Dictionary where pFromJSVal = Dictionary {-# INLINE pFromJSVal #-} instance ToJSVal Dictionary where toJSVal = return . unDictionary {-# INLINE toJSVal #-} instance FromJSVal Dictionary where fromJSVal = return . fmap Dictionary . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class IsGObject o => IsDictionary o toDictionary :: IsDictionary o => o -> Dictionary toDictionary = Dictionary . coerce instance IsDictionary Dictionary instance IsGObject Dictionary where typeGType _ = error "Unable to get the JavaScript type of Dictionary" newtype MutationCallback = MutationCallback { unMutationCallback :: JSVal } noMutationCallback :: Maybe MutationCallback noMutationCallback = Nothing {-# INLINE noMutationCallback #-} instance Eq MutationCallback where (MutationCallback a) == (MutationCallback b) = js_eq a b instance PToJSVal MutationCallback where pToJSVal = unMutationCallback {-# INLINE pToJSVal #-} instance PFromJSVal MutationCallback where pFromJSVal = MutationCallback {-# INLINE pFromJSVal #-} instance ToJSVal MutationCallback where toJSVal = return . unMutationCallback {-# INLINE toJSVal #-} instance FromJSVal MutationCallback where fromJSVal = return . fmap MutationCallback . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class IsGObject o => IsMutationCallback o toMutationCallback :: IsMutationCallback o => o -> MutationCallback toMutationCallback = MutationCallback . coerce instance IsMutationCallback MutationCallback instance IsGObject MutationCallback where typeGType _ = error "Unable to get the JavaScript type of MutationCallback" newtype ArrayBuffer = ArrayBuffer { unArrayBuffer :: JSVal } noArrayBuffer :: Maybe ArrayBuffer noArrayBuffer = Nothing {-# INLINE noArrayBuffer #-} instance Eq ArrayBuffer where (ArrayBuffer a) == (ArrayBuffer b) = js_eq a b instance PToJSVal ArrayBuffer where pToJSVal = unArrayBuffer {-# INLINE pToJSVal #-} instance PFromJSVal ArrayBuffer where pFromJSVal = ArrayBuffer {-# INLINE pFromJSVal #-} instance ToJSVal ArrayBuffer where toJSVal = return . unArrayBuffer {-# INLINE toJSVal #-} instance FromJSVal ArrayBuffer where fromJSVal = return . fmap ArrayBuffer . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class IsGObject o => IsArrayBuffer o toArrayBuffer :: IsArrayBuffer o => o -> ArrayBuffer toArrayBuffer = ArrayBuffer . coerce instance IsArrayBuffer ArrayBuffer instance IsGObject ArrayBuffer where typeGType _ = gTypeArrayBuffer foreign import javascript unsafe "window[\"ArrayBuffer\"]" gTypeArrayBuffer :: GType newtype Float32Array = Float32Array { unFloat32Array :: JSVal } noFloat32Array :: Maybe Float32Array noFloat32Array = Nothing {-# INLINE noFloat32Array #-} instance Eq Float32Array where (Float32Array a) == (Float32Array b) = js_eq a b instance PToJSVal Float32Array where pToJSVal = unFloat32Array {-# INLINE pToJSVal #-} instance PFromJSVal Float32Array where pFromJSVal = Float32Array {-# INLINE pFromJSVal #-} instance ToJSVal Float32Array where toJSVal = return . unFloat32Array {-# INLINE toJSVal #-} instance FromJSVal Float32Array where fromJSVal = return . fmap Float32Array . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class IsGObject o => IsFloat32Array o toFloat32Array :: IsFloat32Array o => o -> Float32Array toFloat32Array = Float32Array . coerce instance IsFloat32Array Float32Array instance IsGObject Float32Array where typeGType _ = gTypeFloat32Array foreign import javascript unsafe "window[\"Float32Array\"]" gTypeFloat32Array :: GType newtype Float64Array = Float64Array { unFloat64Array :: JSVal } noFloat64Array :: Maybe Float64Array noFloat64Array = Nothing {-# INLINE noFloat64Array #-} instance Eq Float64Array where (Float64Array a) == (Float64Array b) = js_eq a b instance PToJSVal Float64Array where pToJSVal = unFloat64Array {-# INLINE pToJSVal #-} instance PFromJSVal Float64Array where pFromJSVal = Float64Array {-# INLINE pFromJSVal #-} instance ToJSVal Float64Array where toJSVal = return . unFloat64Array {-# INLINE toJSVal #-} instance FromJSVal Float64Array where fromJSVal = return . fmap Float64Array . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class IsGObject o => IsFloat64Array o toFloat64Array :: IsFloat64Array o => o -> Float64Array toFloat64Array = Float64Array . coerce instance IsFloat64Array Float64Array instance IsGObject Float64Array where typeGType _ = gTypeFloat64Array foreign import javascript unsafe "window[\"Float64Array\"]" gTypeFloat64Array :: GType newtype Uint8Array = Uint8Array { unUint8Array :: JSVal } noUint8Array :: Maybe Uint8Array noUint8Array = Nothing {-# INLINE noUint8Array #-} instance Eq Uint8Array where (Uint8Array a) == (Uint8Array b) = js_eq a b instance PToJSVal Uint8Array where pToJSVal = unUint8Array {-# INLINE pToJSVal #-} instance PFromJSVal Uint8Array where pFromJSVal = Uint8Array {-# INLINE pFromJSVal #-} instance ToJSVal Uint8Array where toJSVal = return . unUint8Array {-# INLINE toJSVal #-} instance FromJSVal Uint8Array where fromJSVal = return . fmap Uint8Array . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class IsGObject o => IsUint8Array o toUint8Array :: IsUint8Array o => o -> Uint8Array toUint8Array = Uint8Array . coerce instance IsUint8Array Uint8Array instance IsGObject Uint8Array where typeGType _ = gTypeUint8Array foreign import javascript unsafe "window[\"Uint8Array\"]" gTypeUint8Array :: GType newtype Uint8ClampedArray = Uint8ClampedArray { unUint8ClampedArray :: JSVal } noUint8ClampedArray :: Maybe Uint8ClampedArray noUint8ClampedArray = Nothing {-# INLINE noUint8ClampedArray #-} instance Eq Uint8ClampedArray where (Uint8ClampedArray a) == (Uint8ClampedArray b) = js_eq a b instance PToJSVal Uint8ClampedArray where pToJSVal = unUint8ClampedArray {-# INLINE pToJSVal #-} instance PFromJSVal Uint8ClampedArray where pFromJSVal = Uint8ClampedArray {-# INLINE pFromJSVal #-} instance ToJSVal Uint8ClampedArray where toJSVal = return . unUint8ClampedArray {-# INLINE toJSVal #-} instance FromJSVal Uint8ClampedArray where fromJSVal = return . fmap Uint8ClampedArray . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class IsGObject o => IsUint8ClampedArray o toUint8ClampedArray :: IsUint8ClampedArray o => o -> Uint8ClampedArray toUint8ClampedArray = Uint8ClampedArray . coerce instance IsUint8ClampedArray Uint8ClampedArray instance IsGObject Uint8ClampedArray where typeGType _ = gTypeUint8ClampedArray foreign import javascript unsafe "window[\"Uint8ClampedArray\"]" gTypeUint8ClampedArray :: GType newtype Uint16Array = Uint16Array { unUint16Array :: JSVal } noUint16Array :: Maybe Uint16Array noUint16Array = Nothing {-# INLINE noUint16Array #-} instance Eq Uint16Array where (Uint16Array a) == (Uint16Array b) = js_eq a b instance PToJSVal Uint16Array where pToJSVal = unUint16Array {-# INLINE pToJSVal #-} instance PFromJSVal Uint16Array where pFromJSVal = Uint16Array {-# INLINE pFromJSVal #-} instance ToJSVal Uint16Array where toJSVal = return . unUint16Array {-# INLINE toJSVal #-} instance FromJSVal Uint16Array where fromJSVal = return . fmap Uint16Array . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class IsGObject o => IsUint16Array o toUint16Array :: IsUint16Array o => o -> Uint16Array toUint16Array = Uint16Array . coerce instance IsUint16Array Uint16Array instance IsGObject Uint16Array where typeGType _ = gTypeUint16Array foreign import javascript unsafe "window[\"Uint16Array\"]" gTypeUint16Array :: GType newtype Uint32Array = Uint32Array { unUint32Array :: JSVal } noUint32Array :: Maybe Uint32Array noUint32Array = Nothing {-# INLINE noUint32Array #-} instance Eq Uint32Array where (Uint32Array a) == (Uint32Array b) = js_eq a b instance PToJSVal Uint32Array where pToJSVal = unUint32Array {-# INLINE pToJSVal #-} instance PFromJSVal Uint32Array where pFromJSVal = Uint32Array {-# INLINE pFromJSVal #-} instance ToJSVal Uint32Array where toJSVal = return . unUint32Array {-# INLINE toJSVal #-} instance FromJSVal Uint32Array where fromJSVal = return . fmap Uint32Array . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class IsGObject o => IsUint32Array o toUint32Array :: IsUint32Array o => o -> Uint32Array toUint32Array = Uint32Array . coerce instance IsUint32Array Uint32Array instance IsGObject Uint32Array where typeGType _ = gTypeUint32Array foreign import javascript unsafe "window[\"Uint32Array\"]" gTypeUint32Array :: GType newtype Int8Array = Int8Array { unInt8Array :: JSVal } noInt8Array :: Maybe Int8Array noInt8Array = Nothing {-# INLINE noInt8Array #-} instance Eq Int8Array where (Int8Array a) == (Int8Array b) = js_eq a b instance PToJSVal Int8Array where pToJSVal = unInt8Array {-# INLINE pToJSVal #-} instance PFromJSVal Int8Array where pFromJSVal = Int8Array {-# INLINE pFromJSVal #-} instance ToJSVal Int8Array where toJSVal = return . unInt8Array {-# INLINE toJSVal #-} instance FromJSVal Int8Array where fromJSVal = return . fmap Int8Array . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class IsGObject o => IsInt8Array o toInt8Array :: IsInt8Array o => o -> Int8Array toInt8Array = Int8Array . coerce instance IsInt8Array Int8Array instance IsGObject Int8Array where typeGType _ = gTypeInt8Array foreign import javascript unsafe "window[\"Int8Array\"]" gTypeInt8Array :: GType newtype Int16Array = Int16Array { unInt16Array :: JSVal } noInt16Array :: Maybe Int16Array noInt16Array = Nothing {-# INLINE noInt16Array #-} instance Eq Int16Array where (Int16Array a) == (Int16Array b) = js_eq a b instance PToJSVal Int16Array where pToJSVal = unInt16Array {-# INLINE pToJSVal #-} instance PFromJSVal Int16Array where pFromJSVal = Int16Array {-# INLINE pFromJSVal #-} instance ToJSVal Int16Array where toJSVal = return . unInt16Array {-# INLINE toJSVal #-} instance FromJSVal Int16Array where fromJSVal = return . fmap Int16Array . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class IsGObject o => IsInt16Array o toInt16Array :: IsInt16Array o => o -> Int16Array toInt16Array = Int16Array . coerce instance IsInt16Array Int16Array instance IsGObject Int16Array where typeGType _ = gTypeInt16Array foreign import javascript unsafe "window[\"Int16Array\"]" gTypeInt16Array :: GType newtype Int32Array = Int32Array { unInt32Array :: JSVal } noInt32Array :: Maybe Int32Array noInt32Array = Nothing {-# INLINE noInt32Array #-} instance Eq Int32Array where (Int32Array a) == (Int32Array b) = js_eq a b instance PToJSVal Int32Array where pToJSVal = unInt32Array {-# INLINE pToJSVal #-} instance PFromJSVal Int32Array where pFromJSVal = Int32Array {-# INLINE pFromJSVal #-} instance ToJSVal Int32Array where toJSVal = return . unInt32Array {-# INLINE toJSVal #-} instance FromJSVal Int32Array where fromJSVal = return . fmap Int32Array . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class IsGObject o => IsInt32Array o toInt32Array :: IsInt32Array o => o -> Int32Array toInt32Array = Int32Array . coerce instance IsInt32Array Int32Array instance IsGObject Int32Array where typeGType _ = gTypeInt32Array foreign import javascript unsafe "window[\"Int32Array\"]" gTypeInt32Array :: GType newtype ObjectArray = ObjectArray { unObjectArray :: JSVal } noObjectArray :: Maybe ObjectArray noObjectArray = Nothing {-# INLINE noObjectArray #-} instance Eq ObjectArray where (ObjectArray a) == (ObjectArray b) = js_eq a b instance PToJSVal ObjectArray where pToJSVal = unObjectArray {-# INLINE pToJSVal #-} instance PFromJSVal ObjectArray where pFromJSVal = ObjectArray {-# INLINE pFromJSVal #-} instance ToJSVal ObjectArray where toJSVal = return . unObjectArray {-# INLINE toJSVal #-} instance FromJSVal ObjectArray where fromJSVal = return . fmap ObjectArray . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class IsGObject o => IsObjectArray o toObjectArray :: IsObjectArray o => o -> ObjectArray toObjectArray = ObjectArray . coerce instance IsObjectArray ObjectArray instance IsGObject ObjectArray where typeGType _ = error "Unable to get the JavaScript type of ObjectArray" newtype ArrayBufferView = ArrayBufferView { unArrayBufferView :: JSVal } noArrayBufferView :: Maybe ArrayBufferView noArrayBufferView = Nothing {-# INLINE noArrayBufferView #-} instance Eq ArrayBufferView where (ArrayBufferView a) == (ArrayBufferView b) = js_eq a b instance PToJSVal ArrayBufferView where pToJSVal = unArrayBufferView {-# INLINE pToJSVal #-} instance PFromJSVal ArrayBufferView where pFromJSVal = ArrayBufferView {-# INLINE pFromJSVal #-} instance ToJSVal ArrayBufferView where toJSVal = return . unArrayBufferView {-# INLINE toJSVal #-} instance FromJSVal ArrayBufferView where fromJSVal = return . fmap ArrayBufferView . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class IsGObject o => IsArrayBufferView o toArrayBufferView :: IsArrayBufferView o => o -> ArrayBufferView toArrayBufferView = ArrayBufferView . coerce instance IsArrayBufferView ArrayBufferView instance IsGObject ArrayBufferView where typeGType _ = error "Unable to get the JavaScript type of ArrayBufferView" newtype Array = Array { unArray :: JSVal } noArray :: Maybe Array noArray = Nothing {-# INLINE noArray #-} instance Eq Array where (Array a) == (Array b) = js_eq a b instance PToJSVal Array where pToJSVal = unArray {-# INLINE pToJSVal #-} instance PFromJSVal Array where pFromJSVal = Array {-# INLINE pFromJSVal #-} instance ToJSVal Array where toJSVal = return . unArray {-# INLINE toJSVal #-} instance FromJSVal Array where fromJSVal = return . fmap Array . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class IsGObject o => IsArray o toArray :: IsArray o => o -> Array toArray = Array . coerce instance IsArray Array instance IsGObject Array where typeGType _ = gTypeArray foreign import javascript unsafe "window[\"Array\"]" gTypeArray :: GType newtype Date = Date { unDate :: JSVal } noDate :: Maybe Date noDate = Nothing {-# INLINE noDate #-} instance Eq Date where (Date a) == (Date b) = js_eq a b instance PToJSVal Date where pToJSVal = unDate {-# INLINE pToJSVal #-} instance PFromJSVal Date where pFromJSVal = Date {-# INLINE pFromJSVal #-} instance ToJSVal Date where toJSVal = return . unDate {-# INLINE toJSVal #-} instance FromJSVal Date where fromJSVal = return . fmap Date . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class IsGObject o => IsDate o toDate :: IsDate o => o -> Date toDate = Date . coerce instance IsDate Date instance IsGObject Date where typeGType _ = gTypeDate foreign import javascript unsafe "window[\"Date\"]" gTypeDate :: GType newtype Algorithm = Algorithm { unAlgorithm :: JSVal } noAlgorithm :: Maybe Algorithm noAlgorithm = Nothing {-# INLINE noAlgorithm #-} instance Eq Algorithm where (Algorithm a) == (Algorithm b) = js_eq a b instance PToJSVal Algorithm where pToJSVal = unAlgorithm {-# INLINE pToJSVal #-} instance PFromJSVal Algorithm where pFromJSVal = Algorithm {-# INLINE pFromJSVal #-} instance ToJSVal Algorithm where toJSVal = return . unAlgorithm {-# INLINE toJSVal #-} instance FromJSVal Algorithm where fromJSVal = return . fmap Algorithm . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class IsGObject o => IsAlgorithm o toAlgorithm :: IsAlgorithm o => o -> Algorithm toAlgorithm = Algorithm . coerce instance IsAlgorithm Algorithm instance IsGObject Algorithm where typeGType _ = error "Unable to get the JavaScript type of Algorithm" newtype CryptoOperationData = CryptoOperationData { unCryptoOperationData :: JSVal } noCryptoOperationData :: Maybe CryptoOperationData noCryptoOperationData = Nothing {-# INLINE noCryptoOperationData #-} instance Eq CryptoOperationData where (CryptoOperationData a) == (CryptoOperationData b) = js_eq a b instance PToJSVal CryptoOperationData where pToJSVal = unCryptoOperationData {-# INLINE pToJSVal #-} instance PFromJSVal CryptoOperationData where pFromJSVal = CryptoOperationData {-# INLINE pFromJSVal #-} instance ToJSVal CryptoOperationData where toJSVal = return . unCryptoOperationData {-# INLINE toJSVal #-} instance FromJSVal CryptoOperationData where fromJSVal = return . fmap CryptoOperationData . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class IsGObject o => IsCryptoOperationData o toCryptoOperationData :: IsCryptoOperationData o => o -> CryptoOperationData toCryptoOperationData = CryptoOperationData . coerce instance IsCryptoOperationData CryptoOperationData instance IsGObject CryptoOperationData where typeGType _ = error "Unable to get the JavaScript type of CryptoOperationData" instance IsCryptoOperationData ArrayBuffer instance IsCryptoOperationData ArrayBufferView type GLenum = Word32 noGLenum :: Maybe GLenum noGLenum = Nothing {-# INLINE noGLenum #-} type GLboolean = Bool noGLboolean :: Maybe GLboolean noGLboolean = Nothing {-# INLINE noGLboolean #-} type GLbitfield = Word32 noGLbitfield :: Maybe GLbitfield noGLbitfield = Nothing {-# INLINE noGLbitfield #-} type GLbyte = Int8 noGLbyte :: Maybe GLbyte noGLbyte = Nothing {-# INLINE noGLbyte #-} type GLshort = Int16 noGLshort :: Maybe GLshort noGLshort = Nothing {-# INLINE noGLshort #-} type GLint = Int32 noGLint :: Maybe GLint noGLint = Nothing {-# INLINE noGLint #-} type GLint64 = Int64 noGLint64 :: Maybe GLint64 noGLint64 = Nothing {-# INLINE noGLint64 #-} type GLsizei = Int32 noGLsizei :: Maybe GLsizei noGLsizei = Nothing {-# INLINE noGLsizei #-} type GLintptr = Int64 noGLintptr :: Maybe GLintptr noGLintptr = Nothing {-# INLINE noGLintptr #-} type GLsizeiptr = Int64 noGLsizeiptr :: Maybe GLsizeiptr noGLsizeiptr = Nothing {-# INLINE noGLsizeiptr #-} type GLubyte = Word8 noGLubyte :: Maybe GLubyte noGLubyte = Nothing {-# INLINE noGLubyte #-} type GLushort = Word16 noGLushort :: Maybe GLushort noGLushort = Nothing {-# INLINE noGLushort #-} type GLuint = Word32 noGLuint :: Maybe GLuint noGLuint = Nothing {-# INLINE noGLuint #-} type GLuint64 = Word64 noGLuint64 :: Maybe GLuint64 noGLuint64 = Nothing {-# INLINE noGLuint64 #-} type GLfloat = Double noGLfloat :: Maybe GLfloat noGLfloat = Nothing {-# INLINE noGLfloat #-} type GLclampf = Double noGLclampf :: Maybe GLclampf noGLclampf = Nothing {-# INLINE noGLclampf #-} -- AUTO GENERATION STARTS HERE -- The remainder of this file is generated from IDL files using domconv-webkit-jsffi newtype AddEventListenerOptionsOrBool = AddEventListenerOptionsOrBool { unAddEventListenerOptionsOrBool :: JSVal } instance PToJSVal AddEventListenerOptionsOrBool where pToJSVal = unAddEventListenerOptionsOrBool {-# INLINE pToJSVal #-} instance PFromJSVal AddEventListenerOptionsOrBool where pFromJSVal = AddEventListenerOptionsOrBool {-# INLINE pFromJSVal #-} instance ToJSVal AddEventListenerOptionsOrBool where toJSVal = return . unAddEventListenerOptionsOrBool {-# INLINE toJSVal #-} instance FromJSVal AddEventListenerOptionsOrBool where fromJSVal = return . fmap AddEventListenerOptionsOrBool . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (FromJSVal o, ToJSVal o, PToJSVal o) => IsAddEventListenerOptionsOrBool o toAddEventListenerOptionsOrBool :: IsAddEventListenerOptionsOrBool o => o -> AddEventListenerOptionsOrBool toAddEventListenerOptionsOrBool = AddEventListenerOptionsOrBool . pToJSVal instance IsAddEventListenerOptionsOrBool AddEventListenerOptionsOrBool instance IsAddEventListenerOptionsOrBool Bool instance IsAddEventListenerOptionsOrBool AddEventListenerOptions newtype BinaryData = BinaryData { unBinaryData :: JSVal } instance PToJSVal BinaryData where pToJSVal = unBinaryData {-# INLINE pToJSVal #-} instance PFromJSVal BinaryData where pFromJSVal = BinaryData {-# INLINE pFromJSVal #-} instance ToJSVal BinaryData where toJSVal = return . unBinaryData {-# INLINE toJSVal #-} instance FromJSVal BinaryData where fromJSVal = return . fmap BinaryData . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsBinaryData o toBinaryData :: IsBinaryData o => o -> BinaryData toBinaryData = BinaryData . coerce instance IsBinaryData BinaryData instance IsBinaryData ArrayBuffer instance IsBinaryData ArrayBufferView newtype BlobPart = BlobPart { unBlobPart :: JSVal } instance PToJSVal BlobPart where pToJSVal = unBlobPart {-# INLINE pToJSVal #-} instance PFromJSVal BlobPart where pFromJSVal = BlobPart {-# INLINE pFromJSVal #-} instance ToJSVal BlobPart where toJSVal = return . unBlobPart {-# INLINE toJSVal #-} instance FromJSVal BlobPart where fromJSVal = return . fmap BlobPart . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (FromJSVal o, ToJSVal o) => IsBlobPart o instance IsBlobPart BlobPart instance IsBlobPart BinaryData instance IsBlobPart BufferSource instance IsBlobPart ArrayBufferView instance IsBlobPart ArrayBuffer instance IsBlobPart Blob instance IsBlobPart File instance IsBlobPart Text instance IsBlobPart JSString instance IsBlobPart String newtype BodyInit = BodyInit { unBodyInit :: JSVal } instance PToJSVal BodyInit where pToJSVal = unBodyInit {-# INLINE pToJSVal #-} instance PFromJSVal BodyInit where pFromJSVal = BodyInit {-# INLINE pFromJSVal #-} instance ToJSVal BodyInit where toJSVal = return . unBodyInit {-# INLINE toJSVal #-} instance FromJSVal BodyInit where fromJSVal = return . fmap BodyInit . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (FromJSVal o, ToJSVal o) => IsBodyInit o instance IsBodyInit BodyInit instance IsBodyInit Text instance IsBodyInit JSString instance IsBodyInit String instance IsBodyInit FormData instance IsBodyInit BinaryData instance IsBodyInit BufferSource instance IsBodyInit ArrayBufferView instance IsBodyInit ArrayBuffer instance IsBodyInit Blob instance IsBodyInit File newtype BufferDataSource = BufferDataSource { unBufferDataSource :: JSVal } instance PToJSVal BufferDataSource where pToJSVal = unBufferDataSource {-# INLINE pToJSVal #-} instance PFromJSVal BufferDataSource where pFromJSVal = BufferDataSource {-# INLINE pFromJSVal #-} instance ToJSVal BufferDataSource where toJSVal = return . unBufferDataSource {-# INLINE toJSVal #-} instance FromJSVal BufferDataSource where fromJSVal = return . fmap BufferDataSource . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsBufferDataSource o toBufferDataSource :: IsBufferDataSource o => o -> BufferDataSource toBufferDataSource = BufferDataSource . coerce instance IsBufferDataSource BufferDataSource instance IsBufferDataSource ArrayBuffer instance IsBufferDataSource ArrayBufferView newtype BufferSource = BufferSource { unBufferSource :: JSVal } instance PToJSVal BufferSource where pToJSVal = unBufferSource {-# INLINE pToJSVal #-} instance PFromJSVal BufferSource where pFromJSVal = BufferSource {-# INLINE pFromJSVal #-} instance ToJSVal BufferSource where toJSVal = return . unBufferSource {-# INLINE toJSVal #-} instance FromJSVal BufferSource where fromJSVal = return . fmap BufferSource . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsBufferSource o toBufferSource :: IsBufferSource o => o -> BufferSource toBufferSource = BufferSource . coerce instance IsBufferSource BufferSource instance IsBufferSource ArrayBuffer instance IsBufferSource ArrayBufferView newtype CanvasImageSource = CanvasImageSource { unCanvasImageSource :: JSVal } instance PToJSVal CanvasImageSource where pToJSVal = unCanvasImageSource {-# INLINE pToJSVal #-} instance PFromJSVal CanvasImageSource where pFromJSVal = CanvasImageSource {-# INLINE pFromJSVal #-} instance ToJSVal CanvasImageSource where toJSVal = return . unCanvasImageSource {-# INLINE toJSVal #-} instance FromJSVal CanvasImageSource where fromJSVal = return . fmap CanvasImageSource . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsCanvasImageSource o toCanvasImageSource :: IsCanvasImageSource o => o -> CanvasImageSource toCanvasImageSource = CanvasImageSource . coerce instance IsCanvasImageSource CanvasImageSource instance IsCanvasImageSource HTMLImageElement instance IsCanvasImageSource HTMLVideoElement instance IsCanvasImageSource HTMLCanvasElement newtype CanvasStyle = CanvasStyle { unCanvasStyle :: JSVal } instance PToJSVal CanvasStyle where pToJSVal = unCanvasStyle {-# INLINE pToJSVal #-} instance PFromJSVal CanvasStyle where pFromJSVal = CanvasStyle {-# INLINE pFromJSVal #-} instance ToJSVal CanvasStyle where toJSVal = return . unCanvasStyle {-# INLINE toJSVal #-} instance FromJSVal CanvasStyle where fromJSVal = return . fmap CanvasStyle . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (FromJSVal o, ToJSVal o) => IsCanvasStyle o instance IsCanvasStyle CanvasStyle instance IsCanvasStyle CanvasPattern instance IsCanvasStyle CanvasGradient instance IsCanvasStyle Text instance IsCanvasStyle JSString instance IsCanvasStyle String newtype CredentialBodyType = CredentialBodyType { unCredentialBodyType :: JSVal } instance PToJSVal CredentialBodyType where pToJSVal = unCredentialBodyType {-# INLINE pToJSVal #-} instance PFromJSVal CredentialBodyType where pFromJSVal = CredentialBodyType {-# INLINE pFromJSVal #-} instance ToJSVal CredentialBodyType where toJSVal = return . unCredentialBodyType {-# INLINE toJSVal #-} instance FromJSVal CredentialBodyType where fromJSVal = return . fmap CredentialBodyType . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsCredentialBodyType o toCredentialBodyType :: IsCredentialBodyType o => o -> CredentialBodyType toCredentialBodyType = CredentialBodyType . coerce instance IsCredentialBodyType CredentialBodyType instance IsCredentialBodyType URLSearchParams instance IsCredentialBodyType FormData newtype CryptoKeyOrKeyPair = CryptoKeyOrKeyPair { unCryptoKeyOrKeyPair :: JSVal } instance PToJSVal CryptoKeyOrKeyPair where pToJSVal = unCryptoKeyOrKeyPair {-# INLINE pToJSVal #-} instance PFromJSVal CryptoKeyOrKeyPair where pFromJSVal = CryptoKeyOrKeyPair {-# INLINE pFromJSVal #-} instance ToJSVal CryptoKeyOrKeyPair where toJSVal = return . unCryptoKeyOrKeyPair {-# INLINE toJSVal #-} instance FromJSVal CryptoKeyOrKeyPair where fromJSVal = return . fmap CryptoKeyOrKeyPair . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsCryptoKeyOrKeyPair o toCryptoKeyOrKeyPair :: IsCryptoKeyOrKeyPair o => o -> CryptoKeyOrKeyPair toCryptoKeyOrKeyPair = CryptoKeyOrKeyPair . coerce instance IsCryptoKeyOrKeyPair CryptoKeyOrKeyPair instance IsCryptoKeyOrKeyPair CryptoKeyPair instance IsCryptoKeyOrKeyPair CryptoKey newtype EventListenerOptionsOrBool = EventListenerOptionsOrBool { unEventListenerOptionsOrBool :: JSVal } instance PToJSVal EventListenerOptionsOrBool where pToJSVal = unEventListenerOptionsOrBool {-# INLINE pToJSVal #-} instance PFromJSVal EventListenerOptionsOrBool where pFromJSVal = EventListenerOptionsOrBool {-# INLINE pFromJSVal #-} instance ToJSVal EventListenerOptionsOrBool where toJSVal = return . unEventListenerOptionsOrBool {-# INLINE toJSVal #-} instance FromJSVal EventListenerOptionsOrBool where fromJSVal = return . fmap EventListenerOptionsOrBool . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (FromJSVal o, ToJSVal o, PToJSVal o) => IsEventListenerOptionsOrBool o toEventListenerOptionsOrBool :: IsEventListenerOptionsOrBool o => o -> EventListenerOptionsOrBool toEventListenerOptionsOrBool = EventListenerOptionsOrBool . pToJSVal instance IsEventListenerOptionsOrBool EventListenerOptionsOrBool instance IsEventListenerOptionsOrBool Bool instance IsEventListenerOptionsOrBool EventListenerOptions instance IsEventListenerOptionsOrBool AddEventListenerOptions newtype Float32List = Float32List { unFloat32List :: JSVal } instance PToJSVal Float32List where pToJSVal = unFloat32List {-# INLINE pToJSVal #-} instance PFromJSVal Float32List where pFromJSVal = Float32List {-# INLINE pFromJSVal #-} instance ToJSVal Float32List where toJSVal = return . unFloat32List {-# INLINE toJSVal #-} instance FromJSVal Float32List where fromJSVal = return . fmap Float32List . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (FromJSVal o, ToJSVal o) => IsFloat32List o instance IsFloat32List Float32List instance IsFloat32List [GLfloat] instance IsFloat32List Float32Array newtype HTMLCollectionOrElement = HTMLCollectionOrElement { unHTMLCollectionOrElement :: JSVal } instance PToJSVal HTMLCollectionOrElement where pToJSVal = unHTMLCollectionOrElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLCollectionOrElement where pFromJSVal = HTMLCollectionOrElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLCollectionOrElement where toJSVal = return . unHTMLCollectionOrElement {-# INLINE toJSVal #-} instance FromJSVal HTMLCollectionOrElement where fromJSVal = return . fmap HTMLCollectionOrElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsHTMLCollectionOrElement o toHTMLCollectionOrElement :: IsHTMLCollectionOrElement o => o -> HTMLCollectionOrElement toHTMLCollectionOrElement = HTMLCollectionOrElement . coerce instance IsHTMLCollectionOrElement HTMLCollectionOrElement instance IsHTMLCollectionOrElement Element instance IsHTMLCollectionOrElement SVGViewElement instance IsHTMLCollectionOrElement SVGVKernElement instance IsHTMLCollectionOrElement SVGUseElement instance IsHTMLCollectionOrElement SVGTitleElement instance IsHTMLCollectionOrElement SVGTextPositioningElement instance IsHTMLCollectionOrElement SVGTextPathElement instance IsHTMLCollectionOrElement SVGTextElement instance IsHTMLCollectionOrElement SVGTextContentElement instance IsHTMLCollectionOrElement SVGTSpanElement instance IsHTMLCollectionOrElement SVGTRefElement instance IsHTMLCollectionOrElement SVGSymbolElement instance IsHTMLCollectionOrElement SVGSwitchElement instance IsHTMLCollectionOrElement SVGStyleElement instance IsHTMLCollectionOrElement SVGStopElement instance IsHTMLCollectionOrElement SVGSetElement instance IsHTMLCollectionOrElement SVGScriptElement instance IsHTMLCollectionOrElement SVGSVGElement instance IsHTMLCollectionOrElement SVGRectElement instance IsHTMLCollectionOrElement SVGRadialGradientElement instance IsHTMLCollectionOrElement SVGPolylineElement instance IsHTMLCollectionOrElement SVGPolygonElement instance IsHTMLCollectionOrElement SVGPatternElement instance IsHTMLCollectionOrElement SVGPathElement instance IsHTMLCollectionOrElement SVGMissingGlyphElement instance IsHTMLCollectionOrElement SVGMetadataElement instance IsHTMLCollectionOrElement SVGMaskElement instance IsHTMLCollectionOrElement SVGMarkerElement instance IsHTMLCollectionOrElement SVGMPathElement instance IsHTMLCollectionOrElement SVGLinearGradientElement instance IsHTMLCollectionOrElement SVGLineElement instance IsHTMLCollectionOrElement SVGImageElement instance IsHTMLCollectionOrElement SVGHKernElement instance IsHTMLCollectionOrElement SVGGraphicsElement instance IsHTMLCollectionOrElement SVGGradientElement instance IsHTMLCollectionOrElement SVGGlyphRefElement instance IsHTMLCollectionOrElement SVGGlyphElement instance IsHTMLCollectionOrElement SVGGElement instance IsHTMLCollectionOrElement SVGForeignObjectElement instance IsHTMLCollectionOrElement SVGFontFaceUriElement instance IsHTMLCollectionOrElement SVGFontFaceSrcElement instance IsHTMLCollectionOrElement SVGFontFaceNameElement instance IsHTMLCollectionOrElement SVGFontFaceFormatElement instance IsHTMLCollectionOrElement SVGFontFaceElement instance IsHTMLCollectionOrElement SVGFontElement instance IsHTMLCollectionOrElement SVGFilterElement instance IsHTMLCollectionOrElement SVGFETurbulenceElement instance IsHTMLCollectionOrElement SVGFETileElement instance IsHTMLCollectionOrElement SVGFESpotLightElement instance IsHTMLCollectionOrElement SVGFESpecularLightingElement instance IsHTMLCollectionOrElement SVGFEPointLightElement instance IsHTMLCollectionOrElement SVGFEOffsetElement instance IsHTMLCollectionOrElement SVGFEMorphologyElement instance IsHTMLCollectionOrElement SVGFEMergeNodeElement instance IsHTMLCollectionOrElement SVGFEMergeElement instance IsHTMLCollectionOrElement SVGFEImageElement instance IsHTMLCollectionOrElement SVGFEGaussianBlurElement instance IsHTMLCollectionOrElement SVGFEFuncRElement instance IsHTMLCollectionOrElement SVGFEFuncGElement instance IsHTMLCollectionOrElement SVGFEFuncBElement instance IsHTMLCollectionOrElement SVGFEFuncAElement instance IsHTMLCollectionOrElement SVGFEFloodElement instance IsHTMLCollectionOrElement SVGFEDropShadowElement instance IsHTMLCollectionOrElement SVGFEDistantLightElement instance IsHTMLCollectionOrElement SVGFEDisplacementMapElement instance IsHTMLCollectionOrElement SVGFEDiffuseLightingElement instance IsHTMLCollectionOrElement SVGFEConvolveMatrixElement instance IsHTMLCollectionOrElement SVGFECompositeElement instance IsHTMLCollectionOrElement SVGFEComponentTransferElement instance IsHTMLCollectionOrElement SVGFEColorMatrixElement instance IsHTMLCollectionOrElement SVGFEBlendElement instance IsHTMLCollectionOrElement SVGEllipseElement instance IsHTMLCollectionOrElement SVGElement instance IsHTMLCollectionOrElement SVGDescElement instance IsHTMLCollectionOrElement SVGDefsElement instance IsHTMLCollectionOrElement SVGCursorElement instance IsHTMLCollectionOrElement SVGComponentTransferFunctionElement instance IsHTMLCollectionOrElement SVGClipPathElement instance IsHTMLCollectionOrElement SVGCircleElement instance IsHTMLCollectionOrElement SVGAnimationElement instance IsHTMLCollectionOrElement SVGAnimateTransformElement instance IsHTMLCollectionOrElement SVGAnimateMotionElement instance IsHTMLCollectionOrElement SVGAnimateElement instance IsHTMLCollectionOrElement SVGAnimateColorElement instance IsHTMLCollectionOrElement SVGAltGlyphItemElement instance IsHTMLCollectionOrElement SVGAltGlyphElement instance IsHTMLCollectionOrElement SVGAltGlyphDefElement instance IsHTMLCollectionOrElement SVGAElement instance IsHTMLCollectionOrElement HTMLVideoElement instance IsHTMLCollectionOrElement HTMLUnknownElement instance IsHTMLCollectionOrElement HTMLUListElement instance IsHTMLCollectionOrElement HTMLTrackElement instance IsHTMLCollectionOrElement HTMLTitleElement instance IsHTMLCollectionOrElement HTMLTimeElement instance IsHTMLCollectionOrElement HTMLTextAreaElement instance IsHTMLCollectionOrElement HTMLTemplateElement instance IsHTMLCollectionOrElement HTMLTableSectionElement instance IsHTMLCollectionOrElement HTMLTableRowElement instance IsHTMLCollectionOrElement HTMLTableElement instance IsHTMLCollectionOrElement HTMLTableColElement instance IsHTMLCollectionOrElement HTMLTableCellElement instance IsHTMLCollectionOrElement HTMLTableCaptionElement instance IsHTMLCollectionOrElement HTMLStyleElement instance IsHTMLCollectionOrElement HTMLSpanElement instance IsHTMLCollectionOrElement HTMLSourceElement instance IsHTMLCollectionOrElement HTMLSlotElement instance IsHTMLCollectionOrElement HTMLSelectElement instance IsHTMLCollectionOrElement HTMLScriptElement instance IsHTMLCollectionOrElement HTMLQuoteElement instance IsHTMLCollectionOrElement HTMLProgressElement instance IsHTMLCollectionOrElement HTMLPreElement instance IsHTMLCollectionOrElement HTMLPictureElement instance IsHTMLCollectionOrElement HTMLParamElement instance IsHTMLCollectionOrElement HTMLParagraphElement instance IsHTMLCollectionOrElement HTMLOutputElement instance IsHTMLCollectionOrElement HTMLOptionElement instance IsHTMLCollectionOrElement HTMLOptGroupElement instance IsHTMLCollectionOrElement HTMLObjectElement instance IsHTMLCollectionOrElement HTMLOListElement instance IsHTMLCollectionOrElement HTMLModElement instance IsHTMLCollectionOrElement HTMLMeterElement instance IsHTMLCollectionOrElement HTMLMetaElement instance IsHTMLCollectionOrElement HTMLMenuElement instance IsHTMLCollectionOrElement HTMLMediaElement instance IsHTMLCollectionOrElement HTMLMarqueeElement instance IsHTMLCollectionOrElement HTMLMapElement instance IsHTMLCollectionOrElement HTMLLinkElement instance IsHTMLCollectionOrElement HTMLLegendElement instance IsHTMLCollectionOrElement HTMLLabelElement instance IsHTMLCollectionOrElement HTMLLIElement instance IsHTMLCollectionOrElement HTMLKeygenElement instance IsHTMLCollectionOrElement HTMLInputElement instance IsHTMLCollectionOrElement HTMLImageElement instance IsHTMLCollectionOrElement HTMLIFrameElement instance IsHTMLCollectionOrElement HTMLHtmlElement instance IsHTMLCollectionOrElement HTMLHeadingElement instance IsHTMLCollectionOrElement HTMLHeadElement instance IsHTMLCollectionOrElement HTMLHRElement instance IsHTMLCollectionOrElement HTMLFrameSetElement instance IsHTMLCollectionOrElement HTMLFrameElement instance IsHTMLCollectionOrElement HTMLFormElement instance IsHTMLCollectionOrElement HTMLFontElement instance IsHTMLCollectionOrElement HTMLFieldSetElement instance IsHTMLCollectionOrElement HTMLEmbedElement instance IsHTMLCollectionOrElement HTMLElement instance IsHTMLCollectionOrElement HTMLDivElement instance IsHTMLCollectionOrElement HTMLDirectoryElement instance IsHTMLCollectionOrElement HTMLDetailsElement instance IsHTMLCollectionOrElement HTMLDataListElement instance IsHTMLCollectionOrElement HTMLDataElement instance IsHTMLCollectionOrElement HTMLDListElement instance IsHTMLCollectionOrElement HTMLCanvasElement instance IsHTMLCollectionOrElement HTMLButtonElement instance IsHTMLCollectionOrElement HTMLBodyElement instance IsHTMLCollectionOrElement HTMLBaseElement instance IsHTMLCollectionOrElement HTMLBRElement instance IsHTMLCollectionOrElement HTMLAudioElement instance IsHTMLCollectionOrElement HTMLAttachmentElement instance IsHTMLCollectionOrElement HTMLAreaElement instance IsHTMLCollectionOrElement HTMLAppletElement instance IsHTMLCollectionOrElement HTMLAnchorElement instance IsHTMLCollectionOrElement HTMLCollection instance IsHTMLCollectionOrElement HTMLOptionsCollection instance IsHTMLCollectionOrElement HTMLFormControlsCollection newtype HTMLElementOrLong = HTMLElementOrLong { unHTMLElementOrLong :: JSVal } instance PToJSVal HTMLElementOrLong where pToJSVal = unHTMLElementOrLong {-# INLINE pToJSVal #-} instance PFromJSVal HTMLElementOrLong where pFromJSVal = HTMLElementOrLong {-# INLINE pFromJSVal #-} instance ToJSVal HTMLElementOrLong where toJSVal = return . unHTMLElementOrLong {-# INLINE toJSVal #-} instance FromJSVal HTMLElementOrLong where fromJSVal = return . fmap HTMLElementOrLong . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (FromJSVal o, ToJSVal o) => IsHTMLElementOrLong o instance IsHTMLElementOrLong HTMLElementOrLong instance IsHTMLElementOrLong Int instance IsHTMLElementOrLong HTMLElement instance IsHTMLElementOrLong HTMLVideoElement instance IsHTMLElementOrLong HTMLUnknownElement instance IsHTMLElementOrLong HTMLUListElement instance IsHTMLElementOrLong HTMLTrackElement instance IsHTMLElementOrLong HTMLTitleElement instance IsHTMLElementOrLong HTMLTimeElement instance IsHTMLElementOrLong HTMLTextAreaElement instance IsHTMLElementOrLong HTMLTemplateElement instance IsHTMLElementOrLong HTMLTableSectionElement instance IsHTMLElementOrLong HTMLTableRowElement instance IsHTMLElementOrLong HTMLTableElement instance IsHTMLElementOrLong HTMLTableColElement instance IsHTMLElementOrLong HTMLTableCellElement instance IsHTMLElementOrLong HTMLTableCaptionElement instance IsHTMLElementOrLong HTMLStyleElement instance IsHTMLElementOrLong HTMLSpanElement instance IsHTMLElementOrLong HTMLSourceElement instance IsHTMLElementOrLong HTMLSlotElement instance IsHTMLElementOrLong HTMLSelectElement instance IsHTMLElementOrLong HTMLScriptElement instance IsHTMLElementOrLong HTMLQuoteElement instance IsHTMLElementOrLong HTMLProgressElement instance IsHTMLElementOrLong HTMLPreElement instance IsHTMLElementOrLong HTMLPictureElement instance IsHTMLElementOrLong HTMLParamElement instance IsHTMLElementOrLong HTMLParagraphElement instance IsHTMLElementOrLong HTMLOutputElement instance IsHTMLElementOrLong HTMLOptionElement instance IsHTMLElementOrLong HTMLOptGroupElement instance IsHTMLElementOrLong HTMLObjectElement instance IsHTMLElementOrLong HTMLOListElement instance IsHTMLElementOrLong HTMLModElement instance IsHTMLElementOrLong HTMLMeterElement instance IsHTMLElementOrLong HTMLMetaElement instance IsHTMLElementOrLong HTMLMenuElement instance IsHTMLElementOrLong HTMLMediaElement instance IsHTMLElementOrLong HTMLMarqueeElement instance IsHTMLElementOrLong HTMLMapElement instance IsHTMLElementOrLong HTMLLinkElement instance IsHTMLElementOrLong HTMLLegendElement instance IsHTMLElementOrLong HTMLLabelElement instance IsHTMLElementOrLong HTMLLIElement instance IsHTMLElementOrLong HTMLKeygenElement instance IsHTMLElementOrLong HTMLInputElement instance IsHTMLElementOrLong HTMLImageElement instance IsHTMLElementOrLong HTMLIFrameElement instance IsHTMLElementOrLong HTMLHtmlElement instance IsHTMLElementOrLong HTMLHeadingElement instance IsHTMLElementOrLong HTMLHeadElement instance IsHTMLElementOrLong HTMLHRElement instance IsHTMLElementOrLong HTMLFrameSetElement instance IsHTMLElementOrLong HTMLFrameElement instance IsHTMLElementOrLong HTMLFormElement instance IsHTMLElementOrLong HTMLFontElement instance IsHTMLElementOrLong HTMLFieldSetElement instance IsHTMLElementOrLong HTMLEmbedElement instance IsHTMLElementOrLong HTMLDivElement instance IsHTMLElementOrLong HTMLDirectoryElement instance IsHTMLElementOrLong HTMLDetailsElement instance IsHTMLElementOrLong HTMLDataListElement instance IsHTMLElementOrLong HTMLDataElement instance IsHTMLElementOrLong HTMLDListElement instance IsHTMLElementOrLong HTMLCanvasElement instance IsHTMLElementOrLong HTMLButtonElement instance IsHTMLElementOrLong HTMLBodyElement instance IsHTMLElementOrLong HTMLBaseElement instance IsHTMLElementOrLong HTMLBRElement instance IsHTMLElementOrLong HTMLAudioElement instance IsHTMLElementOrLong HTMLAttachmentElement instance IsHTMLElementOrLong HTMLAreaElement instance IsHTMLElementOrLong HTMLAppletElement instance IsHTMLElementOrLong HTMLAnchorElement newtype HTMLOptionElementOrGroup = HTMLOptionElementOrGroup { unHTMLOptionElementOrGroup :: JSVal } instance PToJSVal HTMLOptionElementOrGroup where pToJSVal = unHTMLOptionElementOrGroup {-# INLINE pToJSVal #-} instance PFromJSVal HTMLOptionElementOrGroup where pFromJSVal = HTMLOptionElementOrGroup {-# INLINE pFromJSVal #-} instance ToJSVal HTMLOptionElementOrGroup where toJSVal = return . unHTMLOptionElementOrGroup {-# INLINE toJSVal #-} instance FromJSVal HTMLOptionElementOrGroup where fromJSVal = return . fmap HTMLOptionElementOrGroup . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsHTMLOptionElementOrGroup o toHTMLOptionElementOrGroup :: IsHTMLOptionElementOrGroup o => o -> HTMLOptionElementOrGroup toHTMLOptionElementOrGroup = HTMLOptionElementOrGroup . coerce instance IsHTMLOptionElementOrGroup HTMLOptionElementOrGroup instance IsHTMLOptionElementOrGroup HTMLOptGroupElement instance IsHTMLOptionElementOrGroup HTMLOptionElement newtype IDBCursorSource = IDBCursorSource { unIDBCursorSource :: JSVal } instance PToJSVal IDBCursorSource where pToJSVal = unIDBCursorSource {-# INLINE pToJSVal #-} instance PFromJSVal IDBCursorSource where pFromJSVal = IDBCursorSource {-# INLINE pFromJSVal #-} instance ToJSVal IDBCursorSource where toJSVal = return . unIDBCursorSource {-# INLINE toJSVal #-} instance FromJSVal IDBCursorSource where fromJSVal = return . fmap IDBCursorSource . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsIDBCursorSource o toIDBCursorSource :: IsIDBCursorSource o => o -> IDBCursorSource toIDBCursorSource = IDBCursorSource . coerce instance IsIDBCursorSource IDBCursorSource instance IsIDBCursorSource IDBIndex instance IsIDBCursorSource IDBObjectStore newtype IDBKeyPath = IDBKeyPath { unIDBKeyPath :: JSVal } instance PToJSVal IDBKeyPath where pToJSVal = unIDBKeyPath {-# INLINE pToJSVal #-} instance PFromJSVal IDBKeyPath where pFromJSVal = IDBKeyPath {-# INLINE pFromJSVal #-} instance ToJSVal IDBKeyPath where toJSVal = return . unIDBKeyPath {-# INLINE toJSVal #-} instance FromJSVal IDBKeyPath where fromJSVal = return . fmap IDBKeyPath . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (FromJSVal o, ToJSVal o) => IsIDBKeyPath o instance IsIDBKeyPath IDBKeyPath instance IsIDBKeyPath [Text] instance IsIDBKeyPath [JSString] instance IsIDBKeyPath [String] instance IsIDBKeyPath Text instance IsIDBKeyPath JSString instance IsIDBKeyPath String newtype IDBRequestResult = IDBRequestResult { unIDBRequestResult :: JSVal } instance PToJSVal IDBRequestResult where pToJSVal = unIDBRequestResult {-# INLINE pToJSVal #-} instance PFromJSVal IDBRequestResult where pFromJSVal = IDBRequestResult {-# INLINE pFromJSVal #-} instance ToJSVal IDBRequestResult where toJSVal = return . unIDBRequestResult {-# INLINE toJSVal #-} instance FromJSVal IDBRequestResult where fromJSVal = return . fmap IDBRequestResult . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsIDBRequestResult o toIDBRequestResult :: IsIDBRequestResult o => o -> IDBRequestResult toIDBRequestResult = IDBRequestResult . coerce instance IsIDBRequestResult IDBRequestResult instance IsIDBRequestResult JSVal instance IsIDBRequestResult IDBDatabase instance IsIDBRequestResult IDBCursor instance IsIDBRequestResult IDBCursorWithValue newtype IDBRequestSource = IDBRequestSource { unIDBRequestSource :: JSVal } instance PToJSVal IDBRequestSource where pToJSVal = unIDBRequestSource {-# INLINE pToJSVal #-} instance PFromJSVal IDBRequestSource where pFromJSVal = IDBRequestSource {-# INLINE pFromJSVal #-} instance ToJSVal IDBRequestSource where toJSVal = return . unIDBRequestSource {-# INLINE toJSVal #-} instance FromJSVal IDBRequestSource where fromJSVal = return . fmap IDBRequestSource . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsIDBRequestSource o toIDBRequestSource :: IsIDBRequestSource o => o -> IDBRequestSource toIDBRequestSource = IDBRequestSource . coerce instance IsIDBRequestSource IDBRequestSource instance IsIDBRequestSource IDBCursor instance IsIDBRequestSource IDBCursorWithValue instance IsIDBRequestSource IDBIndex instance IsIDBRequestSource IDBObjectStore newtype Int32List = Int32List { unInt32List :: JSVal } instance PToJSVal Int32List where pToJSVal = unInt32List {-# INLINE pToJSVal #-} instance PFromJSVal Int32List where pFromJSVal = Int32List {-# INLINE pFromJSVal #-} instance ToJSVal Int32List where toJSVal = return . unInt32List {-# INLINE toJSVal #-} instance FromJSVal Int32List where fromJSVal = return . fmap Int32List . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (FromJSVal o, ToJSVal o) => IsInt32List o instance IsInt32List Int32List instance IsInt32List [GLint] instance IsInt32List Int32Array newtype KeyData = KeyData { unKeyData :: JSVal } instance PToJSVal KeyData where pToJSVal = unKeyData {-# INLINE pToJSVal #-} instance PFromJSVal KeyData where pFromJSVal = KeyData {-# INLINE pFromJSVal #-} instance ToJSVal KeyData where toJSVal = return . unKeyData {-# INLINE toJSVal #-} instance FromJSVal KeyData where fromJSVal = return . fmap KeyData . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsKeyData o toKeyData :: IsKeyData o => o -> KeyData toKeyData = KeyData . coerce instance IsKeyData KeyData instance IsKeyData JsonWebKey instance IsKeyData BinaryData instance IsKeyData BufferSource instance IsKeyData ArrayBufferView instance IsKeyData ArrayBuffer newtype MediaProvider = MediaProvider { unMediaProvider :: JSVal } instance PToJSVal MediaProvider where pToJSVal = unMediaProvider {-# INLINE pToJSVal #-} instance PFromJSVal MediaProvider where pFromJSVal = MediaProvider {-# INLINE pFromJSVal #-} instance ToJSVal MediaProvider where toJSVal = return . unMediaProvider {-# INLINE toJSVal #-} instance FromJSVal MediaProvider where fromJSVal = return . fmap MediaProvider . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsMediaProvider o toMediaProvider :: IsMediaProvider o => o -> MediaProvider toMediaProvider = MediaProvider . coerce instance IsMediaProvider MediaProvider instance IsMediaProvider MediaStream instance IsMediaProvider MediaSource instance IsMediaProvider Blob instance IsMediaProvider File newtype MediaStreamTrackOrKind = MediaStreamTrackOrKind { unMediaStreamTrackOrKind :: JSVal } instance PToJSVal MediaStreamTrackOrKind where pToJSVal = unMediaStreamTrackOrKind {-# INLINE pToJSVal #-} instance PFromJSVal MediaStreamTrackOrKind where pFromJSVal = MediaStreamTrackOrKind {-# INLINE pFromJSVal #-} instance ToJSVal MediaStreamTrackOrKind where toJSVal = return . unMediaStreamTrackOrKind {-# INLINE toJSVal #-} instance FromJSVal MediaStreamTrackOrKind where fromJSVal = return . fmap MediaStreamTrackOrKind . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (FromJSVal o, ToJSVal o) => IsMediaStreamTrackOrKind o instance IsMediaStreamTrackOrKind MediaStreamTrackOrKind instance IsMediaStreamTrackOrKind Text instance IsMediaStreamTrackOrKind JSString instance IsMediaStreamTrackOrKind String instance IsMediaStreamTrackOrKind MediaStreamTrack instance IsMediaStreamTrackOrKind CanvasCaptureMediaStreamTrack newtype MessageEventSource = MessageEventSource { unMessageEventSource :: JSVal } instance PToJSVal MessageEventSource where pToJSVal = unMessageEventSource {-# INLINE pToJSVal #-} instance PFromJSVal MessageEventSource where pFromJSVal = MessageEventSource {-# INLINE pFromJSVal #-} instance ToJSVal MessageEventSource where toJSVal = return . unMessageEventSource {-# INLINE toJSVal #-} instance FromJSVal MessageEventSource where fromJSVal = return . fmap MessageEventSource . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsMessageEventSource o toMessageEventSource :: IsMessageEventSource o => o -> MessageEventSource toMessageEventSource = MessageEventSource . coerce instance IsMessageEventSource MessageEventSource instance IsMessageEventSource MessagePort instance IsMessageEventSource Window newtype NodeOrString = NodeOrString { unNodeOrString :: JSVal } instance PToJSVal NodeOrString where pToJSVal = unNodeOrString {-# INLINE pToJSVal #-} instance PFromJSVal NodeOrString where pFromJSVal = NodeOrString {-# INLINE pFromJSVal #-} instance ToJSVal NodeOrString where toJSVal = return . unNodeOrString {-# INLINE toJSVal #-} instance FromJSVal NodeOrString where fromJSVal = return . fmap NodeOrString . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (FromJSVal o, ToJSVal o) => IsNodeOrString o instance IsNodeOrString NodeOrString instance IsNodeOrString Text instance IsNodeOrString JSString instance IsNodeOrString String instance IsNodeOrString Node instance IsNodeOrString XMLDocument instance IsNodeOrString ShadowRoot instance IsNodeOrString SVGViewElement instance IsNodeOrString SVGVKernElement instance IsNodeOrString SVGUseElement instance IsNodeOrString SVGTitleElement instance IsNodeOrString SVGTextPositioningElement instance IsNodeOrString SVGTextPathElement instance IsNodeOrString SVGTextElement instance IsNodeOrString SVGTextContentElement instance IsNodeOrString SVGTSpanElement instance IsNodeOrString SVGTRefElement instance IsNodeOrString SVGSymbolElement instance IsNodeOrString SVGSwitchElement instance IsNodeOrString SVGStyleElement instance IsNodeOrString SVGStopElement instance IsNodeOrString SVGSetElement instance IsNodeOrString SVGScriptElement instance IsNodeOrString SVGSVGElement instance IsNodeOrString SVGRectElement instance IsNodeOrString SVGRadialGradientElement instance IsNodeOrString SVGPolylineElement instance IsNodeOrString SVGPolygonElement instance IsNodeOrString SVGPatternElement instance IsNodeOrString SVGPathElement instance IsNodeOrString SVGMissingGlyphElement instance IsNodeOrString SVGMetadataElement instance IsNodeOrString SVGMaskElement instance IsNodeOrString SVGMarkerElement instance IsNodeOrString SVGMPathElement instance IsNodeOrString SVGLinearGradientElement instance IsNodeOrString SVGLineElement instance IsNodeOrString SVGImageElement instance IsNodeOrString SVGHKernElement instance IsNodeOrString SVGGraphicsElement instance IsNodeOrString SVGGradientElement instance IsNodeOrString SVGGlyphRefElement instance IsNodeOrString SVGGlyphElement instance IsNodeOrString SVGGElement instance IsNodeOrString SVGForeignObjectElement instance IsNodeOrString SVGFontFaceUriElement instance IsNodeOrString SVGFontFaceSrcElement instance IsNodeOrString SVGFontFaceNameElement instance IsNodeOrString SVGFontFaceFormatElement instance IsNodeOrString SVGFontFaceElement instance IsNodeOrString SVGFontElement instance IsNodeOrString SVGFilterElement instance IsNodeOrString SVGFETurbulenceElement instance IsNodeOrString SVGFETileElement instance IsNodeOrString SVGFESpotLightElement instance IsNodeOrString SVGFESpecularLightingElement instance IsNodeOrString SVGFEPointLightElement instance IsNodeOrString SVGFEOffsetElement instance IsNodeOrString SVGFEMorphologyElement instance IsNodeOrString SVGFEMergeNodeElement instance IsNodeOrString SVGFEMergeElement instance IsNodeOrString SVGFEImageElement instance IsNodeOrString SVGFEGaussianBlurElement instance IsNodeOrString SVGFEFuncRElement instance IsNodeOrString SVGFEFuncGElement instance IsNodeOrString SVGFEFuncBElement instance IsNodeOrString SVGFEFuncAElement instance IsNodeOrString SVGFEFloodElement instance IsNodeOrString SVGFEDropShadowElement instance IsNodeOrString SVGFEDistantLightElement instance IsNodeOrString SVGFEDisplacementMapElement instance IsNodeOrString SVGFEDiffuseLightingElement instance IsNodeOrString SVGFEConvolveMatrixElement instance IsNodeOrString SVGFECompositeElement instance IsNodeOrString SVGFEComponentTransferElement instance IsNodeOrString SVGFEColorMatrixElement instance IsNodeOrString SVGFEBlendElement instance IsNodeOrString SVGEllipseElement instance IsNodeOrString SVGElement instance IsNodeOrString SVGDescElement instance IsNodeOrString SVGDefsElement instance IsNodeOrString SVGCursorElement instance IsNodeOrString SVGComponentTransferFunctionElement instance IsNodeOrString SVGClipPathElement instance IsNodeOrString SVGCircleElement instance IsNodeOrString SVGAnimationElement instance IsNodeOrString SVGAnimateTransformElement instance IsNodeOrString SVGAnimateMotionElement instance IsNodeOrString SVGAnimateElement instance IsNodeOrString SVGAnimateColorElement instance IsNodeOrString SVGAltGlyphItemElement instance IsNodeOrString SVGAltGlyphElement instance IsNodeOrString SVGAltGlyphDefElement instance IsNodeOrString SVGAElement instance IsNodeOrString ProcessingInstruction instance IsNodeOrString HTMLVideoElement instance IsNodeOrString HTMLUnknownElement instance IsNodeOrString HTMLUListElement instance IsNodeOrString HTMLTrackElement instance IsNodeOrString HTMLTitleElement instance IsNodeOrString HTMLTimeElement instance IsNodeOrString HTMLTextAreaElement instance IsNodeOrString HTMLTemplateElement instance IsNodeOrString HTMLTableSectionElement instance IsNodeOrString HTMLTableRowElement instance IsNodeOrString HTMLTableElement instance IsNodeOrString HTMLTableColElement instance IsNodeOrString HTMLTableCellElement instance IsNodeOrString HTMLTableCaptionElement instance IsNodeOrString HTMLStyleElement instance IsNodeOrString HTMLSpanElement instance IsNodeOrString HTMLSourceElement instance IsNodeOrString HTMLSlotElement instance IsNodeOrString HTMLSelectElement instance IsNodeOrString HTMLScriptElement instance IsNodeOrString HTMLQuoteElement instance IsNodeOrString HTMLProgressElement instance IsNodeOrString HTMLPreElement instance IsNodeOrString HTMLPictureElement instance IsNodeOrString HTMLParamElement instance IsNodeOrString HTMLParagraphElement instance IsNodeOrString HTMLOutputElement instance IsNodeOrString HTMLOptionElement instance IsNodeOrString HTMLOptGroupElement instance IsNodeOrString HTMLObjectElement instance IsNodeOrString HTMLOListElement instance IsNodeOrString HTMLModElement instance IsNodeOrString HTMLMeterElement instance IsNodeOrString HTMLMetaElement instance IsNodeOrString HTMLMenuElement instance IsNodeOrString HTMLMediaElement instance IsNodeOrString HTMLMarqueeElement instance IsNodeOrString HTMLMapElement instance IsNodeOrString HTMLLinkElement instance IsNodeOrString HTMLLegendElement instance IsNodeOrString HTMLLabelElement instance IsNodeOrString HTMLLIElement instance IsNodeOrString HTMLKeygenElement instance IsNodeOrString HTMLInputElement instance IsNodeOrString HTMLImageElement instance IsNodeOrString HTMLIFrameElement instance IsNodeOrString HTMLHtmlElement instance IsNodeOrString HTMLHeadingElement instance IsNodeOrString HTMLHeadElement instance IsNodeOrString HTMLHRElement instance IsNodeOrString HTMLFrameSetElement instance IsNodeOrString HTMLFrameElement instance IsNodeOrString HTMLFormElement instance IsNodeOrString HTMLFontElement instance IsNodeOrString HTMLFieldSetElement instance IsNodeOrString HTMLEmbedElement instance IsNodeOrString HTMLElement instance IsNodeOrString HTMLDocument instance IsNodeOrString HTMLDivElement instance IsNodeOrString HTMLDirectoryElement instance IsNodeOrString HTMLDetailsElement instance IsNodeOrString HTMLDataListElement instance IsNodeOrString HTMLDataElement instance IsNodeOrString HTMLDListElement instance IsNodeOrString HTMLCanvasElement instance IsNodeOrString HTMLButtonElement instance IsNodeOrString HTMLBodyElement instance IsNodeOrString HTMLBaseElement instance IsNodeOrString HTMLBRElement instance IsNodeOrString HTMLAudioElement instance IsNodeOrString HTMLAttachmentElement instance IsNodeOrString HTMLAreaElement instance IsNodeOrString HTMLAppletElement instance IsNodeOrString HTMLAnchorElement instance IsNodeOrString Element instance IsNodeOrString DocumentType instance IsNodeOrString DocumentFragment instance IsNodeOrString Document instance IsNodeOrString Comment instance IsNodeOrString CharacterData instance IsNodeOrString CDATASection instance IsNodeOrString Attr newtype RTCIceCandidateOrInit = RTCIceCandidateOrInit { unRTCIceCandidateOrInit :: JSVal } instance PToJSVal RTCIceCandidateOrInit where pToJSVal = unRTCIceCandidateOrInit {-# INLINE pToJSVal #-} instance PFromJSVal RTCIceCandidateOrInit where pFromJSVal = RTCIceCandidateOrInit {-# INLINE pFromJSVal #-} instance ToJSVal RTCIceCandidateOrInit where toJSVal = return . unRTCIceCandidateOrInit {-# INLINE toJSVal #-} instance FromJSVal RTCIceCandidateOrInit where fromJSVal = return . fmap RTCIceCandidateOrInit . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsRTCIceCandidateOrInit o toRTCIceCandidateOrInit :: IsRTCIceCandidateOrInit o => o -> RTCIceCandidateOrInit toRTCIceCandidateOrInit = RTCIceCandidateOrInit . coerce instance IsRTCIceCandidateOrInit RTCIceCandidateOrInit instance IsRTCIceCandidateOrInit RTCIceCandidate instance IsRTCIceCandidateOrInit RTCIceCandidateInit newtype RadioNodeListOrElement = RadioNodeListOrElement { unRadioNodeListOrElement :: JSVal } instance PToJSVal RadioNodeListOrElement where pToJSVal = unRadioNodeListOrElement {-# INLINE pToJSVal #-} instance PFromJSVal RadioNodeListOrElement where pFromJSVal = RadioNodeListOrElement {-# INLINE pFromJSVal #-} instance ToJSVal RadioNodeListOrElement where toJSVal = return . unRadioNodeListOrElement {-# INLINE toJSVal #-} instance FromJSVal RadioNodeListOrElement where fromJSVal = return . fmap RadioNodeListOrElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsRadioNodeListOrElement o toRadioNodeListOrElement :: IsRadioNodeListOrElement o => o -> RadioNodeListOrElement toRadioNodeListOrElement = RadioNodeListOrElement . coerce instance IsRadioNodeListOrElement RadioNodeListOrElement instance IsRadioNodeListOrElement Element instance IsRadioNodeListOrElement SVGViewElement instance IsRadioNodeListOrElement SVGVKernElement instance IsRadioNodeListOrElement SVGUseElement instance IsRadioNodeListOrElement SVGTitleElement instance IsRadioNodeListOrElement SVGTextPositioningElement instance IsRadioNodeListOrElement SVGTextPathElement instance IsRadioNodeListOrElement SVGTextElement instance IsRadioNodeListOrElement SVGTextContentElement instance IsRadioNodeListOrElement SVGTSpanElement instance IsRadioNodeListOrElement SVGTRefElement instance IsRadioNodeListOrElement SVGSymbolElement instance IsRadioNodeListOrElement SVGSwitchElement instance IsRadioNodeListOrElement SVGStyleElement instance IsRadioNodeListOrElement SVGStopElement instance IsRadioNodeListOrElement SVGSetElement instance IsRadioNodeListOrElement SVGScriptElement instance IsRadioNodeListOrElement SVGSVGElement instance IsRadioNodeListOrElement SVGRectElement instance IsRadioNodeListOrElement SVGRadialGradientElement instance IsRadioNodeListOrElement SVGPolylineElement instance IsRadioNodeListOrElement SVGPolygonElement instance IsRadioNodeListOrElement SVGPatternElement instance IsRadioNodeListOrElement SVGPathElement instance IsRadioNodeListOrElement SVGMissingGlyphElement instance IsRadioNodeListOrElement SVGMetadataElement instance IsRadioNodeListOrElement SVGMaskElement instance IsRadioNodeListOrElement SVGMarkerElement instance IsRadioNodeListOrElement SVGMPathElement instance IsRadioNodeListOrElement SVGLinearGradientElement instance IsRadioNodeListOrElement SVGLineElement instance IsRadioNodeListOrElement SVGImageElement instance IsRadioNodeListOrElement SVGHKernElement instance IsRadioNodeListOrElement SVGGraphicsElement instance IsRadioNodeListOrElement SVGGradientElement instance IsRadioNodeListOrElement SVGGlyphRefElement instance IsRadioNodeListOrElement SVGGlyphElement instance IsRadioNodeListOrElement SVGGElement instance IsRadioNodeListOrElement SVGForeignObjectElement instance IsRadioNodeListOrElement SVGFontFaceUriElement instance IsRadioNodeListOrElement SVGFontFaceSrcElement instance IsRadioNodeListOrElement SVGFontFaceNameElement instance IsRadioNodeListOrElement SVGFontFaceFormatElement instance IsRadioNodeListOrElement SVGFontFaceElement instance IsRadioNodeListOrElement SVGFontElement instance IsRadioNodeListOrElement SVGFilterElement instance IsRadioNodeListOrElement SVGFETurbulenceElement instance IsRadioNodeListOrElement SVGFETileElement instance IsRadioNodeListOrElement SVGFESpotLightElement instance IsRadioNodeListOrElement SVGFESpecularLightingElement instance IsRadioNodeListOrElement SVGFEPointLightElement instance IsRadioNodeListOrElement SVGFEOffsetElement instance IsRadioNodeListOrElement SVGFEMorphologyElement instance IsRadioNodeListOrElement SVGFEMergeNodeElement instance IsRadioNodeListOrElement SVGFEMergeElement instance IsRadioNodeListOrElement SVGFEImageElement instance IsRadioNodeListOrElement SVGFEGaussianBlurElement instance IsRadioNodeListOrElement SVGFEFuncRElement instance IsRadioNodeListOrElement SVGFEFuncGElement instance IsRadioNodeListOrElement SVGFEFuncBElement instance IsRadioNodeListOrElement SVGFEFuncAElement instance IsRadioNodeListOrElement SVGFEFloodElement instance IsRadioNodeListOrElement SVGFEDropShadowElement instance IsRadioNodeListOrElement SVGFEDistantLightElement instance IsRadioNodeListOrElement SVGFEDisplacementMapElement instance IsRadioNodeListOrElement SVGFEDiffuseLightingElement instance IsRadioNodeListOrElement SVGFEConvolveMatrixElement instance IsRadioNodeListOrElement SVGFECompositeElement instance IsRadioNodeListOrElement SVGFEComponentTransferElement instance IsRadioNodeListOrElement SVGFEColorMatrixElement instance IsRadioNodeListOrElement SVGFEBlendElement instance IsRadioNodeListOrElement SVGEllipseElement instance IsRadioNodeListOrElement SVGElement instance IsRadioNodeListOrElement SVGDescElement instance IsRadioNodeListOrElement SVGDefsElement instance IsRadioNodeListOrElement SVGCursorElement instance IsRadioNodeListOrElement SVGComponentTransferFunctionElement instance IsRadioNodeListOrElement SVGClipPathElement instance IsRadioNodeListOrElement SVGCircleElement instance IsRadioNodeListOrElement SVGAnimationElement instance IsRadioNodeListOrElement SVGAnimateTransformElement instance IsRadioNodeListOrElement SVGAnimateMotionElement instance IsRadioNodeListOrElement SVGAnimateElement instance IsRadioNodeListOrElement SVGAnimateColorElement instance IsRadioNodeListOrElement SVGAltGlyphItemElement instance IsRadioNodeListOrElement SVGAltGlyphElement instance IsRadioNodeListOrElement SVGAltGlyphDefElement instance IsRadioNodeListOrElement SVGAElement instance IsRadioNodeListOrElement HTMLVideoElement instance IsRadioNodeListOrElement HTMLUnknownElement instance IsRadioNodeListOrElement HTMLUListElement instance IsRadioNodeListOrElement HTMLTrackElement instance IsRadioNodeListOrElement HTMLTitleElement instance IsRadioNodeListOrElement HTMLTimeElement instance IsRadioNodeListOrElement HTMLTextAreaElement instance IsRadioNodeListOrElement HTMLTemplateElement instance IsRadioNodeListOrElement HTMLTableSectionElement instance IsRadioNodeListOrElement HTMLTableRowElement instance IsRadioNodeListOrElement HTMLTableElement instance IsRadioNodeListOrElement HTMLTableColElement instance IsRadioNodeListOrElement HTMLTableCellElement instance IsRadioNodeListOrElement HTMLTableCaptionElement instance IsRadioNodeListOrElement HTMLStyleElement instance IsRadioNodeListOrElement HTMLSpanElement instance IsRadioNodeListOrElement HTMLSourceElement instance IsRadioNodeListOrElement HTMLSlotElement instance IsRadioNodeListOrElement HTMLSelectElement instance IsRadioNodeListOrElement HTMLScriptElement instance IsRadioNodeListOrElement HTMLQuoteElement instance IsRadioNodeListOrElement HTMLProgressElement instance IsRadioNodeListOrElement HTMLPreElement instance IsRadioNodeListOrElement HTMLPictureElement instance IsRadioNodeListOrElement HTMLParamElement instance IsRadioNodeListOrElement HTMLParagraphElement instance IsRadioNodeListOrElement HTMLOutputElement instance IsRadioNodeListOrElement HTMLOptionElement instance IsRadioNodeListOrElement HTMLOptGroupElement instance IsRadioNodeListOrElement HTMLObjectElement instance IsRadioNodeListOrElement HTMLOListElement instance IsRadioNodeListOrElement HTMLModElement instance IsRadioNodeListOrElement HTMLMeterElement instance IsRadioNodeListOrElement HTMLMetaElement instance IsRadioNodeListOrElement HTMLMenuElement instance IsRadioNodeListOrElement HTMLMediaElement instance IsRadioNodeListOrElement HTMLMarqueeElement instance IsRadioNodeListOrElement HTMLMapElement instance IsRadioNodeListOrElement HTMLLinkElement instance IsRadioNodeListOrElement HTMLLegendElement instance IsRadioNodeListOrElement HTMLLabelElement instance IsRadioNodeListOrElement HTMLLIElement instance IsRadioNodeListOrElement HTMLKeygenElement instance IsRadioNodeListOrElement HTMLInputElement instance IsRadioNodeListOrElement HTMLImageElement instance IsRadioNodeListOrElement HTMLIFrameElement instance IsRadioNodeListOrElement HTMLHtmlElement instance IsRadioNodeListOrElement HTMLHeadingElement instance IsRadioNodeListOrElement HTMLHeadElement instance IsRadioNodeListOrElement HTMLHRElement instance IsRadioNodeListOrElement HTMLFrameSetElement instance IsRadioNodeListOrElement HTMLFrameElement instance IsRadioNodeListOrElement HTMLFormElement instance IsRadioNodeListOrElement HTMLFontElement instance IsRadioNodeListOrElement HTMLFieldSetElement instance IsRadioNodeListOrElement HTMLEmbedElement instance IsRadioNodeListOrElement HTMLElement instance IsRadioNodeListOrElement HTMLDivElement instance IsRadioNodeListOrElement HTMLDirectoryElement instance IsRadioNodeListOrElement HTMLDetailsElement instance IsRadioNodeListOrElement HTMLDataListElement instance IsRadioNodeListOrElement HTMLDataElement instance IsRadioNodeListOrElement HTMLDListElement instance IsRadioNodeListOrElement HTMLCanvasElement instance IsRadioNodeListOrElement HTMLButtonElement instance IsRadioNodeListOrElement HTMLBodyElement instance IsRadioNodeListOrElement HTMLBaseElement instance IsRadioNodeListOrElement HTMLBRElement instance IsRadioNodeListOrElement HTMLAudioElement instance IsRadioNodeListOrElement HTMLAttachmentElement instance IsRadioNodeListOrElement HTMLAreaElement instance IsRadioNodeListOrElement HTMLAppletElement instance IsRadioNodeListOrElement HTMLAnchorElement instance IsRadioNodeListOrElement RadioNodeList newtype RenderingContext = RenderingContext { unRenderingContext :: JSVal } instance PToJSVal RenderingContext where pToJSVal = unRenderingContext {-# INLINE pToJSVal #-} instance PFromJSVal RenderingContext where pFromJSVal = RenderingContext {-# INLINE pFromJSVal #-} instance ToJSVal RenderingContext where toJSVal = return . unRenderingContext {-# INLINE toJSVal #-} instance FromJSVal RenderingContext where fromJSVal = return . fmap RenderingContext . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsRenderingContext o toRenderingContext :: IsRenderingContext o => o -> RenderingContext toRenderingContext = RenderingContext . coerce instance IsRenderingContext RenderingContext instance IsRenderingContext WebGLRenderingContextBase instance IsRenderingContext WebGLRenderingContext instance IsRenderingContext WebGL2RenderingContext instance IsRenderingContext CanvasRenderingContext2D newtype SQLValue = SQLValue { unSQLValue :: JSVal } instance PToJSVal SQLValue where pToJSVal = unSQLValue {-# INLINE pToJSVal #-} instance PFromJSVal SQLValue where pFromJSVal = SQLValue {-# INLINE pFromJSVal #-} instance ToJSVal SQLValue where toJSVal = return . unSQLValue {-# INLINE toJSVal #-} instance FromJSVal SQLValue where fromJSVal = return . fmap SQLValue . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (FromJSVal o, ToJSVal o) => IsSQLValue o instance IsSQLValue SQLValue instance IsSQLValue (Maybe Text) instance IsSQLValue (Maybe JSString) instance IsSQLValue (Maybe String) instance IsSQLValue Double newtype StringOrArrayBuffer = StringOrArrayBuffer { unStringOrArrayBuffer :: JSVal } instance PToJSVal StringOrArrayBuffer where pToJSVal = unStringOrArrayBuffer {-# INLINE pToJSVal #-} instance PFromJSVal StringOrArrayBuffer where pFromJSVal = StringOrArrayBuffer {-# INLINE pFromJSVal #-} instance ToJSVal StringOrArrayBuffer where toJSVal = return . unStringOrArrayBuffer {-# INLINE toJSVal #-} instance FromJSVal StringOrArrayBuffer where fromJSVal = return . fmap StringOrArrayBuffer . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (FromJSVal o, ToJSVal o) => IsStringOrArrayBuffer o instance IsStringOrArrayBuffer StringOrArrayBuffer instance IsStringOrArrayBuffer ArrayBuffer instance IsStringOrArrayBuffer Text instance IsStringOrArrayBuffer JSString instance IsStringOrArrayBuffer String newtype StringOrBinaryData = StringOrBinaryData { unStringOrBinaryData :: JSVal } instance PToJSVal StringOrBinaryData where pToJSVal = unStringOrBinaryData {-# INLINE pToJSVal #-} instance PFromJSVal StringOrBinaryData where pFromJSVal = StringOrBinaryData {-# INLINE pFromJSVal #-} instance ToJSVal StringOrBinaryData where toJSVal = return . unStringOrBinaryData {-# INLINE toJSVal #-} instance FromJSVal StringOrBinaryData where fromJSVal = return . fmap StringOrBinaryData . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (FromJSVal o, ToJSVal o) => IsStringOrBinaryData o instance IsStringOrBinaryData StringOrBinaryData instance IsStringOrBinaryData BinaryData instance IsStringOrBinaryData BufferSource instance IsStringOrBinaryData ArrayBufferView instance IsStringOrBinaryData ArrayBuffer instance IsStringOrBinaryData Text instance IsStringOrBinaryData JSString instance IsStringOrBinaryData String newtype StringOrStrings = StringOrStrings { unStringOrStrings :: JSVal } instance PToJSVal StringOrStrings where pToJSVal = unStringOrStrings {-# INLINE pToJSVal #-} instance PFromJSVal StringOrStrings where pFromJSVal = StringOrStrings {-# INLINE pFromJSVal #-} instance ToJSVal StringOrStrings where toJSVal = return . unStringOrStrings {-# INLINE toJSVal #-} instance FromJSVal StringOrStrings where fromJSVal = return . fmap StringOrStrings . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (FromJSVal o, ToJSVal o) => IsStringOrStrings o instance IsStringOrStrings StringOrStrings instance IsStringOrStrings [Text] instance IsStringOrStrings [JSString] instance IsStringOrStrings [String] instance IsStringOrStrings Text instance IsStringOrStrings JSString instance IsStringOrStrings String newtype TexImageSource = TexImageSource { unTexImageSource :: JSVal } instance PToJSVal TexImageSource where pToJSVal = unTexImageSource {-# INLINE pToJSVal #-} instance PFromJSVal TexImageSource where pFromJSVal = TexImageSource {-# INLINE pFromJSVal #-} instance ToJSVal TexImageSource where toJSVal = return . unTexImageSource {-# INLINE toJSVal #-} instance FromJSVal TexImageSource where fromJSVal = return . fmap TexImageSource . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsTexImageSource o toTexImageSource :: IsTexImageSource o => o -> TexImageSource toTexImageSource = TexImageSource . coerce instance IsTexImageSource TexImageSource instance IsTexImageSource ImageData instance IsTexImageSource HTMLImageElement instance IsTexImageSource HTMLVideoElement instance IsTexImageSource HTMLCanvasElement newtype Track = Track { unTrack :: JSVal } instance PToJSVal Track where pToJSVal = unTrack {-# INLINE pToJSVal #-} instance PFromJSVal Track where pFromJSVal = Track {-# INLINE pFromJSVal #-} instance ToJSVal Track where toJSVal = return . unTrack {-# INLINE toJSVal #-} instance FromJSVal Track where fromJSVal = return . fmap Track . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsTrack o toTrack :: IsTrack o => o -> Track toTrack = Track . coerce instance IsTrack Track instance IsTrack TextTrack instance IsTrack AudioTrack instance IsTrack VideoTrack newtype URLSearchParamsInit = URLSearchParamsInit { unURLSearchParamsInit :: JSVal } instance PToJSVal URLSearchParamsInit where pToJSVal = unURLSearchParamsInit {-# INLINE pToJSVal #-} instance PFromJSVal URLSearchParamsInit where pFromJSVal = URLSearchParamsInit {-# INLINE pFromJSVal #-} instance ToJSVal URLSearchParamsInit where toJSVal = return . unURLSearchParamsInit {-# INLINE toJSVal #-} instance FromJSVal URLSearchParamsInit where fromJSVal = return . fmap URLSearchParamsInit . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (FromJSVal o, ToJSVal o) => IsURLSearchParamsInit o instance IsURLSearchParamsInit URLSearchParamsInit instance IsURLSearchParamsInit Text instance IsURLSearchParamsInit JSString instance IsURLSearchParamsInit String instance IsURLSearchParamsInit [[Text]] instance IsURLSearchParamsInit [[JSString]] instance IsURLSearchParamsInit [[String]] newtype XMLHttpRequestBody = XMLHttpRequestBody { unXMLHttpRequestBody :: JSVal } instance PToJSVal XMLHttpRequestBody where pToJSVal = unXMLHttpRequestBody {-# INLINE pToJSVal #-} instance PFromJSVal XMLHttpRequestBody where pFromJSVal = XMLHttpRequestBody {-# INLINE pFromJSVal #-} instance ToJSVal XMLHttpRequestBody where toJSVal = return . unXMLHttpRequestBody {-# INLINE toJSVal #-} instance FromJSVal XMLHttpRequestBody where fromJSVal = return . fmap XMLHttpRequestBody . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} 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 "GHCJS.DOM.ANGLEInstancedArrays". -- -- newtype ANGLEInstancedArrays = ANGLEInstancedArrays { unANGLEInstancedArrays :: JSVal } instance Eq (ANGLEInstancedArrays) where (ANGLEInstancedArrays a) == (ANGLEInstancedArrays b) = js_eq a b instance PToJSVal ANGLEInstancedArrays where pToJSVal = unANGLEInstancedArrays {-# INLINE pToJSVal #-} instance PFromJSVal ANGLEInstancedArrays where pFromJSVal = ANGLEInstancedArrays {-# INLINE pFromJSVal #-} instance ToJSVal ANGLEInstancedArrays where toJSVal = return . unANGLEInstancedArrays {-# INLINE toJSVal #-} instance FromJSVal ANGLEInstancedArrays where fromJSVal = return . fmap ANGLEInstancedArrays . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject ANGLEInstancedArrays where typeGType _ = gTypeANGLEInstancedArrays {-# INLINE typeGType #-} noANGLEInstancedArrays :: Maybe ANGLEInstancedArrays noANGLEInstancedArrays = Nothing {-# INLINE noANGLEInstancedArrays #-} foreign import javascript unsafe "window[\"ANGLEInstancedArrays\"]" gTypeANGLEInstancedArrays :: GType -- | Functions for this inteface are in "GHCJS.DOM.AbstractWorker". -- -- newtype AbstractWorker = AbstractWorker { unAbstractWorker :: JSVal } instance Eq (AbstractWorker) where (AbstractWorker a) == (AbstractWorker b) = js_eq a b instance PToJSVal AbstractWorker where pToJSVal = unAbstractWorker {-# INLINE pToJSVal #-} instance PFromJSVal AbstractWorker where pFromJSVal = AbstractWorker {-# INLINE pFromJSVal #-} instance ToJSVal AbstractWorker where toJSVal = return . unAbstractWorker {-# INLINE toJSVal #-} instance FromJSVal AbstractWorker where fromJSVal = return . fmap AbstractWorker . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsGObject o) => IsAbstractWorker o toAbstractWorker :: IsAbstractWorker o => o -> AbstractWorker toAbstractWorker = AbstractWorker . coerce instance IsAbstractWorker AbstractWorker instance IsGObject AbstractWorker where typeGType _ = gTypeAbstractWorker {-# INLINE typeGType #-} noAbstractWorker :: Maybe AbstractWorker noAbstractWorker = Nothing {-# INLINE noAbstractWorker #-} foreign import javascript unsafe "window[\"AbstractWorker\"]" gTypeAbstractWorker :: GType -- | Functions for this inteface are in "GHCJS.DOM.Acceleration". -- -- newtype Acceleration = Acceleration { unAcceleration :: JSVal } instance Eq (Acceleration) where (Acceleration a) == (Acceleration b) = js_eq a b instance PToJSVal Acceleration where pToJSVal = unAcceleration {-# INLINE pToJSVal #-} instance PFromJSVal Acceleration where pFromJSVal = Acceleration {-# INLINE pFromJSVal #-} instance ToJSVal Acceleration where toJSVal = return . unAcceleration {-# INLINE toJSVal #-} instance FromJSVal Acceleration where fromJSVal = return . fmap Acceleration . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject Acceleration where typeGType _ = gTypeAcceleration {-# INLINE typeGType #-} noAcceleration :: Maybe Acceleration noAcceleration = Nothing {-# INLINE noAcceleration #-} foreign import javascript unsafe "window[\"Acceleration\"]" gTypeAcceleration :: GType -- | Functions for this inteface are in "GHCJS.DOM.AddEventListenerOptions". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventListenerOptions" -- -- newtype AddEventListenerOptions = AddEventListenerOptions { unAddEventListenerOptions :: JSVal } instance Eq (AddEventListenerOptions) where (AddEventListenerOptions a) == (AddEventListenerOptions b) = js_eq a b instance PToJSVal AddEventListenerOptions where pToJSVal = unAddEventListenerOptions {-# INLINE pToJSVal #-} instance PFromJSVal AddEventListenerOptions where pFromJSVal = AddEventListenerOptions {-# INLINE pFromJSVal #-} instance ToJSVal AddEventListenerOptions where toJSVal = return . unAddEventListenerOptions {-# INLINE toJSVal #-} instance FromJSVal AddEventListenerOptions where fromJSVal = return . fmap AddEventListenerOptions . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventListenerOptions AddEventListenerOptions instance IsGObject AddEventListenerOptions where typeGType _ = gTypeAddEventListenerOptions {-# INLINE typeGType #-} noAddEventListenerOptions :: Maybe AddEventListenerOptions noAddEventListenerOptions = Nothing {-# INLINE noAddEventListenerOptions #-} foreign import javascript unsafe "window[\"AddEventListenerOptions\"]" gTypeAddEventListenerOptions :: GType -- | Functions for this inteface are in "GHCJS.DOM.AesCbcCfbParams". -- Base interface functions are in: -- -- * "GHCJS.DOM.CryptoAlgorithmParameters" -- -- newtype AesCbcCfbParams = AesCbcCfbParams { unAesCbcCfbParams :: JSVal } instance Eq (AesCbcCfbParams) where (AesCbcCfbParams a) == (AesCbcCfbParams b) = js_eq a b instance PToJSVal AesCbcCfbParams where pToJSVal = unAesCbcCfbParams {-# INLINE pToJSVal #-} instance PFromJSVal AesCbcCfbParams where pFromJSVal = AesCbcCfbParams {-# INLINE pFromJSVal #-} instance ToJSVal AesCbcCfbParams where toJSVal = return . unAesCbcCfbParams {-# INLINE toJSVal #-} instance FromJSVal AesCbcCfbParams where fromJSVal = return . fmap AesCbcCfbParams . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsCryptoAlgorithmParameters AesCbcCfbParams instance IsGObject AesCbcCfbParams where typeGType _ = gTypeAesCbcCfbParams {-# INLINE typeGType #-} noAesCbcCfbParams :: Maybe AesCbcCfbParams noAesCbcCfbParams = Nothing {-# INLINE noAesCbcCfbParams #-} foreign import javascript unsafe "window[\"AesCbcCfbParams\"]" gTypeAesCbcCfbParams :: GType -- | Functions for this inteface are in "GHCJS.DOM.AesCtrParams". -- Base interface functions are in: -- -- * "GHCJS.DOM.CryptoAlgorithmParameters" -- -- newtype AesCtrParams = AesCtrParams { unAesCtrParams :: JSVal } instance Eq (AesCtrParams) where (AesCtrParams a) == (AesCtrParams b) = js_eq a b instance PToJSVal AesCtrParams where pToJSVal = unAesCtrParams {-# INLINE pToJSVal #-} instance PFromJSVal AesCtrParams where pFromJSVal = AesCtrParams {-# INLINE pFromJSVal #-} instance ToJSVal AesCtrParams where toJSVal = return . unAesCtrParams {-# INLINE toJSVal #-} instance FromJSVal AesCtrParams where fromJSVal = return . fmap AesCtrParams . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsCryptoAlgorithmParameters AesCtrParams instance IsGObject AesCtrParams where typeGType _ = gTypeAesCtrParams {-# INLINE typeGType #-} noAesCtrParams :: Maybe AesCtrParams noAesCtrParams = Nothing {-# INLINE noAesCtrParams #-} foreign import javascript unsafe "window[\"AesCtrParams\"]" gTypeAesCtrParams :: GType -- | Functions for this inteface are in "GHCJS.DOM.AesGcmParams". -- Base interface functions are in: -- -- * "GHCJS.DOM.CryptoAlgorithmParameters" -- -- newtype AesGcmParams = AesGcmParams { unAesGcmParams :: JSVal } instance Eq (AesGcmParams) where (AesGcmParams a) == (AesGcmParams b) = js_eq a b instance PToJSVal AesGcmParams where pToJSVal = unAesGcmParams {-# INLINE pToJSVal #-} instance PFromJSVal AesGcmParams where pFromJSVal = AesGcmParams {-# INLINE pFromJSVal #-} instance ToJSVal AesGcmParams where toJSVal = return . unAesGcmParams {-# INLINE toJSVal #-} instance FromJSVal AesGcmParams where fromJSVal = return . fmap AesGcmParams . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsCryptoAlgorithmParameters AesGcmParams instance IsGObject AesGcmParams where typeGType _ = gTypeAesGcmParams {-# INLINE typeGType #-} noAesGcmParams :: Maybe AesGcmParams noAesGcmParams = Nothing {-# INLINE noAesGcmParams #-} foreign import javascript unsafe "window[\"AesGcmParams\"]" gTypeAesGcmParams :: GType -- | Functions for this inteface are in "GHCJS.DOM.AesKeyParams". -- Base interface functions are in: -- -- * "GHCJS.DOM.CryptoAlgorithmParameters" -- -- newtype AesKeyParams = AesKeyParams { unAesKeyParams :: JSVal } instance Eq (AesKeyParams) where (AesKeyParams a) == (AesKeyParams b) = js_eq a b instance PToJSVal AesKeyParams where pToJSVal = unAesKeyParams {-# INLINE pToJSVal #-} instance PFromJSVal AesKeyParams where pFromJSVal = AesKeyParams {-# INLINE pFromJSVal #-} instance ToJSVal AesKeyParams where toJSVal = return . unAesKeyParams {-# INLINE toJSVal #-} instance FromJSVal AesKeyParams where fromJSVal = return . fmap AesKeyParams . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsCryptoAlgorithmParameters AesKeyParams instance IsGObject AesKeyParams where typeGType _ = gTypeAesKeyParams {-# INLINE typeGType #-} noAesKeyParams :: Maybe AesKeyParams noAesKeyParams = Nothing {-# INLINE noAesKeyParams #-} foreign import javascript unsafe "window[\"AesKeyParams\"]" gTypeAesKeyParams :: GType -- | Functions for this inteface are in "GHCJS.DOM.AnalyserNode". -- Base interface functions are in: -- -- * "GHCJS.DOM.AudioNode" -- * "GHCJS.DOM.EventTarget" -- -- newtype AnalyserNode = AnalyserNode { unAnalyserNode :: JSVal } instance Eq (AnalyserNode) where (AnalyserNode a) == (AnalyserNode b) = js_eq a b instance PToJSVal AnalyserNode where pToJSVal = unAnalyserNode {-# INLINE pToJSVal #-} instance PFromJSVal AnalyserNode where pFromJSVal = AnalyserNode {-# INLINE pFromJSVal #-} instance ToJSVal AnalyserNode where toJSVal = return . unAnalyserNode {-# INLINE toJSVal #-} instance FromJSVal AnalyserNode where fromJSVal = return . fmap AnalyserNode . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsAudioNode AnalyserNode instance IsEventTarget AnalyserNode instance IsGObject AnalyserNode where typeGType _ = gTypeAnalyserNode {-# INLINE typeGType #-} noAnalyserNode :: Maybe AnalyserNode noAnalyserNode = Nothing {-# INLINE noAnalyserNode #-} foreign import javascript unsafe "window[\"AnalyserNode\"]" gTypeAnalyserNode :: GType -- | Functions for this inteface are in "GHCJS.DOM.Animatable". -- -- newtype Animatable = Animatable { unAnimatable :: JSVal } instance Eq (Animatable) where (Animatable a) == (Animatable b) = js_eq a b instance PToJSVal Animatable where pToJSVal = unAnimatable {-# INLINE pToJSVal #-} instance PFromJSVal Animatable where pFromJSVal = Animatable {-# INLINE pFromJSVal #-} instance ToJSVal Animatable where toJSVal = return . unAnimatable {-# INLINE toJSVal #-} instance FromJSVal Animatable where fromJSVal = return . fmap Animatable . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsGObject o) => IsAnimatable o toAnimatable :: IsAnimatable o => o -> Animatable toAnimatable = Animatable . coerce instance IsAnimatable Animatable instance IsGObject Animatable where typeGType _ = gTypeAnimatable {-# INLINE typeGType #-} noAnimatable :: Maybe Animatable noAnimatable = Nothing {-# INLINE noAnimatable #-} foreign import javascript unsafe "window[\"Animatable\"]" gTypeAnimatable :: GType -- | Functions for this inteface are in "GHCJS.DOM.Animation". -- -- newtype Animation = Animation { unAnimation :: JSVal } instance Eq (Animation) where (Animation a) == (Animation b) = js_eq a b instance PToJSVal Animation where pToJSVal = unAnimation {-# INLINE pToJSVal #-} instance PFromJSVal Animation where pFromJSVal = Animation {-# INLINE pFromJSVal #-} instance ToJSVal Animation where toJSVal = return . unAnimation {-# INLINE toJSVal #-} instance FromJSVal Animation where fromJSVal = return . fmap Animation . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject Animation where typeGType _ = gTypeAnimation {-# INLINE typeGType #-} noAnimation :: Maybe Animation noAnimation = Nothing {-# INLINE noAnimation #-} foreign import javascript unsafe "window[\"Animation\"]" gTypeAnimation :: GType -- | Functions for this inteface are in "GHCJS.DOM.AnimationEffect". -- -- newtype AnimationEffect = AnimationEffect { unAnimationEffect :: JSVal } instance Eq (AnimationEffect) where (AnimationEffect a) == (AnimationEffect b) = js_eq a b instance PToJSVal AnimationEffect where pToJSVal = unAnimationEffect {-# INLINE pToJSVal #-} instance PFromJSVal AnimationEffect where pFromJSVal = AnimationEffect {-# INLINE pFromJSVal #-} instance ToJSVal AnimationEffect where toJSVal = return . unAnimationEffect {-# INLINE toJSVal #-} instance FromJSVal AnimationEffect where fromJSVal = return . fmap AnimationEffect . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsGObject o) => IsAnimationEffect o toAnimationEffect :: IsAnimationEffect o => o -> AnimationEffect toAnimationEffect = AnimationEffect . coerce instance IsAnimationEffect AnimationEffect instance IsGObject AnimationEffect where typeGType _ = gTypeAnimationEffect {-# INLINE typeGType #-} noAnimationEffect :: Maybe AnimationEffect noAnimationEffect = Nothing {-# INLINE noAnimationEffect #-} foreign import javascript unsafe "window[\"AnimationEffect\"]" gTypeAnimationEffect :: GType -- | Functions for this inteface are in "GHCJS.DOM.AnimationEvent". -- Base interface functions are in: -- -- * "GHCJS.DOM.Event" -- -- newtype AnimationEvent = AnimationEvent { unAnimationEvent :: JSVal } instance Eq (AnimationEvent) where (AnimationEvent a) == (AnimationEvent b) = js_eq a b instance PToJSVal AnimationEvent where pToJSVal = unAnimationEvent {-# INLINE pToJSVal #-} instance PFromJSVal AnimationEvent where pFromJSVal = AnimationEvent {-# INLINE pFromJSVal #-} instance ToJSVal AnimationEvent where toJSVal = return . unAnimationEvent {-# INLINE toJSVal #-} instance FromJSVal AnimationEvent where fromJSVal = return . fmap AnimationEvent . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEvent AnimationEvent instance IsGObject AnimationEvent where typeGType _ = gTypeAnimationEvent {-# INLINE typeGType #-} noAnimationEvent :: Maybe AnimationEvent noAnimationEvent = Nothing {-# INLINE noAnimationEvent #-} foreign import javascript unsafe "window[\"AnimationEvent\"]" gTypeAnimationEvent :: GType -- | Functions for this inteface are in "GHCJS.DOM.AnimationEventInit". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventInit" -- -- newtype AnimationEventInit = AnimationEventInit { unAnimationEventInit :: JSVal } instance Eq (AnimationEventInit) where (AnimationEventInit a) == (AnimationEventInit b) = js_eq a b instance PToJSVal AnimationEventInit where pToJSVal = unAnimationEventInit {-# INLINE pToJSVal #-} instance PFromJSVal AnimationEventInit where pFromJSVal = AnimationEventInit {-# INLINE pFromJSVal #-} instance ToJSVal AnimationEventInit where toJSVal = return . unAnimationEventInit {-# INLINE toJSVal #-} instance FromJSVal AnimationEventInit where fromJSVal = return . fmap AnimationEventInit . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventInit AnimationEventInit instance IsGObject AnimationEventInit where typeGType _ = gTypeAnimationEventInit {-# INLINE typeGType #-} noAnimationEventInit :: Maybe AnimationEventInit noAnimationEventInit = Nothing {-# INLINE noAnimationEventInit #-} foreign import javascript unsafe "window[\"AnimationEventInit\"]" gTypeAnimationEventInit :: GType -- | Functions for this inteface are in "GHCJS.DOM.AnimationTimeline". -- -- newtype AnimationTimeline = AnimationTimeline { unAnimationTimeline :: JSVal } instance Eq (AnimationTimeline) where (AnimationTimeline a) == (AnimationTimeline b) = js_eq a b instance PToJSVal AnimationTimeline where pToJSVal = unAnimationTimeline {-# INLINE pToJSVal #-} instance PFromJSVal AnimationTimeline where pFromJSVal = AnimationTimeline {-# INLINE pFromJSVal #-} instance ToJSVal AnimationTimeline where toJSVal = return . unAnimationTimeline {-# INLINE toJSVal #-} instance FromJSVal AnimationTimeline where fromJSVal = return . fmap AnimationTimeline . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsGObject o) => IsAnimationTimeline o toAnimationTimeline :: IsAnimationTimeline o => o -> AnimationTimeline toAnimationTimeline = AnimationTimeline . coerce instance IsAnimationTimeline AnimationTimeline instance IsGObject AnimationTimeline where typeGType _ = gTypeAnimationTimeline {-# INLINE typeGType #-} noAnimationTimeline :: Maybe AnimationTimeline noAnimationTimeline = Nothing {-# INLINE noAnimationTimeline #-} foreign import javascript unsafe "window[\"AnimationTimeline\"]" gTypeAnimationTimeline :: GType -- | Functions for this inteface are in "GHCJS.DOM.ApplePayError". -- -- newtype ApplePayError = ApplePayError { unApplePayError :: JSVal } instance Eq (ApplePayError) where (ApplePayError a) == (ApplePayError b) = js_eq a b instance PToJSVal ApplePayError where pToJSVal = unApplePayError {-# INLINE pToJSVal #-} instance PFromJSVal ApplePayError where pFromJSVal = ApplePayError {-# INLINE pFromJSVal #-} instance ToJSVal ApplePayError where toJSVal = return . unApplePayError {-# INLINE toJSVal #-} instance FromJSVal ApplePayError where fromJSVal = return . fmap ApplePayError . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject ApplePayError where typeGType _ = gTypeApplePayError {-# INLINE typeGType #-} noApplePayError :: Maybe ApplePayError noApplePayError = Nothing {-# INLINE noApplePayError #-} foreign import javascript unsafe "window[\"ApplePayError\"]" gTypeApplePayError :: GType -- | Functions for this inteface are in "GHCJS.DOM.ApplePayLineItem". -- -- newtype ApplePayLineItem = ApplePayLineItem { unApplePayLineItem :: JSVal } instance Eq (ApplePayLineItem) where (ApplePayLineItem a) == (ApplePayLineItem b) = js_eq a b instance PToJSVal ApplePayLineItem where pToJSVal = unApplePayLineItem {-# INLINE pToJSVal #-} instance PFromJSVal ApplePayLineItem where pFromJSVal = ApplePayLineItem {-# INLINE pFromJSVal #-} instance ToJSVal ApplePayLineItem where toJSVal = return . unApplePayLineItem {-# INLINE toJSVal #-} instance FromJSVal ApplePayLineItem where fromJSVal = return . fmap ApplePayLineItem . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject ApplePayLineItem where typeGType _ = gTypeApplePayLineItem {-# INLINE typeGType #-} noApplePayLineItem :: Maybe ApplePayLineItem noApplePayLineItem = Nothing {-# INLINE noApplePayLineItem #-} foreign import javascript unsafe "window[\"ApplePayLineItem\"]" gTypeApplePayLineItem :: GType -- | Functions for this inteface are in "GHCJS.DOM.ApplePayPayment". -- -- newtype ApplePayPayment = ApplePayPayment { unApplePayPayment :: JSVal } instance Eq (ApplePayPayment) where (ApplePayPayment a) == (ApplePayPayment b) = js_eq a b instance PToJSVal ApplePayPayment where pToJSVal = unApplePayPayment {-# INLINE pToJSVal #-} instance PFromJSVal ApplePayPayment where pFromJSVal = ApplePayPayment {-# INLINE pFromJSVal #-} instance ToJSVal ApplePayPayment where toJSVal = return . unApplePayPayment {-# INLINE toJSVal #-} instance FromJSVal ApplePayPayment where fromJSVal = return . fmap ApplePayPayment . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject ApplePayPayment where typeGType _ = gTypeApplePayPayment {-# INLINE typeGType #-} noApplePayPayment :: Maybe ApplePayPayment noApplePayPayment = Nothing {-# INLINE noApplePayPayment #-} foreign import javascript unsafe "window[\"ApplePayPayment\"]" gTypeApplePayPayment :: GType -- | Functions for this inteface are in "GHCJS.DOM.ApplePayPaymentAuthorizationResult". -- -- newtype ApplePayPaymentAuthorizationResult = ApplePayPaymentAuthorizationResult { unApplePayPaymentAuthorizationResult :: JSVal } instance Eq (ApplePayPaymentAuthorizationResult) where (ApplePayPaymentAuthorizationResult a) == (ApplePayPaymentAuthorizationResult b) = js_eq a b instance PToJSVal ApplePayPaymentAuthorizationResult where pToJSVal = unApplePayPaymentAuthorizationResult {-# INLINE pToJSVal #-} instance PFromJSVal ApplePayPaymentAuthorizationResult where pFromJSVal = ApplePayPaymentAuthorizationResult {-# INLINE pFromJSVal #-} instance ToJSVal ApplePayPaymentAuthorizationResult where toJSVal = return . unApplePayPaymentAuthorizationResult {-# INLINE toJSVal #-} instance FromJSVal ApplePayPaymentAuthorizationResult where fromJSVal = return . fmap ApplePayPaymentAuthorizationResult . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject ApplePayPaymentAuthorizationResult where typeGType _ = gTypeApplePayPaymentAuthorizationResult {-# INLINE typeGType #-} noApplePayPaymentAuthorizationResult :: Maybe ApplePayPaymentAuthorizationResult noApplePayPaymentAuthorizationResult = Nothing {-# INLINE noApplePayPaymentAuthorizationResult #-} foreign import javascript unsafe "window[\"ApplePayPaymentAuthorizationResult\"]" gTypeApplePayPaymentAuthorizationResult :: GType -- | Functions for this inteface are in "GHCJS.DOM.ApplePayPaymentAuthorizedEvent". -- Base interface functions are in: -- -- * "GHCJS.DOM.Event" -- -- newtype ApplePayPaymentAuthorizedEvent = ApplePayPaymentAuthorizedEvent { unApplePayPaymentAuthorizedEvent :: JSVal } instance Eq (ApplePayPaymentAuthorizedEvent) where (ApplePayPaymentAuthorizedEvent a) == (ApplePayPaymentAuthorizedEvent b) = js_eq a b instance PToJSVal ApplePayPaymentAuthorizedEvent where pToJSVal = unApplePayPaymentAuthorizedEvent {-# INLINE pToJSVal #-} instance PFromJSVal ApplePayPaymentAuthorizedEvent where pFromJSVal = ApplePayPaymentAuthorizedEvent {-# INLINE pFromJSVal #-} instance ToJSVal ApplePayPaymentAuthorizedEvent where toJSVal = return . unApplePayPaymentAuthorizedEvent {-# INLINE toJSVal #-} instance FromJSVal ApplePayPaymentAuthorizedEvent where fromJSVal = return . fmap ApplePayPaymentAuthorizedEvent . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEvent ApplePayPaymentAuthorizedEvent instance IsGObject ApplePayPaymentAuthorizedEvent where typeGType _ = gTypeApplePayPaymentAuthorizedEvent {-# INLINE typeGType #-} noApplePayPaymentAuthorizedEvent :: Maybe ApplePayPaymentAuthorizedEvent noApplePayPaymentAuthorizedEvent = Nothing {-# INLINE noApplePayPaymentAuthorizedEvent #-} foreign import javascript unsafe "window[\"ApplePayPaymentAuthorizedEvent\"]" gTypeApplePayPaymentAuthorizedEvent :: GType -- | Functions for this inteface are in "GHCJS.DOM.ApplePayPaymentContact". -- -- newtype ApplePayPaymentContact = ApplePayPaymentContact { unApplePayPaymentContact :: JSVal } instance Eq (ApplePayPaymentContact) where (ApplePayPaymentContact a) == (ApplePayPaymentContact b) = js_eq a b instance PToJSVal ApplePayPaymentContact where pToJSVal = unApplePayPaymentContact {-# INLINE pToJSVal #-} instance PFromJSVal ApplePayPaymentContact where pFromJSVal = ApplePayPaymentContact {-# INLINE pFromJSVal #-} instance ToJSVal ApplePayPaymentContact where toJSVal = return . unApplePayPaymentContact {-# INLINE toJSVal #-} instance FromJSVal ApplePayPaymentContact where fromJSVal = return . fmap ApplePayPaymentContact . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject ApplePayPaymentContact where typeGType _ = gTypeApplePayPaymentContact {-# INLINE typeGType #-} noApplePayPaymentContact :: Maybe ApplePayPaymentContact noApplePayPaymentContact = Nothing {-# INLINE noApplePayPaymentContact #-} foreign import javascript unsafe "window[\"ApplePayPaymentContact\"]" gTypeApplePayPaymentContact :: GType -- | Functions for this inteface are in "GHCJS.DOM.ApplePayPaymentMethod". -- -- newtype ApplePayPaymentMethod = ApplePayPaymentMethod { unApplePayPaymentMethod :: JSVal } instance Eq (ApplePayPaymentMethod) where (ApplePayPaymentMethod a) == (ApplePayPaymentMethod b) = js_eq a b instance PToJSVal ApplePayPaymentMethod where pToJSVal = unApplePayPaymentMethod {-# INLINE pToJSVal #-} instance PFromJSVal ApplePayPaymentMethod where pFromJSVal = ApplePayPaymentMethod {-# INLINE pFromJSVal #-} instance ToJSVal ApplePayPaymentMethod where toJSVal = return . unApplePayPaymentMethod {-# INLINE toJSVal #-} instance FromJSVal ApplePayPaymentMethod where fromJSVal = return . fmap ApplePayPaymentMethod . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject ApplePayPaymentMethod where typeGType _ = gTypeApplePayPaymentMethod {-# INLINE typeGType #-} noApplePayPaymentMethod :: Maybe ApplePayPaymentMethod noApplePayPaymentMethod = Nothing {-# INLINE noApplePayPaymentMethod #-} foreign import javascript unsafe "window[\"ApplePayPaymentMethod\"]" gTypeApplePayPaymentMethod :: GType -- | Functions for this inteface are in "GHCJS.DOM.ApplePayPaymentMethodSelectedEvent". -- Base interface functions are in: -- -- * "GHCJS.DOM.Event" -- -- newtype ApplePayPaymentMethodSelectedEvent = ApplePayPaymentMethodSelectedEvent { unApplePayPaymentMethodSelectedEvent :: JSVal } instance Eq (ApplePayPaymentMethodSelectedEvent) where (ApplePayPaymentMethodSelectedEvent a) == (ApplePayPaymentMethodSelectedEvent b) = js_eq a b instance PToJSVal ApplePayPaymentMethodSelectedEvent where pToJSVal = unApplePayPaymentMethodSelectedEvent {-# INLINE pToJSVal #-} instance PFromJSVal ApplePayPaymentMethodSelectedEvent where pFromJSVal = ApplePayPaymentMethodSelectedEvent {-# INLINE pFromJSVal #-} instance ToJSVal ApplePayPaymentMethodSelectedEvent where toJSVal = return . unApplePayPaymentMethodSelectedEvent {-# INLINE toJSVal #-} instance FromJSVal ApplePayPaymentMethodSelectedEvent where fromJSVal = return . fmap ApplePayPaymentMethodSelectedEvent . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEvent ApplePayPaymentMethodSelectedEvent instance IsGObject ApplePayPaymentMethodSelectedEvent where typeGType _ = gTypeApplePayPaymentMethodSelectedEvent {-# INLINE typeGType #-} noApplePayPaymentMethodSelectedEvent :: Maybe ApplePayPaymentMethodSelectedEvent noApplePayPaymentMethodSelectedEvent = Nothing {-# INLINE noApplePayPaymentMethodSelectedEvent #-} foreign import javascript unsafe "window[\"ApplePayPaymentMethodSelectedEvent\"]" gTypeApplePayPaymentMethodSelectedEvent :: GType -- | Functions for this inteface are in "GHCJS.DOM.ApplePayPaymentMethodUpdate". -- -- newtype ApplePayPaymentMethodUpdate = ApplePayPaymentMethodUpdate { unApplePayPaymentMethodUpdate :: JSVal } instance Eq (ApplePayPaymentMethodUpdate) where (ApplePayPaymentMethodUpdate a) == (ApplePayPaymentMethodUpdate b) = js_eq a b instance PToJSVal ApplePayPaymentMethodUpdate where pToJSVal = unApplePayPaymentMethodUpdate {-# INLINE pToJSVal #-} instance PFromJSVal ApplePayPaymentMethodUpdate where pFromJSVal = ApplePayPaymentMethodUpdate {-# INLINE pFromJSVal #-} instance ToJSVal ApplePayPaymentMethodUpdate where toJSVal = return . unApplePayPaymentMethodUpdate {-# INLINE toJSVal #-} instance FromJSVal ApplePayPaymentMethodUpdate where fromJSVal = return . fmap ApplePayPaymentMethodUpdate . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject ApplePayPaymentMethodUpdate where typeGType _ = gTypeApplePayPaymentMethodUpdate {-# INLINE typeGType #-} noApplePayPaymentMethodUpdate :: Maybe ApplePayPaymentMethodUpdate noApplePayPaymentMethodUpdate = Nothing {-# INLINE noApplePayPaymentMethodUpdate #-} foreign import javascript unsafe "window[\"ApplePayPaymentMethodUpdate\"]" gTypeApplePayPaymentMethodUpdate :: GType -- | Functions for this inteface are in "GHCJS.DOM.ApplePayPaymentPass". -- -- newtype ApplePayPaymentPass = ApplePayPaymentPass { unApplePayPaymentPass :: JSVal } instance Eq (ApplePayPaymentPass) where (ApplePayPaymentPass a) == (ApplePayPaymentPass b) = js_eq a b instance PToJSVal ApplePayPaymentPass where pToJSVal = unApplePayPaymentPass {-# INLINE pToJSVal #-} instance PFromJSVal ApplePayPaymentPass where pFromJSVal = ApplePayPaymentPass {-# INLINE pFromJSVal #-} instance ToJSVal ApplePayPaymentPass where toJSVal = return . unApplePayPaymentPass {-# INLINE toJSVal #-} instance FromJSVal ApplePayPaymentPass where fromJSVal = return . fmap ApplePayPaymentPass . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject ApplePayPaymentPass where typeGType _ = gTypeApplePayPaymentPass {-# INLINE typeGType #-} noApplePayPaymentPass :: Maybe ApplePayPaymentPass noApplePayPaymentPass = Nothing {-# INLINE noApplePayPaymentPass #-} foreign import javascript unsafe "window[\"ApplePayPaymentPass\"]" gTypeApplePayPaymentPass :: GType -- | Functions for this inteface are in "GHCJS.DOM.ApplePayPaymentRequest". -- -- newtype ApplePayPaymentRequest = ApplePayPaymentRequest { unApplePayPaymentRequest :: JSVal } instance Eq (ApplePayPaymentRequest) where (ApplePayPaymentRequest a) == (ApplePayPaymentRequest b) = js_eq a b instance PToJSVal ApplePayPaymentRequest where pToJSVal = unApplePayPaymentRequest {-# INLINE pToJSVal #-} instance PFromJSVal ApplePayPaymentRequest where pFromJSVal = ApplePayPaymentRequest {-# INLINE pFromJSVal #-} instance ToJSVal ApplePayPaymentRequest where toJSVal = return . unApplePayPaymentRequest {-# INLINE toJSVal #-} instance FromJSVal ApplePayPaymentRequest where fromJSVal = return . fmap ApplePayPaymentRequest . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject ApplePayPaymentRequest where typeGType _ = gTypeApplePayPaymentRequest {-# INLINE typeGType #-} noApplePayPaymentRequest :: Maybe ApplePayPaymentRequest noApplePayPaymentRequest = Nothing {-# INLINE noApplePayPaymentRequest #-} foreign import javascript unsafe "window[\"ApplePayPaymentRequest\"]" gTypeApplePayPaymentRequest :: GType -- | Functions for this inteface are in "GHCJS.DOM.ApplePayPaymentToken". -- -- newtype ApplePayPaymentToken = ApplePayPaymentToken { unApplePayPaymentToken :: JSVal } instance Eq (ApplePayPaymentToken) where (ApplePayPaymentToken a) == (ApplePayPaymentToken b) = js_eq a b instance PToJSVal ApplePayPaymentToken where pToJSVal = unApplePayPaymentToken {-# INLINE pToJSVal #-} instance PFromJSVal ApplePayPaymentToken where pFromJSVal = ApplePayPaymentToken {-# INLINE pFromJSVal #-} instance ToJSVal ApplePayPaymentToken where toJSVal = return . unApplePayPaymentToken {-# INLINE toJSVal #-} instance FromJSVal ApplePayPaymentToken where fromJSVal = return . fmap ApplePayPaymentToken . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject ApplePayPaymentToken where typeGType _ = gTypeApplePayPaymentToken {-# INLINE typeGType #-} noApplePayPaymentToken :: Maybe ApplePayPaymentToken noApplePayPaymentToken = Nothing {-# INLINE noApplePayPaymentToken #-} foreign import javascript unsafe "window[\"ApplePayPaymentToken\"]" gTypeApplePayPaymentToken :: GType -- | Functions for this inteface are in "GHCJS.DOM.ApplePaySession". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventTarget" -- -- newtype ApplePaySession = ApplePaySession { unApplePaySession :: JSVal } instance Eq (ApplePaySession) where (ApplePaySession a) == (ApplePaySession b) = js_eq a b instance PToJSVal ApplePaySession where pToJSVal = unApplePaySession {-# INLINE pToJSVal #-} instance PFromJSVal ApplePaySession where pFromJSVal = ApplePaySession {-# INLINE pFromJSVal #-} instance ToJSVal ApplePaySession where toJSVal = return . unApplePaySession {-# INLINE toJSVal #-} instance FromJSVal ApplePaySession where fromJSVal = return . fmap ApplePaySession . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventTarget ApplePaySession instance IsGObject ApplePaySession where typeGType _ = gTypeApplePaySession {-# INLINE typeGType #-} noApplePaySession :: Maybe ApplePaySession noApplePaySession = Nothing {-# INLINE noApplePaySession #-} foreign import javascript unsafe "window[\"ApplePaySession\"]" gTypeApplePaySession :: GType -- | Functions for this inteface are in "GHCJS.DOM.ApplePayShippingContactSelectedEvent". -- Base interface functions are in: -- -- * "GHCJS.DOM.Event" -- -- newtype ApplePayShippingContactSelectedEvent = ApplePayShippingContactSelectedEvent { unApplePayShippingContactSelectedEvent :: JSVal } instance Eq (ApplePayShippingContactSelectedEvent) where (ApplePayShippingContactSelectedEvent a) == (ApplePayShippingContactSelectedEvent b) = js_eq a b instance PToJSVal ApplePayShippingContactSelectedEvent where pToJSVal = unApplePayShippingContactSelectedEvent {-# INLINE pToJSVal #-} instance PFromJSVal ApplePayShippingContactSelectedEvent where pFromJSVal = ApplePayShippingContactSelectedEvent {-# INLINE pFromJSVal #-} instance ToJSVal ApplePayShippingContactSelectedEvent where toJSVal = return . unApplePayShippingContactSelectedEvent {-# INLINE toJSVal #-} instance FromJSVal ApplePayShippingContactSelectedEvent where fromJSVal = return . fmap ApplePayShippingContactSelectedEvent . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEvent ApplePayShippingContactSelectedEvent instance IsGObject ApplePayShippingContactSelectedEvent where typeGType _ = gTypeApplePayShippingContactSelectedEvent {-# INLINE typeGType #-} noApplePayShippingContactSelectedEvent :: Maybe ApplePayShippingContactSelectedEvent noApplePayShippingContactSelectedEvent = Nothing {-# INLINE noApplePayShippingContactSelectedEvent #-} foreign import javascript unsafe "window[\"ApplePayShippingContactSelectedEvent\"]" gTypeApplePayShippingContactSelectedEvent :: GType -- | Functions for this inteface are in "GHCJS.DOM.ApplePayShippingContactUpdate". -- -- newtype ApplePayShippingContactUpdate = ApplePayShippingContactUpdate { unApplePayShippingContactUpdate :: JSVal } instance Eq (ApplePayShippingContactUpdate) where (ApplePayShippingContactUpdate a) == (ApplePayShippingContactUpdate b) = js_eq a b instance PToJSVal ApplePayShippingContactUpdate where pToJSVal = unApplePayShippingContactUpdate {-# INLINE pToJSVal #-} instance PFromJSVal ApplePayShippingContactUpdate where pFromJSVal = ApplePayShippingContactUpdate {-# INLINE pFromJSVal #-} instance ToJSVal ApplePayShippingContactUpdate where toJSVal = return . unApplePayShippingContactUpdate {-# INLINE toJSVal #-} instance FromJSVal ApplePayShippingContactUpdate where fromJSVal = return . fmap ApplePayShippingContactUpdate . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject ApplePayShippingContactUpdate where typeGType _ = gTypeApplePayShippingContactUpdate {-# INLINE typeGType #-} noApplePayShippingContactUpdate :: Maybe ApplePayShippingContactUpdate noApplePayShippingContactUpdate = Nothing {-# INLINE noApplePayShippingContactUpdate #-} foreign import javascript unsafe "window[\"ApplePayShippingContactUpdate\"]" gTypeApplePayShippingContactUpdate :: GType -- | Functions for this inteface are in "GHCJS.DOM.ApplePayShippingMethod". -- -- newtype ApplePayShippingMethod = ApplePayShippingMethod { unApplePayShippingMethod :: JSVal } instance Eq (ApplePayShippingMethod) where (ApplePayShippingMethod a) == (ApplePayShippingMethod b) = js_eq a b instance PToJSVal ApplePayShippingMethod where pToJSVal = unApplePayShippingMethod {-# INLINE pToJSVal #-} instance PFromJSVal ApplePayShippingMethod where pFromJSVal = ApplePayShippingMethod {-# INLINE pFromJSVal #-} instance ToJSVal ApplePayShippingMethod where toJSVal = return . unApplePayShippingMethod {-# INLINE toJSVal #-} instance FromJSVal ApplePayShippingMethod where fromJSVal = return . fmap ApplePayShippingMethod . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject ApplePayShippingMethod where typeGType _ = gTypeApplePayShippingMethod {-# INLINE typeGType #-} noApplePayShippingMethod :: Maybe ApplePayShippingMethod noApplePayShippingMethod = Nothing {-# INLINE noApplePayShippingMethod #-} foreign import javascript unsafe "window[\"ApplePayShippingMethod\"]" gTypeApplePayShippingMethod :: GType -- | Functions for this inteface are in "GHCJS.DOM.ApplePayShippingMethodSelectedEvent". -- Base interface functions are in: -- -- * "GHCJS.DOM.Event" -- -- newtype ApplePayShippingMethodSelectedEvent = ApplePayShippingMethodSelectedEvent { unApplePayShippingMethodSelectedEvent :: JSVal } instance Eq (ApplePayShippingMethodSelectedEvent) where (ApplePayShippingMethodSelectedEvent a) == (ApplePayShippingMethodSelectedEvent b) = js_eq a b instance PToJSVal ApplePayShippingMethodSelectedEvent where pToJSVal = unApplePayShippingMethodSelectedEvent {-# INLINE pToJSVal #-} instance PFromJSVal ApplePayShippingMethodSelectedEvent where pFromJSVal = ApplePayShippingMethodSelectedEvent {-# INLINE pFromJSVal #-} instance ToJSVal ApplePayShippingMethodSelectedEvent where toJSVal = return . unApplePayShippingMethodSelectedEvent {-# INLINE toJSVal #-} instance FromJSVal ApplePayShippingMethodSelectedEvent where fromJSVal = return . fmap ApplePayShippingMethodSelectedEvent . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEvent ApplePayShippingMethodSelectedEvent instance IsGObject ApplePayShippingMethodSelectedEvent where typeGType _ = gTypeApplePayShippingMethodSelectedEvent {-# INLINE typeGType #-} noApplePayShippingMethodSelectedEvent :: Maybe ApplePayShippingMethodSelectedEvent noApplePayShippingMethodSelectedEvent = Nothing {-# INLINE noApplePayShippingMethodSelectedEvent #-} foreign import javascript unsafe "window[\"ApplePayShippingMethodSelectedEvent\"]" gTypeApplePayShippingMethodSelectedEvent :: GType -- | Functions for this inteface are in "GHCJS.DOM.ApplePayShippingMethodUpdate". -- -- newtype ApplePayShippingMethodUpdate = ApplePayShippingMethodUpdate { unApplePayShippingMethodUpdate :: JSVal } instance Eq (ApplePayShippingMethodUpdate) where (ApplePayShippingMethodUpdate a) == (ApplePayShippingMethodUpdate b) = js_eq a b instance PToJSVal ApplePayShippingMethodUpdate where pToJSVal = unApplePayShippingMethodUpdate {-# INLINE pToJSVal #-} instance PFromJSVal ApplePayShippingMethodUpdate where pFromJSVal = ApplePayShippingMethodUpdate {-# INLINE pFromJSVal #-} instance ToJSVal ApplePayShippingMethodUpdate where toJSVal = return . unApplePayShippingMethodUpdate {-# INLINE toJSVal #-} instance FromJSVal ApplePayShippingMethodUpdate where fromJSVal = return . fmap ApplePayShippingMethodUpdate . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject ApplePayShippingMethodUpdate where typeGType _ = gTypeApplePayShippingMethodUpdate {-# INLINE typeGType #-} noApplePayShippingMethodUpdate :: Maybe ApplePayShippingMethodUpdate noApplePayShippingMethodUpdate = Nothing {-# INLINE noApplePayShippingMethodUpdate #-} foreign import javascript unsafe "window[\"ApplePayShippingMethodUpdate\"]" gTypeApplePayShippingMethodUpdate :: GType -- | Functions for this inteface are in "GHCJS.DOM.ApplePayValidateMerchantEvent". -- Base interface functions are in: -- -- * "GHCJS.DOM.Event" -- -- newtype ApplePayValidateMerchantEvent = ApplePayValidateMerchantEvent { unApplePayValidateMerchantEvent :: JSVal } instance Eq (ApplePayValidateMerchantEvent) where (ApplePayValidateMerchantEvent a) == (ApplePayValidateMerchantEvent b) = js_eq a b instance PToJSVal ApplePayValidateMerchantEvent where pToJSVal = unApplePayValidateMerchantEvent {-# INLINE pToJSVal #-} instance PFromJSVal ApplePayValidateMerchantEvent where pFromJSVal = ApplePayValidateMerchantEvent {-# INLINE pFromJSVal #-} instance ToJSVal ApplePayValidateMerchantEvent where toJSVal = return . unApplePayValidateMerchantEvent {-# INLINE toJSVal #-} instance FromJSVal ApplePayValidateMerchantEvent where fromJSVal = return . fmap ApplePayValidateMerchantEvent . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEvent ApplePayValidateMerchantEvent instance IsGObject ApplePayValidateMerchantEvent where typeGType _ = gTypeApplePayValidateMerchantEvent {-# INLINE typeGType #-} noApplePayValidateMerchantEvent :: Maybe ApplePayValidateMerchantEvent noApplePayValidateMerchantEvent = Nothing {-# INLINE noApplePayValidateMerchantEvent #-} foreign import javascript unsafe "window[\"ApplePayValidateMerchantEvent\"]" gTypeApplePayValidateMerchantEvent :: GType -- | Functions for this inteface are in "GHCJS.DOM.ApplicationCache". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventTarget" -- -- newtype ApplicationCache = ApplicationCache { unApplicationCache :: JSVal } instance Eq (ApplicationCache) where (ApplicationCache a) == (ApplicationCache b) = js_eq a b instance PToJSVal ApplicationCache where pToJSVal = unApplicationCache {-# INLINE pToJSVal #-} instance PFromJSVal ApplicationCache where pFromJSVal = ApplicationCache {-# INLINE pFromJSVal #-} instance ToJSVal ApplicationCache where toJSVal = return . unApplicationCache {-# INLINE toJSVal #-} instance FromJSVal ApplicationCache where fromJSVal = return . fmap ApplicationCache . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventTarget ApplicationCache instance IsGObject ApplicationCache where typeGType _ = gTypeApplicationCache {-# INLINE typeGType #-} noApplicationCache :: Maybe ApplicationCache noApplicationCache = Nothing {-# INLINE noApplicationCache #-} foreign import javascript unsafe "window[\"ApplicationCache\"]" gTypeApplicationCache :: GType -- | Functions for this inteface are in "GHCJS.DOM.AssignedNodesOptions". -- -- newtype AssignedNodesOptions = AssignedNodesOptions { unAssignedNodesOptions :: JSVal } instance Eq (AssignedNodesOptions) where (AssignedNodesOptions a) == (AssignedNodesOptions b) = js_eq a b instance PToJSVal AssignedNodesOptions where pToJSVal = unAssignedNodesOptions {-# INLINE pToJSVal #-} instance PFromJSVal AssignedNodesOptions where pFromJSVal = AssignedNodesOptions {-# INLINE pFromJSVal #-} instance ToJSVal AssignedNodesOptions where toJSVal = return . unAssignedNodesOptions {-# INLINE toJSVal #-} instance FromJSVal AssignedNodesOptions where fromJSVal = return . fmap AssignedNodesOptions . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject AssignedNodesOptions where typeGType _ = gTypeAssignedNodesOptions {-# INLINE typeGType #-} noAssignedNodesOptions :: Maybe AssignedNodesOptions noAssignedNodesOptions = Nothing {-# INLINE noAssignedNodesOptions #-} foreign import javascript unsafe "window[\"AssignedNodesOptions\"]" gTypeAssignedNodesOptions :: GType -- | Functions for this inteface are in "GHCJS.DOM.Attr". -- Base interface functions are in: -- -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- -- newtype Attr = Attr { unAttr :: JSVal } instance Eq (Attr) where (Attr a) == (Attr b) = js_eq a b instance PToJSVal Attr where pToJSVal = unAttr {-# INLINE pToJSVal #-} instance PFromJSVal Attr where pFromJSVal = Attr {-# INLINE pFromJSVal #-} instance ToJSVal Attr where toJSVal = return . unAttr {-# INLINE toJSVal #-} instance FromJSVal Attr where fromJSVal = return . fmap Attr . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsNode Attr instance IsEventTarget Attr instance IsGObject Attr where typeGType _ = gTypeAttr {-# INLINE typeGType #-} noAttr :: Maybe Attr noAttr = Nothing {-# INLINE noAttr #-} foreign import javascript unsafe "window[\"Attr\"]" gTypeAttr :: GType -- | Functions for this inteface are in "GHCJS.DOM.AudioBuffer". -- -- newtype AudioBuffer = AudioBuffer { unAudioBuffer :: JSVal } instance Eq (AudioBuffer) where (AudioBuffer a) == (AudioBuffer b) = js_eq a b instance PToJSVal AudioBuffer where pToJSVal = unAudioBuffer {-# INLINE pToJSVal #-} instance PFromJSVal AudioBuffer where pFromJSVal = AudioBuffer {-# INLINE pFromJSVal #-} instance ToJSVal AudioBuffer where toJSVal = return . unAudioBuffer {-# INLINE toJSVal #-} instance FromJSVal AudioBuffer where fromJSVal = return . fmap AudioBuffer . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject AudioBuffer where typeGType _ = gTypeAudioBuffer {-# INLINE typeGType #-} noAudioBuffer :: Maybe AudioBuffer noAudioBuffer = Nothing {-# INLINE noAudioBuffer #-} foreign import javascript unsafe "window[\"AudioBuffer\"]" gTypeAudioBuffer :: GType -- | Functions for this inteface are in "GHCJS.DOM.AudioBufferSourceNode". -- Base interface functions are in: -- -- * "GHCJS.DOM.AudioNode" -- * "GHCJS.DOM.EventTarget" -- -- newtype AudioBufferSourceNode = AudioBufferSourceNode { unAudioBufferSourceNode :: JSVal } instance Eq (AudioBufferSourceNode) where (AudioBufferSourceNode a) == (AudioBufferSourceNode b) = js_eq a b instance PToJSVal AudioBufferSourceNode where pToJSVal = unAudioBufferSourceNode {-# INLINE pToJSVal #-} instance PFromJSVal AudioBufferSourceNode where pFromJSVal = AudioBufferSourceNode {-# INLINE pFromJSVal #-} instance ToJSVal AudioBufferSourceNode where toJSVal = return . unAudioBufferSourceNode {-# INLINE toJSVal #-} instance FromJSVal AudioBufferSourceNode where fromJSVal = return . fmap AudioBufferSourceNode . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsAudioNode AudioBufferSourceNode instance IsEventTarget AudioBufferSourceNode instance IsGObject AudioBufferSourceNode where typeGType _ = gTypeAudioBufferSourceNode {-# INLINE typeGType #-} noAudioBufferSourceNode :: Maybe AudioBufferSourceNode noAudioBufferSourceNode = Nothing {-# INLINE noAudioBufferSourceNode #-} foreign import javascript unsafe "window[\"AudioBufferSourceNode\"]" gTypeAudioBufferSourceNode :: GType -- | Functions for this inteface are in "GHCJS.DOM.AudioContext". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventTarget" -- -- newtype AudioContext = AudioContext { unAudioContext :: JSVal } instance Eq (AudioContext) where (AudioContext a) == (AudioContext b) = js_eq a b instance PToJSVal AudioContext where pToJSVal = unAudioContext {-# INLINE pToJSVal #-} instance PFromJSVal AudioContext where pFromJSVal = AudioContext {-# INLINE pFromJSVal #-} instance ToJSVal AudioContext where toJSVal = return . unAudioContext {-# INLINE toJSVal #-} instance FromJSVal AudioContext where fromJSVal = return . fmap AudioContext . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsEventTarget o, IsGObject o) => IsAudioContext o toAudioContext :: IsAudioContext o => o -> AudioContext toAudioContext = AudioContext . coerce instance IsAudioContext AudioContext instance IsEventTarget AudioContext instance IsGObject AudioContext where typeGType _ = gTypeAudioContext {-# INLINE typeGType #-} noAudioContext :: Maybe AudioContext noAudioContext = Nothing {-# INLINE noAudioContext #-} foreign import javascript unsafe "window[\"AudioContext\"]" gTypeAudioContext :: GType -- | Functions for this inteface are in "GHCJS.DOM.AudioDestinationNode". -- Base interface functions are in: -- -- * "GHCJS.DOM.AudioNode" -- * "GHCJS.DOM.EventTarget" -- -- newtype AudioDestinationNode = AudioDestinationNode { unAudioDestinationNode :: JSVal } instance Eq (AudioDestinationNode) where (AudioDestinationNode a) == (AudioDestinationNode b) = js_eq a b instance PToJSVal AudioDestinationNode where pToJSVal = unAudioDestinationNode {-# INLINE pToJSVal #-} instance PFromJSVal AudioDestinationNode where pFromJSVal = AudioDestinationNode {-# INLINE pFromJSVal #-} instance ToJSVal AudioDestinationNode where toJSVal = return . unAudioDestinationNode {-# INLINE toJSVal #-} instance FromJSVal AudioDestinationNode where fromJSVal = return . fmap AudioDestinationNode . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsAudioNode AudioDestinationNode instance IsEventTarget AudioDestinationNode instance IsGObject AudioDestinationNode where typeGType _ = gTypeAudioDestinationNode {-# INLINE typeGType #-} noAudioDestinationNode :: Maybe AudioDestinationNode noAudioDestinationNode = Nothing {-# INLINE noAudioDestinationNode #-} foreign import javascript unsafe "window[\"AudioDestinationNode\"]" gTypeAudioDestinationNode :: GType -- | Functions for this inteface are in "GHCJS.DOM.AudioListener". -- -- newtype AudioListener = AudioListener { unAudioListener :: JSVal } instance Eq (AudioListener) where (AudioListener a) == (AudioListener b) = js_eq a b instance PToJSVal AudioListener where pToJSVal = unAudioListener {-# INLINE pToJSVal #-} instance PFromJSVal AudioListener where pFromJSVal = AudioListener {-# INLINE pFromJSVal #-} instance ToJSVal AudioListener where toJSVal = return . unAudioListener {-# INLINE toJSVal #-} instance FromJSVal AudioListener where fromJSVal = return . fmap AudioListener . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject AudioListener where typeGType _ = gTypeAudioListener {-# INLINE typeGType #-} noAudioListener :: Maybe AudioListener noAudioListener = Nothing {-# INLINE noAudioListener #-} foreign import javascript unsafe "window[\"AudioListener\"]" gTypeAudioListener :: GType -- | Functions for this inteface are in "GHCJS.DOM.AudioNode". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventTarget" -- -- newtype AudioNode = AudioNode { unAudioNode :: JSVal } instance Eq (AudioNode) where (AudioNode a) == (AudioNode b) = js_eq a b instance PToJSVal AudioNode where pToJSVal = unAudioNode {-# INLINE pToJSVal #-} instance PFromJSVal AudioNode where pFromJSVal = AudioNode {-# INLINE pFromJSVal #-} instance ToJSVal AudioNode where toJSVal = return . unAudioNode {-# INLINE toJSVal #-} instance FromJSVal AudioNode where fromJSVal = return . fmap AudioNode . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsEventTarget o, IsGObject o) => IsAudioNode o toAudioNode :: IsAudioNode o => o -> AudioNode toAudioNode = AudioNode . coerce instance IsAudioNode AudioNode instance IsEventTarget AudioNode instance IsGObject AudioNode where typeGType _ = gTypeAudioNode {-# INLINE typeGType #-} noAudioNode :: Maybe AudioNode noAudioNode = Nothing {-# INLINE noAudioNode #-} foreign import javascript unsafe "window[\"AudioNode\"]" gTypeAudioNode :: GType -- | Functions for this inteface are in "GHCJS.DOM.AudioParam". -- -- newtype AudioParam = AudioParam { unAudioParam :: JSVal } instance Eq (AudioParam) where (AudioParam a) == (AudioParam b) = js_eq a b instance PToJSVal AudioParam where pToJSVal = unAudioParam {-# INLINE pToJSVal #-} instance PFromJSVal AudioParam where pFromJSVal = AudioParam {-# INLINE pFromJSVal #-} instance ToJSVal AudioParam where toJSVal = return . unAudioParam {-# INLINE toJSVal #-} instance FromJSVal AudioParam where fromJSVal = return . fmap AudioParam . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject AudioParam where typeGType _ = gTypeAudioParam {-# INLINE typeGType #-} noAudioParam :: Maybe AudioParam noAudioParam = Nothing {-# INLINE noAudioParam #-} foreign import javascript unsafe "window[\"AudioParam\"]" gTypeAudioParam :: GType -- | Functions for this inteface are in "GHCJS.DOM.AudioProcessingEvent". -- Base interface functions are in: -- -- * "GHCJS.DOM.Event" -- -- newtype AudioProcessingEvent = AudioProcessingEvent { unAudioProcessingEvent :: JSVal } instance Eq (AudioProcessingEvent) where (AudioProcessingEvent a) == (AudioProcessingEvent b) = js_eq a b instance PToJSVal AudioProcessingEvent where pToJSVal = unAudioProcessingEvent {-# INLINE pToJSVal #-} instance PFromJSVal AudioProcessingEvent where pFromJSVal = AudioProcessingEvent {-# INLINE pFromJSVal #-} instance ToJSVal AudioProcessingEvent where toJSVal = return . unAudioProcessingEvent {-# INLINE toJSVal #-} instance FromJSVal AudioProcessingEvent where fromJSVal = return . fmap AudioProcessingEvent . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEvent AudioProcessingEvent instance IsGObject AudioProcessingEvent where typeGType _ = gTypeAudioProcessingEvent {-# INLINE typeGType #-} noAudioProcessingEvent :: Maybe AudioProcessingEvent noAudioProcessingEvent = Nothing {-# INLINE noAudioProcessingEvent #-} foreign import javascript unsafe "window[\"AudioProcessingEvent\"]" gTypeAudioProcessingEvent :: GType -- | Functions for this inteface are in "GHCJS.DOM.AudioTrack". -- -- newtype AudioTrack = AudioTrack { unAudioTrack :: JSVal } instance Eq (AudioTrack) where (AudioTrack a) == (AudioTrack b) = js_eq a b instance PToJSVal AudioTrack where pToJSVal = unAudioTrack {-# INLINE pToJSVal #-} instance PFromJSVal AudioTrack where pFromJSVal = AudioTrack {-# INLINE pFromJSVal #-} instance ToJSVal AudioTrack where toJSVal = return . unAudioTrack {-# INLINE toJSVal #-} instance FromJSVal AudioTrack where fromJSVal = return . fmap AudioTrack . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject AudioTrack where typeGType _ = gTypeAudioTrack {-# INLINE typeGType #-} noAudioTrack :: Maybe AudioTrack noAudioTrack = Nothing {-# INLINE noAudioTrack #-} foreign import javascript unsafe "window[\"AudioTrack\"]" gTypeAudioTrack :: GType -- | Functions for this inteface are in "GHCJS.DOM.AudioTrackList". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventTarget" -- -- newtype AudioTrackList = AudioTrackList { unAudioTrackList :: JSVal } instance Eq (AudioTrackList) where (AudioTrackList a) == (AudioTrackList b) = js_eq a b instance PToJSVal AudioTrackList where pToJSVal = unAudioTrackList {-# INLINE pToJSVal #-} instance PFromJSVal AudioTrackList where pFromJSVal = AudioTrackList {-# INLINE pFromJSVal #-} instance ToJSVal AudioTrackList where toJSVal = return . unAudioTrackList {-# INLINE toJSVal #-} instance FromJSVal AudioTrackList where fromJSVal = return . fmap AudioTrackList . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventTarget AudioTrackList instance IsGObject AudioTrackList where typeGType _ = gTypeAudioTrackList {-# INLINE typeGType #-} noAudioTrackList :: Maybe AudioTrackList noAudioTrackList = Nothing {-# INLINE noAudioTrackList #-} foreign import javascript unsafe "window[\"AudioTrackList\"]" gTypeAudioTrackList :: GType -- | Functions for this inteface are in "GHCJS.DOM.AutocompleteErrorEvent". -- Base interface functions are in: -- -- * "GHCJS.DOM.Event" -- -- newtype AutocompleteErrorEvent = AutocompleteErrorEvent { unAutocompleteErrorEvent :: JSVal } instance Eq (AutocompleteErrorEvent) where (AutocompleteErrorEvent a) == (AutocompleteErrorEvent b) = js_eq a b instance PToJSVal AutocompleteErrorEvent where pToJSVal = unAutocompleteErrorEvent {-# INLINE pToJSVal #-} instance PFromJSVal AutocompleteErrorEvent where pFromJSVal = AutocompleteErrorEvent {-# INLINE pFromJSVal #-} instance ToJSVal AutocompleteErrorEvent where toJSVal = return . unAutocompleteErrorEvent {-# INLINE toJSVal #-} instance FromJSVal AutocompleteErrorEvent where fromJSVal = return . fmap AutocompleteErrorEvent . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEvent AutocompleteErrorEvent instance IsGObject AutocompleteErrorEvent where typeGType _ = gTypeAutocompleteErrorEvent {-# INLINE typeGType #-} noAutocompleteErrorEvent :: Maybe AutocompleteErrorEvent noAutocompleteErrorEvent = Nothing {-# INLINE noAutocompleteErrorEvent #-} foreign import javascript unsafe "window[\"AutocompleteErrorEvent\"]" gTypeAutocompleteErrorEvent :: GType -- | Functions for this inteface are in "GHCJS.DOM.AutocompleteErrorEventInit". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventInit" -- -- newtype AutocompleteErrorEventInit = AutocompleteErrorEventInit { unAutocompleteErrorEventInit :: JSVal } instance Eq (AutocompleteErrorEventInit) where (AutocompleteErrorEventInit a) == (AutocompleteErrorEventInit b) = js_eq a b instance PToJSVal AutocompleteErrorEventInit where pToJSVal = unAutocompleteErrorEventInit {-# INLINE pToJSVal #-} instance PFromJSVal AutocompleteErrorEventInit where pFromJSVal = AutocompleteErrorEventInit {-# INLINE pFromJSVal #-} instance ToJSVal AutocompleteErrorEventInit where toJSVal = return . unAutocompleteErrorEventInit {-# INLINE toJSVal #-} instance FromJSVal AutocompleteErrorEventInit where fromJSVal = return . fmap AutocompleteErrorEventInit . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventInit AutocompleteErrorEventInit instance IsGObject AutocompleteErrorEventInit where typeGType _ = gTypeAutocompleteErrorEventInit {-# INLINE typeGType #-} noAutocompleteErrorEventInit :: Maybe AutocompleteErrorEventInit noAutocompleteErrorEventInit = Nothing {-# INLINE noAutocompleteErrorEventInit #-} foreign import javascript unsafe "window[\"AutocompleteErrorEventInit\"]" gTypeAutocompleteErrorEventInit :: GType -- | Functions for this inteface are in "GHCJS.DOM.BarProp". -- -- newtype BarProp = BarProp { unBarProp :: JSVal } instance Eq (BarProp) where (BarProp a) == (BarProp b) = js_eq a b instance PToJSVal BarProp where pToJSVal = unBarProp {-# INLINE pToJSVal #-} instance PFromJSVal BarProp where pFromJSVal = BarProp {-# INLINE pFromJSVal #-} instance ToJSVal BarProp where toJSVal = return . unBarProp {-# INLINE toJSVal #-} instance FromJSVal BarProp where fromJSVal = return . fmap BarProp . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject BarProp where typeGType _ = gTypeBarProp {-# INLINE typeGType #-} noBarProp :: Maybe BarProp noBarProp = Nothing {-# INLINE noBarProp #-} foreign import javascript unsafe "window[\"BarProp\"]" gTypeBarProp :: GType -- | Functions for this inteface are in "GHCJS.DOM.BasicCredential". -- -- newtype BasicCredential = BasicCredential { unBasicCredential :: JSVal } instance Eq (BasicCredential) where (BasicCredential a) == (BasicCredential b) = js_eq a b instance PToJSVal BasicCredential where pToJSVal = unBasicCredential {-# INLINE pToJSVal #-} instance PFromJSVal BasicCredential where pFromJSVal = BasicCredential {-# INLINE pFromJSVal #-} instance ToJSVal BasicCredential where toJSVal = return . unBasicCredential {-# INLINE toJSVal #-} instance FromJSVal BasicCredential where fromJSVal = return . fmap BasicCredential . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsGObject o) => IsBasicCredential o toBasicCredential :: IsBasicCredential o => o -> BasicCredential toBasicCredential = BasicCredential . coerce instance IsBasicCredential BasicCredential instance IsGObject BasicCredential where typeGType _ = gTypeBasicCredential {-# INLINE typeGType #-} noBasicCredential :: Maybe BasicCredential noBasicCredential = Nothing {-# INLINE noBasicCredential #-} foreign import javascript unsafe "window[\"BasicCredential\"]" gTypeBasicCredential :: GType -- | Functions for this inteface are in "GHCJS.DOM.BeforeLoadEvent". -- Base interface functions are in: -- -- * "GHCJS.DOM.Event" -- -- newtype BeforeLoadEvent = BeforeLoadEvent { unBeforeLoadEvent :: JSVal } instance Eq (BeforeLoadEvent) where (BeforeLoadEvent a) == (BeforeLoadEvent b) = js_eq a b instance PToJSVal BeforeLoadEvent where pToJSVal = unBeforeLoadEvent {-# INLINE pToJSVal #-} instance PFromJSVal BeforeLoadEvent where pFromJSVal = BeforeLoadEvent {-# INLINE pFromJSVal #-} instance ToJSVal BeforeLoadEvent where toJSVal = return . unBeforeLoadEvent {-# INLINE toJSVal #-} instance FromJSVal BeforeLoadEvent where fromJSVal = return . fmap BeforeLoadEvent . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEvent BeforeLoadEvent instance IsGObject BeforeLoadEvent where typeGType _ = gTypeBeforeLoadEvent {-# INLINE typeGType #-} noBeforeLoadEvent :: Maybe BeforeLoadEvent noBeforeLoadEvent = Nothing {-# INLINE noBeforeLoadEvent #-} foreign import javascript unsafe "window[\"BeforeLoadEvent\"]" gTypeBeforeLoadEvent :: GType -- | Functions for this inteface are in "GHCJS.DOM.BeforeLoadEventInit". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventInit" -- -- newtype BeforeLoadEventInit = BeforeLoadEventInit { unBeforeLoadEventInit :: JSVal } instance Eq (BeforeLoadEventInit) where (BeforeLoadEventInit a) == (BeforeLoadEventInit b) = js_eq a b instance PToJSVal BeforeLoadEventInit where pToJSVal = unBeforeLoadEventInit {-# INLINE pToJSVal #-} instance PFromJSVal BeforeLoadEventInit where pFromJSVal = BeforeLoadEventInit {-# INLINE pFromJSVal #-} instance ToJSVal BeforeLoadEventInit where toJSVal = return . unBeforeLoadEventInit {-# INLINE toJSVal #-} instance FromJSVal BeforeLoadEventInit where fromJSVal = return . fmap BeforeLoadEventInit . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventInit BeforeLoadEventInit instance IsGObject BeforeLoadEventInit where typeGType _ = gTypeBeforeLoadEventInit {-# INLINE typeGType #-} noBeforeLoadEventInit :: Maybe BeforeLoadEventInit noBeforeLoadEventInit = Nothing {-# INLINE noBeforeLoadEventInit #-} foreign import javascript unsafe "window[\"BeforeLoadEventInit\"]" gTypeBeforeLoadEventInit :: GType -- | Functions for this inteface are in "GHCJS.DOM.BeforeUnloadEvent". -- Base interface functions are in: -- -- * "GHCJS.DOM.Event" -- -- newtype BeforeUnloadEvent = BeforeUnloadEvent { unBeforeUnloadEvent :: JSVal } instance Eq (BeforeUnloadEvent) where (BeforeUnloadEvent a) == (BeforeUnloadEvent b) = js_eq a b instance PToJSVal BeforeUnloadEvent where pToJSVal = unBeforeUnloadEvent {-# INLINE pToJSVal #-} instance PFromJSVal BeforeUnloadEvent where pFromJSVal = BeforeUnloadEvent {-# INLINE pFromJSVal #-} instance ToJSVal BeforeUnloadEvent where toJSVal = return . unBeforeUnloadEvent {-# INLINE toJSVal #-} instance FromJSVal BeforeUnloadEvent where fromJSVal = return . fmap BeforeUnloadEvent . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEvent BeforeUnloadEvent instance IsGObject BeforeUnloadEvent where typeGType _ = gTypeBeforeUnloadEvent {-# INLINE typeGType #-} noBeforeUnloadEvent :: Maybe BeforeUnloadEvent noBeforeUnloadEvent = Nothing {-# INLINE noBeforeUnloadEvent #-} foreign import javascript unsafe "window[\"BeforeUnloadEvent\"]" gTypeBeforeUnloadEvent :: GType -- | Functions for this inteface are in "GHCJS.DOM.BiquadFilterNode". -- Base interface functions are in: -- -- * "GHCJS.DOM.AudioNode" -- * "GHCJS.DOM.EventTarget" -- -- newtype BiquadFilterNode = BiquadFilterNode { unBiquadFilterNode :: JSVal } instance Eq (BiquadFilterNode) where (BiquadFilterNode a) == (BiquadFilterNode b) = js_eq a b instance PToJSVal BiquadFilterNode where pToJSVal = unBiquadFilterNode {-# INLINE pToJSVal #-} instance PFromJSVal BiquadFilterNode where pFromJSVal = BiquadFilterNode {-# INLINE pFromJSVal #-} instance ToJSVal BiquadFilterNode where toJSVal = return . unBiquadFilterNode {-# INLINE toJSVal #-} instance FromJSVal BiquadFilterNode where fromJSVal = return . fmap BiquadFilterNode . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsAudioNode BiquadFilterNode instance IsEventTarget BiquadFilterNode instance IsGObject BiquadFilterNode where typeGType _ = gTypeBiquadFilterNode {-# INLINE typeGType #-} noBiquadFilterNode :: Maybe BiquadFilterNode noBiquadFilterNode = Nothing {-# INLINE noBiquadFilterNode #-} foreign import javascript unsafe "window[\"BiquadFilterNode\"]" gTypeBiquadFilterNode :: GType -- | Functions for this inteface are in "GHCJS.DOM.Blob". -- -- newtype Blob = Blob { unBlob :: JSVal } instance Eq (Blob) where (Blob a) == (Blob b) = js_eq a b instance PToJSVal Blob where pToJSVal = unBlob {-# INLINE pToJSVal #-} instance PFromJSVal Blob where pFromJSVal = Blob {-# INLINE pFromJSVal #-} instance ToJSVal Blob where toJSVal = return . unBlob {-# INLINE toJSVal #-} instance FromJSVal Blob where fromJSVal = return . fmap Blob . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsGObject o) => IsBlob o toBlob :: IsBlob o => o -> Blob toBlob = Blob . coerce instance IsBlob Blob instance IsGObject Blob where typeGType _ = gTypeBlob {-# INLINE typeGType #-} noBlob :: Maybe Blob noBlob = Nothing {-# INLINE noBlob #-} foreign import javascript unsafe "window[\"Blob\"]" gTypeBlob :: GType -- | Functions for this inteface are in "GHCJS.DOM.BlobPropertyBag". -- -- newtype BlobPropertyBag = BlobPropertyBag { unBlobPropertyBag :: JSVal } instance Eq (BlobPropertyBag) where (BlobPropertyBag a) == (BlobPropertyBag b) = js_eq a b instance PToJSVal BlobPropertyBag where pToJSVal = unBlobPropertyBag {-# INLINE pToJSVal #-} instance PFromJSVal BlobPropertyBag where pFromJSVal = BlobPropertyBag {-# INLINE pFromJSVal #-} instance ToJSVal BlobPropertyBag where toJSVal = return . unBlobPropertyBag {-# INLINE toJSVal #-} instance FromJSVal BlobPropertyBag where fromJSVal = return . fmap BlobPropertyBag . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsGObject o) => IsBlobPropertyBag o toBlobPropertyBag :: IsBlobPropertyBag o => o -> BlobPropertyBag toBlobPropertyBag = BlobPropertyBag . coerce instance IsBlobPropertyBag BlobPropertyBag instance IsGObject BlobPropertyBag where typeGType _ = gTypeBlobPropertyBag {-# INLINE typeGType #-} noBlobPropertyBag :: Maybe BlobPropertyBag noBlobPropertyBag = Nothing {-# INLINE noBlobPropertyBag #-} foreign import javascript unsafe "window[\"BlobPropertyBag\"]" gTypeBlobPropertyBag :: GType -- | Functions for this inteface are in "GHCJS.DOM.Body". -- -- newtype Body = Body { unBody :: JSVal } instance Eq (Body) where (Body a) == (Body b) = js_eq a b instance PToJSVal Body where pToJSVal = unBody {-# INLINE pToJSVal #-} instance PFromJSVal Body where pFromJSVal = Body {-# INLINE pFromJSVal #-} instance ToJSVal Body where toJSVal = return . unBody {-# INLINE toJSVal #-} instance FromJSVal Body where fromJSVal = return . fmap Body . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsGObject o) => IsBody o toBody :: IsBody o => o -> Body toBody = Body . coerce instance IsBody Body instance IsGObject Body where typeGType _ = gTypeBody {-# INLINE typeGType #-} noBody :: Maybe Body noBody = Nothing {-# INLINE noBody #-} foreign import javascript unsafe "window[\"Body\"]" gTypeBody :: GType -- | Functions for this inteface are in "GHCJS.DOM.ByteLengthQueuingStrategy". -- -- newtype ByteLengthQueuingStrategy = ByteLengthQueuingStrategy { unByteLengthQueuingStrategy :: JSVal } instance Eq (ByteLengthQueuingStrategy) where (ByteLengthQueuingStrategy a) == (ByteLengthQueuingStrategy b) = js_eq a b instance PToJSVal ByteLengthQueuingStrategy where pToJSVal = unByteLengthQueuingStrategy {-# INLINE pToJSVal #-} instance PFromJSVal ByteLengthQueuingStrategy where pFromJSVal = ByteLengthQueuingStrategy {-# INLINE pFromJSVal #-} instance ToJSVal ByteLengthQueuingStrategy where toJSVal = return . unByteLengthQueuingStrategy {-# INLINE toJSVal #-} instance FromJSVal ByteLengthQueuingStrategy where fromJSVal = return . fmap ByteLengthQueuingStrategy . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject ByteLengthQueuingStrategy where typeGType _ = gTypeByteLengthQueuingStrategy {-# INLINE typeGType #-} noByteLengthQueuingStrategy :: Maybe ByteLengthQueuingStrategy noByteLengthQueuingStrategy = Nothing {-# INLINE noByteLengthQueuingStrategy #-} foreign import javascript unsafe "window[\"ByteLengthQueuingStrategy\"]" gTypeByteLengthQueuingStrategy :: GType -- | Functions for this inteface are in "GHCJS.DOM.CDATASection". -- Base interface functions are in: -- -- * "GHCJS.DOM.Text" -- * "GHCJS.DOM.CharacterData" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Slotable" -- -- newtype CDATASection = CDATASection { unCDATASection :: JSVal } instance Eq (CDATASection) where (CDATASection a) == (CDATASection b) = js_eq a b instance PToJSVal CDATASection where pToJSVal = unCDATASection {-# INLINE pToJSVal #-} instance PFromJSVal CDATASection where pFromJSVal = CDATASection {-# INLINE pFromJSVal #-} instance ToJSVal CDATASection where toJSVal = return . unCDATASection {-# INLINE toJSVal #-} instance FromJSVal CDATASection where fromJSVal = return . fmap CDATASection . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsText CDATASection instance IsCharacterData CDATASection instance IsNode CDATASection instance IsEventTarget CDATASection instance IsNonDocumentTypeChildNode CDATASection instance IsChildNode CDATASection instance IsSlotable CDATASection instance IsGObject CDATASection where typeGType _ = gTypeCDATASection {-# INLINE typeGType #-} noCDATASection :: Maybe CDATASection noCDATASection = Nothing {-# INLINE noCDATASection #-} foreign import javascript unsafe "window[\"CDATASection\"]" gTypeCDATASection :: GType -- | Functions for this inteface are in "GHCJS.DOM.CSS". -- -- newtype CSS = CSS { unCSS :: JSVal } instance Eq (CSS) where (CSS a) == (CSS b) = js_eq a b instance PToJSVal CSS where pToJSVal = unCSS {-# INLINE pToJSVal #-} instance PFromJSVal CSS where pFromJSVal = CSS {-# INLINE pFromJSVal #-} instance ToJSVal CSS where toJSVal = return . unCSS {-# INLINE toJSVal #-} instance FromJSVal CSS where fromJSVal = return . fmap CSS . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject CSS where typeGType _ = gTypeCSS {-# INLINE typeGType #-} noCSS :: Maybe CSS noCSS = Nothing {-# INLINE noCSS #-} foreign import javascript unsafe "window[\"CSS\"]" gTypeCSS :: GType -- | Functions for this inteface are in "GHCJS.DOM.CSSFontFaceLoadEvent". -- Base interface functions are in: -- -- * "GHCJS.DOM.Event" -- -- newtype CSSFontFaceLoadEvent = CSSFontFaceLoadEvent { unCSSFontFaceLoadEvent :: JSVal } instance Eq (CSSFontFaceLoadEvent) where (CSSFontFaceLoadEvent a) == (CSSFontFaceLoadEvent b) = js_eq a b instance PToJSVal CSSFontFaceLoadEvent where pToJSVal = unCSSFontFaceLoadEvent {-# INLINE pToJSVal #-} instance PFromJSVal CSSFontFaceLoadEvent where pFromJSVal = CSSFontFaceLoadEvent {-# INLINE pFromJSVal #-} instance ToJSVal CSSFontFaceLoadEvent where toJSVal = return . unCSSFontFaceLoadEvent {-# INLINE toJSVal #-} instance FromJSVal CSSFontFaceLoadEvent where fromJSVal = return . fmap CSSFontFaceLoadEvent . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEvent CSSFontFaceLoadEvent instance IsGObject CSSFontFaceLoadEvent where typeGType _ = gTypeCSSFontFaceLoadEvent {-# INLINE typeGType #-} noCSSFontFaceLoadEvent :: Maybe CSSFontFaceLoadEvent noCSSFontFaceLoadEvent = Nothing {-# INLINE noCSSFontFaceLoadEvent #-} foreign import javascript unsafe "window[\"CSSFontFaceLoadEvent\"]" gTypeCSSFontFaceLoadEvent :: GType -- | Functions for this inteface are in "GHCJS.DOM.CSSFontFaceLoadEventInit". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventInit" -- -- newtype CSSFontFaceLoadEventInit = CSSFontFaceLoadEventInit { unCSSFontFaceLoadEventInit :: JSVal } instance Eq (CSSFontFaceLoadEventInit) where (CSSFontFaceLoadEventInit a) == (CSSFontFaceLoadEventInit b) = js_eq a b instance PToJSVal CSSFontFaceLoadEventInit where pToJSVal = unCSSFontFaceLoadEventInit {-# INLINE pToJSVal #-} instance PFromJSVal CSSFontFaceLoadEventInit where pFromJSVal = CSSFontFaceLoadEventInit {-# INLINE pFromJSVal #-} instance ToJSVal CSSFontFaceLoadEventInit where toJSVal = return . unCSSFontFaceLoadEventInit {-# INLINE toJSVal #-} instance FromJSVal CSSFontFaceLoadEventInit where fromJSVal = return . fmap CSSFontFaceLoadEventInit . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventInit CSSFontFaceLoadEventInit instance IsGObject CSSFontFaceLoadEventInit where typeGType _ = gTypeCSSFontFaceLoadEventInit {-# INLINE typeGType #-} noCSSFontFaceLoadEventInit :: Maybe CSSFontFaceLoadEventInit noCSSFontFaceLoadEventInit = Nothing {-# INLINE noCSSFontFaceLoadEventInit #-} foreign import javascript unsafe "window[\"CSSFontFaceLoadEventInit\"]" gTypeCSSFontFaceLoadEventInit :: GType -- | Functions for this inteface are in "GHCJS.DOM.CSSFontFaceRule". -- Base interface functions are in: -- -- * "GHCJS.DOM.CSSRule" -- -- newtype CSSFontFaceRule = CSSFontFaceRule { unCSSFontFaceRule :: JSVal } instance Eq (CSSFontFaceRule) where (CSSFontFaceRule a) == (CSSFontFaceRule b) = js_eq a b instance PToJSVal CSSFontFaceRule where pToJSVal = unCSSFontFaceRule {-# INLINE pToJSVal #-} instance PFromJSVal CSSFontFaceRule where pFromJSVal = CSSFontFaceRule {-# INLINE pFromJSVal #-} instance ToJSVal CSSFontFaceRule where toJSVal = return . unCSSFontFaceRule {-# INLINE toJSVal #-} instance FromJSVal CSSFontFaceRule where fromJSVal = return . fmap CSSFontFaceRule . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsCSSRule CSSFontFaceRule instance IsGObject CSSFontFaceRule where typeGType _ = gTypeCSSFontFaceRule {-# INLINE typeGType #-} noCSSFontFaceRule :: Maybe CSSFontFaceRule noCSSFontFaceRule = Nothing {-# INLINE noCSSFontFaceRule #-} foreign import javascript unsafe "window[\"CSSFontFaceRule\"]" gTypeCSSFontFaceRule :: GType -- | Functions for this inteface are in "GHCJS.DOM.CSSImportRule". -- Base interface functions are in: -- -- * "GHCJS.DOM.CSSRule" -- -- newtype CSSImportRule = CSSImportRule { unCSSImportRule :: JSVal } instance Eq (CSSImportRule) where (CSSImportRule a) == (CSSImportRule b) = js_eq a b instance PToJSVal CSSImportRule where pToJSVal = unCSSImportRule {-# INLINE pToJSVal #-} instance PFromJSVal CSSImportRule where pFromJSVal = CSSImportRule {-# INLINE pFromJSVal #-} instance ToJSVal CSSImportRule where toJSVal = return . unCSSImportRule {-# INLINE toJSVal #-} instance FromJSVal CSSImportRule where fromJSVal = return . fmap CSSImportRule . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsCSSRule CSSImportRule instance IsGObject CSSImportRule where typeGType _ = gTypeCSSImportRule {-# INLINE typeGType #-} noCSSImportRule :: Maybe CSSImportRule noCSSImportRule = Nothing {-# INLINE noCSSImportRule #-} foreign import javascript unsafe "window[\"CSSImportRule\"]" gTypeCSSImportRule :: GType -- | Functions for this inteface are in "GHCJS.DOM.CSSKeyframeRule". -- Base interface functions are in: -- -- * "GHCJS.DOM.CSSRule" -- -- newtype CSSKeyframeRule = CSSKeyframeRule { unCSSKeyframeRule :: JSVal } instance Eq (CSSKeyframeRule) where (CSSKeyframeRule a) == (CSSKeyframeRule b) = js_eq a b instance PToJSVal CSSKeyframeRule where pToJSVal = unCSSKeyframeRule {-# INLINE pToJSVal #-} instance PFromJSVal CSSKeyframeRule where pFromJSVal = CSSKeyframeRule {-# INLINE pFromJSVal #-} instance ToJSVal CSSKeyframeRule where toJSVal = return . unCSSKeyframeRule {-# INLINE toJSVal #-} instance FromJSVal CSSKeyframeRule where fromJSVal = return . fmap CSSKeyframeRule . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsCSSRule CSSKeyframeRule instance IsGObject CSSKeyframeRule where typeGType _ = gTypeCSSKeyframeRule {-# INLINE typeGType #-} noCSSKeyframeRule :: Maybe CSSKeyframeRule noCSSKeyframeRule = Nothing {-# INLINE noCSSKeyframeRule #-} foreign import javascript unsafe "window[\"CSSKeyframeRule\"]" gTypeCSSKeyframeRule :: GType -- | Functions for this inteface are in "GHCJS.DOM.CSSKeyframesRule". -- Base interface functions are in: -- -- * "GHCJS.DOM.CSSRule" -- -- newtype CSSKeyframesRule = CSSKeyframesRule { unCSSKeyframesRule :: JSVal } instance Eq (CSSKeyframesRule) where (CSSKeyframesRule a) == (CSSKeyframesRule b) = js_eq a b instance PToJSVal CSSKeyframesRule where pToJSVal = unCSSKeyframesRule {-# INLINE pToJSVal #-} instance PFromJSVal CSSKeyframesRule where pFromJSVal = CSSKeyframesRule {-# INLINE pFromJSVal #-} instance ToJSVal CSSKeyframesRule where toJSVal = return . unCSSKeyframesRule {-# INLINE toJSVal #-} instance FromJSVal CSSKeyframesRule where fromJSVal = return . fmap CSSKeyframesRule . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsCSSRule CSSKeyframesRule instance IsGObject CSSKeyframesRule where typeGType _ = gTypeCSSKeyframesRule {-# INLINE typeGType #-} noCSSKeyframesRule :: Maybe CSSKeyframesRule noCSSKeyframesRule = Nothing {-# INLINE noCSSKeyframesRule #-} foreign import javascript unsafe "window[\"CSSKeyframesRule\"]" gTypeCSSKeyframesRule :: GType -- | Functions for this inteface are in "GHCJS.DOM.CSSMediaRule". -- Base interface functions are in: -- -- * "GHCJS.DOM.CSSRule" -- -- newtype CSSMediaRule = CSSMediaRule { unCSSMediaRule :: JSVal } instance Eq (CSSMediaRule) where (CSSMediaRule a) == (CSSMediaRule b) = js_eq a b instance PToJSVal CSSMediaRule where pToJSVal = unCSSMediaRule {-# INLINE pToJSVal #-} instance PFromJSVal CSSMediaRule where pFromJSVal = CSSMediaRule {-# INLINE pFromJSVal #-} instance ToJSVal CSSMediaRule where toJSVal = return . unCSSMediaRule {-# INLINE toJSVal #-} instance FromJSVal CSSMediaRule where fromJSVal = return . fmap CSSMediaRule . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsCSSRule CSSMediaRule instance IsGObject CSSMediaRule where typeGType _ = gTypeCSSMediaRule {-# INLINE typeGType #-} noCSSMediaRule :: Maybe CSSMediaRule noCSSMediaRule = Nothing {-# INLINE noCSSMediaRule #-} foreign import javascript unsafe "window[\"CSSMediaRule\"]" gTypeCSSMediaRule :: GType -- | Functions for this inteface are in "GHCJS.DOM.CSSNamespaceRule". -- Base interface functions are in: -- -- * "GHCJS.DOM.CSSRule" -- -- newtype CSSNamespaceRule = CSSNamespaceRule { unCSSNamespaceRule :: JSVal } instance Eq (CSSNamespaceRule) where (CSSNamespaceRule a) == (CSSNamespaceRule b) = js_eq a b instance PToJSVal CSSNamespaceRule where pToJSVal = unCSSNamespaceRule {-# INLINE pToJSVal #-} instance PFromJSVal CSSNamespaceRule where pFromJSVal = CSSNamespaceRule {-# INLINE pFromJSVal #-} instance ToJSVal CSSNamespaceRule where toJSVal = return . unCSSNamespaceRule {-# INLINE toJSVal #-} instance FromJSVal CSSNamespaceRule where fromJSVal = return . fmap CSSNamespaceRule . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsCSSRule CSSNamespaceRule instance IsGObject CSSNamespaceRule where typeGType _ = gTypeCSSNamespaceRule {-# INLINE typeGType #-} noCSSNamespaceRule :: Maybe CSSNamespaceRule noCSSNamespaceRule = Nothing {-# INLINE noCSSNamespaceRule #-} foreign import javascript unsafe "window[\"CSSNamespaceRule\"]" gTypeCSSNamespaceRule :: GType -- | Functions for this inteface are in "GHCJS.DOM.CSSPageRule". -- Base interface functions are in: -- -- * "GHCJS.DOM.CSSRule" -- -- newtype CSSPageRule = CSSPageRule { unCSSPageRule :: JSVal } instance Eq (CSSPageRule) where (CSSPageRule a) == (CSSPageRule b) = js_eq a b instance PToJSVal CSSPageRule where pToJSVal = unCSSPageRule {-# INLINE pToJSVal #-} instance PFromJSVal CSSPageRule where pFromJSVal = CSSPageRule {-# INLINE pFromJSVal #-} instance ToJSVal CSSPageRule where toJSVal = return . unCSSPageRule {-# INLINE toJSVal #-} instance FromJSVal CSSPageRule where fromJSVal = return . fmap CSSPageRule . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsCSSRule CSSPageRule instance IsGObject CSSPageRule where typeGType _ = gTypeCSSPageRule {-# INLINE typeGType #-} noCSSPageRule :: Maybe CSSPageRule noCSSPageRule = Nothing {-# INLINE noCSSPageRule #-} foreign import javascript unsafe "window[\"CSSPageRule\"]" gTypeCSSPageRule :: GType -- | Functions for this inteface are in "GHCJS.DOM.CSSPrimitiveValue". -- Base interface functions are in: -- -- * "GHCJS.DOM.CSSValue" -- -- newtype CSSPrimitiveValue = CSSPrimitiveValue { unCSSPrimitiveValue :: JSVal } instance Eq (CSSPrimitiveValue) where (CSSPrimitiveValue a) == (CSSPrimitiveValue b) = js_eq a b instance PToJSVal CSSPrimitiveValue where pToJSVal = unCSSPrimitiveValue {-# INLINE pToJSVal #-} instance PFromJSVal CSSPrimitiveValue where pFromJSVal = CSSPrimitiveValue {-# INLINE pFromJSVal #-} instance ToJSVal CSSPrimitiveValue where toJSVal = return . unCSSPrimitiveValue {-# INLINE toJSVal #-} instance FromJSVal CSSPrimitiveValue where fromJSVal = return . fmap CSSPrimitiveValue . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsCSSValue CSSPrimitiveValue instance IsGObject CSSPrimitiveValue where typeGType _ = gTypeCSSPrimitiveValue {-# INLINE typeGType #-} noCSSPrimitiveValue :: Maybe CSSPrimitiveValue noCSSPrimitiveValue = Nothing {-# INLINE noCSSPrimitiveValue #-} foreign import javascript unsafe "window[\"CSSPrimitiveValue\"]" gTypeCSSPrimitiveValue :: GType -- | Functions for this inteface are in "GHCJS.DOM.CSSRule". -- -- newtype CSSRule = CSSRule { unCSSRule :: JSVal } instance Eq (CSSRule) where (CSSRule a) == (CSSRule b) = js_eq a b instance PToJSVal CSSRule where pToJSVal = unCSSRule {-# INLINE pToJSVal #-} instance PFromJSVal CSSRule where pFromJSVal = CSSRule {-# INLINE pFromJSVal #-} instance ToJSVal CSSRule where toJSVal = return . unCSSRule {-# INLINE toJSVal #-} instance FromJSVal CSSRule where fromJSVal = return . fmap CSSRule . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsGObject o) => IsCSSRule o toCSSRule :: IsCSSRule o => o -> CSSRule toCSSRule = CSSRule . coerce instance IsCSSRule CSSRule instance IsGObject CSSRule where typeGType _ = gTypeCSSRule {-# INLINE typeGType #-} noCSSRule :: Maybe CSSRule noCSSRule = Nothing {-# INLINE noCSSRule #-} foreign import javascript unsafe "window[\"CSSRule\"]" gTypeCSSRule :: GType -- | Functions for this inteface are in "GHCJS.DOM.CSSRuleList". -- -- newtype CSSRuleList = CSSRuleList { unCSSRuleList :: JSVal } instance Eq (CSSRuleList) where (CSSRuleList a) == (CSSRuleList b) = js_eq a b instance PToJSVal CSSRuleList where pToJSVal = unCSSRuleList {-# INLINE pToJSVal #-} instance PFromJSVal CSSRuleList where pFromJSVal = CSSRuleList {-# INLINE pFromJSVal #-} instance ToJSVal CSSRuleList where toJSVal = return . unCSSRuleList {-# INLINE toJSVal #-} instance FromJSVal CSSRuleList where fromJSVal = return . fmap CSSRuleList . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject CSSRuleList where typeGType _ = gTypeCSSRuleList {-# INLINE typeGType #-} noCSSRuleList :: Maybe CSSRuleList noCSSRuleList = Nothing {-# INLINE noCSSRuleList #-} foreign import javascript unsafe "window[\"CSSRuleList\"]" gTypeCSSRuleList :: GType -- | Functions for this inteface are in "GHCJS.DOM.CSSStyleDeclaration". -- -- newtype CSSStyleDeclaration = CSSStyleDeclaration { unCSSStyleDeclaration :: JSVal } instance Eq (CSSStyleDeclaration) where (CSSStyleDeclaration a) == (CSSStyleDeclaration b) = js_eq a b instance PToJSVal CSSStyleDeclaration where pToJSVal = unCSSStyleDeclaration {-# INLINE pToJSVal #-} instance PFromJSVal CSSStyleDeclaration where pFromJSVal = CSSStyleDeclaration {-# INLINE pFromJSVal #-} instance ToJSVal CSSStyleDeclaration where toJSVal = return . unCSSStyleDeclaration {-# INLINE toJSVal #-} instance FromJSVal CSSStyleDeclaration where fromJSVal = return . fmap CSSStyleDeclaration . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject CSSStyleDeclaration where typeGType _ = gTypeCSSStyleDeclaration {-# INLINE typeGType #-} noCSSStyleDeclaration :: Maybe CSSStyleDeclaration noCSSStyleDeclaration = Nothing {-# INLINE noCSSStyleDeclaration #-} foreign import javascript unsafe "window[\"CSSStyleDeclaration\"]" gTypeCSSStyleDeclaration :: GType -- | Functions for this inteface are in "GHCJS.DOM.CSSStyleRule". -- Base interface functions are in: -- -- * "GHCJS.DOM.CSSRule" -- -- newtype CSSStyleRule = CSSStyleRule { unCSSStyleRule :: JSVal } instance Eq (CSSStyleRule) where (CSSStyleRule a) == (CSSStyleRule b) = js_eq a b instance PToJSVal CSSStyleRule where pToJSVal = unCSSStyleRule {-# INLINE pToJSVal #-} instance PFromJSVal CSSStyleRule where pFromJSVal = CSSStyleRule {-# INLINE pFromJSVal #-} instance ToJSVal CSSStyleRule where toJSVal = return . unCSSStyleRule {-# INLINE toJSVal #-} instance FromJSVal CSSStyleRule where fromJSVal = return . fmap CSSStyleRule . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsCSSRule CSSStyleRule instance IsGObject CSSStyleRule where typeGType _ = gTypeCSSStyleRule {-# INLINE typeGType #-} noCSSStyleRule :: Maybe CSSStyleRule noCSSStyleRule = Nothing {-# INLINE noCSSStyleRule #-} foreign import javascript unsafe "window[\"CSSStyleRule\"]" gTypeCSSStyleRule :: GType -- | Functions for this inteface are in "GHCJS.DOM.CSSStyleSheet". -- Base interface functions are in: -- -- * "GHCJS.DOM.StyleSheet" -- -- newtype CSSStyleSheet = CSSStyleSheet { unCSSStyleSheet :: JSVal } instance Eq (CSSStyleSheet) where (CSSStyleSheet a) == (CSSStyleSheet b) = js_eq a b instance PToJSVal CSSStyleSheet where pToJSVal = unCSSStyleSheet {-# INLINE pToJSVal #-} instance PFromJSVal CSSStyleSheet where pFromJSVal = CSSStyleSheet {-# INLINE pFromJSVal #-} instance ToJSVal CSSStyleSheet where toJSVal = return . unCSSStyleSheet {-# INLINE toJSVal #-} instance FromJSVal CSSStyleSheet where fromJSVal = return . fmap CSSStyleSheet . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsStyleSheet CSSStyleSheet instance IsGObject CSSStyleSheet where typeGType _ = gTypeCSSStyleSheet {-# INLINE typeGType #-} noCSSStyleSheet :: Maybe CSSStyleSheet noCSSStyleSheet = Nothing {-# INLINE noCSSStyleSheet #-} foreign import javascript unsafe "window[\"CSSStyleSheet\"]" gTypeCSSStyleSheet :: GType -- | Functions for this inteface are in "GHCJS.DOM.CSSSupportsRule". -- Base interface functions are in: -- -- * "GHCJS.DOM.CSSRule" -- -- newtype CSSSupportsRule = CSSSupportsRule { unCSSSupportsRule :: JSVal } instance Eq (CSSSupportsRule) where (CSSSupportsRule a) == (CSSSupportsRule b) = js_eq a b instance PToJSVal CSSSupportsRule where pToJSVal = unCSSSupportsRule {-# INLINE pToJSVal #-} instance PFromJSVal CSSSupportsRule where pFromJSVal = CSSSupportsRule {-# INLINE pFromJSVal #-} instance ToJSVal CSSSupportsRule where toJSVal = return . unCSSSupportsRule {-# INLINE toJSVal #-} instance FromJSVal CSSSupportsRule where fromJSVal = return . fmap CSSSupportsRule . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsCSSRule CSSSupportsRule instance IsGObject CSSSupportsRule where typeGType _ = gTypeCSSSupportsRule {-# INLINE typeGType #-} noCSSSupportsRule :: Maybe CSSSupportsRule noCSSSupportsRule = Nothing {-# INLINE noCSSSupportsRule #-} foreign import javascript unsafe "window[\"CSSSupportsRule\"]" gTypeCSSSupportsRule :: GType -- | Functions for this inteface are in "GHCJS.DOM.CSSUnknownRule". -- Base interface functions are in: -- -- * "GHCJS.DOM.CSSRule" -- -- newtype CSSUnknownRule = CSSUnknownRule { unCSSUnknownRule :: JSVal } instance Eq (CSSUnknownRule) where (CSSUnknownRule a) == (CSSUnknownRule b) = js_eq a b instance PToJSVal CSSUnknownRule where pToJSVal = unCSSUnknownRule {-# INLINE pToJSVal #-} instance PFromJSVal CSSUnknownRule where pFromJSVal = CSSUnknownRule {-# INLINE pFromJSVal #-} instance ToJSVal CSSUnknownRule where toJSVal = return . unCSSUnknownRule {-# INLINE toJSVal #-} instance FromJSVal CSSUnknownRule where fromJSVal = return . fmap CSSUnknownRule . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsCSSRule CSSUnknownRule instance IsGObject CSSUnknownRule where typeGType _ = gTypeCSSUnknownRule {-# INLINE typeGType #-} noCSSUnknownRule :: Maybe CSSUnknownRule noCSSUnknownRule = Nothing {-# INLINE noCSSUnknownRule #-} foreign import javascript unsafe "window[\"CSSUnknownRule\"]" gTypeCSSUnknownRule :: GType -- | Functions for this inteface are in "GHCJS.DOM.CSSValue". -- -- newtype CSSValue = CSSValue { unCSSValue :: JSVal } instance Eq (CSSValue) where (CSSValue a) == (CSSValue b) = js_eq a b instance PToJSVal CSSValue where pToJSVal = unCSSValue {-# INLINE pToJSVal #-} instance PFromJSVal CSSValue where pFromJSVal = CSSValue {-# INLINE pFromJSVal #-} instance ToJSVal CSSValue where toJSVal = return . unCSSValue {-# INLINE toJSVal #-} instance FromJSVal CSSValue where fromJSVal = return . fmap CSSValue . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsGObject o) => IsCSSValue o toCSSValue :: IsCSSValue o => o -> CSSValue toCSSValue = CSSValue . coerce instance IsCSSValue CSSValue instance IsGObject CSSValue where typeGType _ = gTypeCSSValue {-# INLINE typeGType #-} noCSSValue :: Maybe CSSValue noCSSValue = Nothing {-# INLINE noCSSValue #-} foreign import javascript unsafe "window[\"CSSValue\"]" gTypeCSSValue :: GType -- | Functions for this inteface are in "GHCJS.DOM.CSSValueList". -- Base interface functions are in: -- -- * "GHCJS.DOM.CSSValue" -- -- newtype CSSValueList = CSSValueList { unCSSValueList :: JSVal } instance Eq (CSSValueList) where (CSSValueList a) == (CSSValueList b) = js_eq a b instance PToJSVal CSSValueList where pToJSVal = unCSSValueList {-# INLINE pToJSVal #-} instance PFromJSVal CSSValueList where pFromJSVal = CSSValueList {-# INLINE pFromJSVal #-} instance ToJSVal CSSValueList where toJSVal = return . unCSSValueList {-# INLINE toJSVal #-} instance FromJSVal CSSValueList where fromJSVal = return . fmap CSSValueList . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsCSSValue CSSValueList instance IsGObject CSSValueList where typeGType _ = gTypeCSSValueList {-# INLINE typeGType #-} noCSSValueList :: Maybe CSSValueList noCSSValueList = Nothing {-# INLINE noCSSValueList #-} foreign import javascript unsafe "window[\"CSSValueList\"]" gTypeCSSValueList :: GType -- | Functions for this inteface are in "GHCJS.DOM.CanvasCaptureMediaStreamTrack". -- Base interface functions are in: -- -- * "GHCJS.DOM.MediaStreamTrack" -- * "GHCJS.DOM.EventTarget" -- -- newtype CanvasCaptureMediaStreamTrack = CanvasCaptureMediaStreamTrack { unCanvasCaptureMediaStreamTrack :: JSVal } instance Eq (CanvasCaptureMediaStreamTrack) where (CanvasCaptureMediaStreamTrack a) == (CanvasCaptureMediaStreamTrack b) = js_eq a b instance PToJSVal CanvasCaptureMediaStreamTrack where pToJSVal = unCanvasCaptureMediaStreamTrack {-# INLINE pToJSVal #-} instance PFromJSVal CanvasCaptureMediaStreamTrack where pFromJSVal = CanvasCaptureMediaStreamTrack {-# INLINE pFromJSVal #-} instance ToJSVal CanvasCaptureMediaStreamTrack where toJSVal = return . unCanvasCaptureMediaStreamTrack {-# INLINE toJSVal #-} instance FromJSVal CanvasCaptureMediaStreamTrack where fromJSVal = return . fmap CanvasCaptureMediaStreamTrack . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsMediaStreamTrack CanvasCaptureMediaStreamTrack instance IsEventTarget CanvasCaptureMediaStreamTrack instance IsGObject CanvasCaptureMediaStreamTrack where typeGType _ = gTypeCanvasCaptureMediaStreamTrack {-# INLINE typeGType #-} noCanvasCaptureMediaStreamTrack :: Maybe CanvasCaptureMediaStreamTrack noCanvasCaptureMediaStreamTrack = Nothing {-# INLINE noCanvasCaptureMediaStreamTrack #-} foreign import javascript unsafe "window[\"CanvasCaptureMediaStreamTrack\"]" gTypeCanvasCaptureMediaStreamTrack :: GType -- | Functions for this inteface are in "GHCJS.DOM.CanvasGradient". -- -- newtype CanvasGradient = CanvasGradient { unCanvasGradient :: JSVal } instance Eq (CanvasGradient) where (CanvasGradient a) == (CanvasGradient b) = js_eq a b instance PToJSVal CanvasGradient where pToJSVal = unCanvasGradient {-# INLINE pToJSVal #-} instance PFromJSVal CanvasGradient where pFromJSVal = CanvasGradient {-# INLINE pFromJSVal #-} instance ToJSVal CanvasGradient where toJSVal = return . unCanvasGradient {-# INLINE toJSVal #-} instance FromJSVal CanvasGradient where fromJSVal = return . fmap CanvasGradient . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject CanvasGradient where typeGType _ = gTypeCanvasGradient {-# INLINE typeGType #-} noCanvasGradient :: Maybe CanvasGradient noCanvasGradient = Nothing {-# INLINE noCanvasGradient #-} foreign import javascript unsafe "window[\"CanvasGradient\"]" gTypeCanvasGradient :: GType -- | Functions for this inteface are in "GHCJS.DOM.CanvasPath". -- -- newtype CanvasPath = CanvasPath { unCanvasPath :: JSVal } instance Eq (CanvasPath) where (CanvasPath a) == (CanvasPath b) = js_eq a b instance PToJSVal CanvasPath where pToJSVal = unCanvasPath {-# INLINE pToJSVal #-} instance PFromJSVal CanvasPath where pFromJSVal = CanvasPath {-# INLINE pFromJSVal #-} instance ToJSVal CanvasPath where toJSVal = return . unCanvasPath {-# INLINE toJSVal #-} instance FromJSVal CanvasPath where fromJSVal = return . fmap CanvasPath . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsGObject o) => IsCanvasPath o toCanvasPath :: IsCanvasPath o => o -> CanvasPath toCanvasPath = CanvasPath . coerce instance IsCanvasPath CanvasPath instance IsGObject CanvasPath where typeGType _ = gTypeCanvasPath {-# INLINE typeGType #-} noCanvasPath :: Maybe CanvasPath noCanvasPath = Nothing {-# INLINE noCanvasPath #-} foreign import javascript unsafe "window[\"CanvasPath\"]" gTypeCanvasPath :: GType -- | Functions for this inteface are in "GHCJS.DOM.CanvasPattern". -- -- newtype CanvasPattern = CanvasPattern { unCanvasPattern :: JSVal } instance Eq (CanvasPattern) where (CanvasPattern a) == (CanvasPattern b) = js_eq a b instance PToJSVal CanvasPattern where pToJSVal = unCanvasPattern {-# INLINE pToJSVal #-} instance PFromJSVal CanvasPattern where pFromJSVal = CanvasPattern {-# INLINE pFromJSVal #-} instance ToJSVal CanvasPattern where toJSVal = return . unCanvasPattern {-# INLINE toJSVal #-} instance FromJSVal CanvasPattern where fromJSVal = return . fmap CanvasPattern . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject CanvasPattern where typeGType _ = gTypeCanvasPattern {-# INLINE typeGType #-} noCanvasPattern :: Maybe CanvasPattern noCanvasPattern = Nothing {-# INLINE noCanvasPattern #-} foreign import javascript unsafe "window[\"CanvasPattern\"]" gTypeCanvasPattern :: GType -- | Functions for this inteface are in "GHCJS.DOM.CanvasProxy". -- -- newtype CanvasProxy = CanvasProxy { unCanvasProxy :: JSVal } instance Eq (CanvasProxy) where (CanvasProxy a) == (CanvasProxy b) = js_eq a b instance PToJSVal CanvasProxy where pToJSVal = unCanvasProxy {-# INLINE pToJSVal #-} instance PFromJSVal CanvasProxy where pFromJSVal = CanvasProxy {-# INLINE pFromJSVal #-} instance ToJSVal CanvasProxy where toJSVal = return . unCanvasProxy {-# INLINE toJSVal #-} instance FromJSVal CanvasProxy where fromJSVal = return . fmap CanvasProxy . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject CanvasProxy where typeGType _ = gTypeCanvasProxy {-# INLINE typeGType #-} noCanvasProxy :: Maybe CanvasProxy noCanvasProxy = Nothing {-# INLINE noCanvasProxy #-} foreign import javascript unsafe "window[\"CanvasProxy\"]" gTypeCanvasProxy :: GType -- | Functions for this inteface are in "GHCJS.DOM.CanvasRenderingContext2D". -- Base interface functions are in: -- -- * "GHCJS.DOM.CanvasPath" -- -- newtype CanvasRenderingContext2D = CanvasRenderingContext2D { unCanvasRenderingContext2D :: JSVal } instance Eq (CanvasRenderingContext2D) where (CanvasRenderingContext2D a) == (CanvasRenderingContext2D b) = js_eq a b instance PToJSVal CanvasRenderingContext2D where pToJSVal = unCanvasRenderingContext2D {-# INLINE pToJSVal #-} instance PFromJSVal CanvasRenderingContext2D where pFromJSVal = CanvasRenderingContext2D {-# INLINE pFromJSVal #-} instance ToJSVal CanvasRenderingContext2D where toJSVal = return . unCanvasRenderingContext2D {-# INLINE toJSVal #-} instance FromJSVal CanvasRenderingContext2D where fromJSVal = return . fmap CanvasRenderingContext2D . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsCanvasPath CanvasRenderingContext2D instance IsGObject CanvasRenderingContext2D where typeGType _ = gTypeCanvasRenderingContext2D {-# INLINE typeGType #-} noCanvasRenderingContext2D :: Maybe CanvasRenderingContext2D noCanvasRenderingContext2D = Nothing {-# INLINE noCanvasRenderingContext2D #-} foreign import javascript unsafe "window[\"CanvasRenderingContext2D\"]" gTypeCanvasRenderingContext2D :: GType -- | Functions for this inteface are in "GHCJS.DOM.ChannelMergerNode". -- Base interface functions are in: -- -- * "GHCJS.DOM.AudioNode" -- * "GHCJS.DOM.EventTarget" -- -- newtype ChannelMergerNode = ChannelMergerNode { unChannelMergerNode :: JSVal } instance Eq (ChannelMergerNode) where (ChannelMergerNode a) == (ChannelMergerNode b) = js_eq a b instance PToJSVal ChannelMergerNode where pToJSVal = unChannelMergerNode {-# INLINE pToJSVal #-} instance PFromJSVal ChannelMergerNode where pFromJSVal = ChannelMergerNode {-# INLINE pFromJSVal #-} instance ToJSVal ChannelMergerNode where toJSVal = return . unChannelMergerNode {-# INLINE toJSVal #-} instance FromJSVal ChannelMergerNode where fromJSVal = return . fmap ChannelMergerNode . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsAudioNode ChannelMergerNode instance IsEventTarget ChannelMergerNode instance IsGObject ChannelMergerNode where typeGType _ = gTypeChannelMergerNode {-# INLINE typeGType #-} noChannelMergerNode :: Maybe ChannelMergerNode noChannelMergerNode = Nothing {-# INLINE noChannelMergerNode #-} foreign import javascript unsafe "window[\"ChannelMergerNode\"]" gTypeChannelMergerNode :: GType -- | Functions for this inteface are in "GHCJS.DOM.ChannelSplitterNode". -- Base interface functions are in: -- -- * "GHCJS.DOM.AudioNode" -- * "GHCJS.DOM.EventTarget" -- -- newtype ChannelSplitterNode = ChannelSplitterNode { unChannelSplitterNode :: JSVal } instance Eq (ChannelSplitterNode) where (ChannelSplitterNode a) == (ChannelSplitterNode b) = js_eq a b instance PToJSVal ChannelSplitterNode where pToJSVal = unChannelSplitterNode {-# INLINE pToJSVal #-} instance PFromJSVal ChannelSplitterNode where pFromJSVal = ChannelSplitterNode {-# INLINE pFromJSVal #-} instance ToJSVal ChannelSplitterNode where toJSVal = return . unChannelSplitterNode {-# INLINE toJSVal #-} instance FromJSVal ChannelSplitterNode where fromJSVal = return . fmap ChannelSplitterNode . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsAudioNode ChannelSplitterNode instance IsEventTarget ChannelSplitterNode instance IsGObject ChannelSplitterNode where typeGType _ = gTypeChannelSplitterNode {-# INLINE typeGType #-} noChannelSplitterNode :: Maybe ChannelSplitterNode noChannelSplitterNode = Nothing {-# INLINE noChannelSplitterNode #-} foreign import javascript unsafe "window[\"ChannelSplitterNode\"]" gTypeChannelSplitterNode :: GType -- | Functions for this inteface are in "GHCJS.DOM.CharacterData". -- Base interface functions are in: -- -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.ChildNode" -- -- newtype CharacterData = CharacterData { unCharacterData :: JSVal } instance Eq (CharacterData) where (CharacterData a) == (CharacterData b) = js_eq a b instance PToJSVal CharacterData where pToJSVal = unCharacterData {-# INLINE pToJSVal #-} instance PFromJSVal CharacterData where pFromJSVal = CharacterData {-# INLINE pFromJSVal #-} instance ToJSVal CharacterData where toJSVal = return . unCharacterData {-# INLINE toJSVal #-} instance FromJSVal CharacterData where fromJSVal = return . fmap CharacterData . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsNode o, IsEventTarget o, IsNonDocumentTypeChildNode o, IsChildNode o, IsGObject o) => IsCharacterData o toCharacterData :: IsCharacterData o => o -> CharacterData toCharacterData = CharacterData . coerce instance IsCharacterData CharacterData instance IsNode CharacterData instance IsEventTarget CharacterData instance IsNonDocumentTypeChildNode CharacterData instance IsChildNode CharacterData instance IsGObject CharacterData where typeGType _ = gTypeCharacterData {-# INLINE typeGType #-} noCharacterData :: Maybe CharacterData noCharacterData = Nothing {-# INLINE noCharacterData #-} foreign import javascript unsafe "window[\"CharacterData\"]" gTypeCharacterData :: GType -- | Functions for this inteface are in "GHCJS.DOM.ChildNode". -- -- newtype ChildNode = ChildNode { unChildNode :: JSVal } instance Eq (ChildNode) where (ChildNode a) == (ChildNode b) = js_eq a b instance PToJSVal ChildNode where pToJSVal = unChildNode {-# INLINE pToJSVal #-} instance PFromJSVal ChildNode where pFromJSVal = ChildNode {-# INLINE pFromJSVal #-} instance ToJSVal ChildNode where toJSVal = return . unChildNode {-# INLINE toJSVal #-} instance FromJSVal ChildNode where fromJSVal = return . fmap ChildNode . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsGObject o) => IsChildNode o toChildNode :: IsChildNode o => o -> ChildNode toChildNode = ChildNode . coerce instance IsChildNode ChildNode instance IsGObject ChildNode where typeGType _ = gTypeChildNode {-# INLINE typeGType #-} noChildNode :: Maybe ChildNode noChildNode = Nothing {-# INLINE noChildNode #-} foreign import javascript unsafe "window[\"ChildNode\"]" gTypeChildNode :: GType -- | Functions for this inteface are in "GHCJS.DOM.ClipboardEvent". -- Base interface functions are in: -- -- * "GHCJS.DOM.Event" -- -- newtype ClipboardEvent = ClipboardEvent { unClipboardEvent :: JSVal } instance Eq (ClipboardEvent) where (ClipboardEvent a) == (ClipboardEvent b) = js_eq a b instance PToJSVal ClipboardEvent where pToJSVal = unClipboardEvent {-# INLINE pToJSVal #-} instance PFromJSVal ClipboardEvent where pFromJSVal = ClipboardEvent {-# INLINE pFromJSVal #-} instance ToJSVal ClipboardEvent where toJSVal = return . unClipboardEvent {-# INLINE toJSVal #-} instance FromJSVal ClipboardEvent where fromJSVal = return . fmap ClipboardEvent . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEvent ClipboardEvent instance IsGObject ClipboardEvent where typeGType _ = gTypeClipboardEvent {-# INLINE typeGType #-} noClipboardEvent :: Maybe ClipboardEvent noClipboardEvent = Nothing {-# INLINE noClipboardEvent #-} foreign import javascript unsafe "window[\"ClipboardEvent\"]" gTypeClipboardEvent :: GType -- | Functions for this inteface are in "GHCJS.DOM.ClipboardEventInit". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventInit" -- -- newtype ClipboardEventInit = ClipboardEventInit { unClipboardEventInit :: JSVal } instance Eq (ClipboardEventInit) where (ClipboardEventInit a) == (ClipboardEventInit b) = js_eq a b instance PToJSVal ClipboardEventInit where pToJSVal = unClipboardEventInit {-# INLINE pToJSVal #-} instance PFromJSVal ClipboardEventInit where pFromJSVal = ClipboardEventInit {-# INLINE pFromJSVal #-} instance ToJSVal ClipboardEventInit where toJSVal = return . unClipboardEventInit {-# INLINE toJSVal #-} instance FromJSVal ClipboardEventInit where fromJSVal = return . fmap ClipboardEventInit . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventInit ClipboardEventInit instance IsGObject ClipboardEventInit where typeGType _ = gTypeClipboardEventInit {-# INLINE typeGType #-} noClipboardEventInit :: Maybe ClipboardEventInit noClipboardEventInit = Nothing {-# INLINE noClipboardEventInit #-} foreign import javascript unsafe "window[\"ClipboardEventInit\"]" gTypeClipboardEventInit :: GType -- | Functions for this inteface are in "GHCJS.DOM.CloseEvent". -- Base interface functions are in: -- -- * "GHCJS.DOM.Event" -- -- newtype CloseEvent = CloseEvent { unCloseEvent :: JSVal } instance Eq (CloseEvent) where (CloseEvent a) == (CloseEvent b) = js_eq a b instance PToJSVal CloseEvent where pToJSVal = unCloseEvent {-# INLINE pToJSVal #-} instance PFromJSVal CloseEvent where pFromJSVal = CloseEvent {-# INLINE pFromJSVal #-} instance ToJSVal CloseEvent where toJSVal = return . unCloseEvent {-# INLINE toJSVal #-} instance FromJSVal CloseEvent where fromJSVal = return . fmap CloseEvent . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEvent CloseEvent instance IsGObject CloseEvent where typeGType _ = gTypeCloseEvent {-# INLINE typeGType #-} noCloseEvent :: Maybe CloseEvent noCloseEvent = Nothing {-# INLINE noCloseEvent #-} foreign import javascript unsafe "window[\"CloseEvent\"]" gTypeCloseEvent :: GType -- | Functions for this inteface are in "GHCJS.DOM.CloseEventInit". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventInit" -- -- newtype CloseEventInit = CloseEventInit { unCloseEventInit :: JSVal } instance Eq (CloseEventInit) where (CloseEventInit a) == (CloseEventInit b) = js_eq a b instance PToJSVal CloseEventInit where pToJSVal = unCloseEventInit {-# INLINE pToJSVal #-} instance PFromJSVal CloseEventInit where pFromJSVal = CloseEventInit {-# INLINE pFromJSVal #-} instance ToJSVal CloseEventInit where toJSVal = return . unCloseEventInit {-# INLINE toJSVal #-} instance FromJSVal CloseEventInit where fromJSVal = return . fmap CloseEventInit . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventInit CloseEventInit instance IsGObject CloseEventInit where typeGType _ = gTypeCloseEventInit {-# INLINE typeGType #-} noCloseEventInit :: Maybe CloseEventInit noCloseEventInit = Nothing {-# INLINE noCloseEventInit #-} foreign import javascript unsafe "window[\"CloseEventInit\"]" gTypeCloseEventInit :: GType -- | Functions for this inteface are in "GHCJS.DOM.CommandLineAPIHost". -- -- newtype CommandLineAPIHost = CommandLineAPIHost { unCommandLineAPIHost :: JSVal } instance Eq (CommandLineAPIHost) where (CommandLineAPIHost a) == (CommandLineAPIHost b) = js_eq a b instance PToJSVal CommandLineAPIHost where pToJSVal = unCommandLineAPIHost {-# INLINE pToJSVal #-} instance PFromJSVal CommandLineAPIHost where pFromJSVal = CommandLineAPIHost {-# INLINE pFromJSVal #-} instance ToJSVal CommandLineAPIHost where toJSVal = return . unCommandLineAPIHost {-# INLINE toJSVal #-} instance FromJSVal CommandLineAPIHost where fromJSVal = return . fmap CommandLineAPIHost . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject CommandLineAPIHost where typeGType _ = gTypeCommandLineAPIHost {-# INLINE typeGType #-} noCommandLineAPIHost :: Maybe CommandLineAPIHost noCommandLineAPIHost = Nothing {-# INLINE noCommandLineAPIHost #-} foreign import javascript unsafe "window[\"CommandLineAPIHost\"]" gTypeCommandLineAPIHost :: GType -- | Functions for this inteface are in "GHCJS.DOM.Comment". -- Base interface functions are in: -- -- * "GHCJS.DOM.CharacterData" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.ChildNode" -- -- newtype Comment = Comment { unComment :: JSVal } instance Eq (Comment) where (Comment a) == (Comment b) = js_eq a b instance PToJSVal Comment where pToJSVal = unComment {-# INLINE pToJSVal #-} instance PFromJSVal Comment where pFromJSVal = Comment {-# INLINE pFromJSVal #-} instance ToJSVal Comment where toJSVal = return . unComment {-# INLINE toJSVal #-} instance FromJSVal Comment where fromJSVal = return . fmap Comment . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsCharacterData Comment instance IsNode Comment instance IsEventTarget Comment instance IsNonDocumentTypeChildNode Comment instance IsChildNode Comment instance IsGObject Comment where typeGType _ = gTypeComment {-# INLINE typeGType #-} noComment :: Maybe Comment noComment = Nothing {-# INLINE noComment #-} foreign import javascript unsafe "window[\"Comment\"]" gTypeComment :: GType -- | Functions for this inteface are in "GHCJS.DOM.CompositionEvent". -- Base interface functions are in: -- -- * "GHCJS.DOM.UIEvent" -- * "GHCJS.DOM.Event" -- -- newtype CompositionEvent = CompositionEvent { unCompositionEvent :: JSVal } instance Eq (CompositionEvent) where (CompositionEvent a) == (CompositionEvent b) = js_eq a b instance PToJSVal CompositionEvent where pToJSVal = unCompositionEvent {-# INLINE pToJSVal #-} instance PFromJSVal CompositionEvent where pFromJSVal = CompositionEvent {-# INLINE pFromJSVal #-} instance ToJSVal CompositionEvent where toJSVal = return . unCompositionEvent {-# INLINE toJSVal #-} instance FromJSVal CompositionEvent where fromJSVal = return . fmap CompositionEvent . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsUIEvent CompositionEvent instance IsEvent CompositionEvent instance IsGObject CompositionEvent where typeGType _ = gTypeCompositionEvent {-# INLINE typeGType #-} noCompositionEvent :: Maybe CompositionEvent noCompositionEvent = Nothing {-# INLINE noCompositionEvent #-} foreign import javascript unsafe "window[\"CompositionEvent\"]" gTypeCompositionEvent :: GType -- | Functions for this inteface are in "GHCJS.DOM.CompositionEventInit". -- Base interface functions are in: -- -- * "GHCJS.DOM.UIEventInit" -- * "GHCJS.DOM.EventInit" -- -- newtype CompositionEventInit = CompositionEventInit { unCompositionEventInit :: JSVal } instance Eq (CompositionEventInit) where (CompositionEventInit a) == (CompositionEventInit b) = js_eq a b instance PToJSVal CompositionEventInit where pToJSVal = unCompositionEventInit {-# INLINE pToJSVal #-} instance PFromJSVal CompositionEventInit where pFromJSVal = CompositionEventInit {-# INLINE pFromJSVal #-} instance ToJSVal CompositionEventInit where toJSVal = return . unCompositionEventInit {-# INLINE toJSVal #-} instance FromJSVal CompositionEventInit where fromJSVal = return . fmap CompositionEventInit . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsUIEventInit CompositionEventInit instance IsEventInit CompositionEventInit instance IsGObject CompositionEventInit where typeGType _ = gTypeCompositionEventInit {-# INLINE typeGType #-} noCompositionEventInit :: Maybe CompositionEventInit noCompositionEventInit = Nothing {-# INLINE noCompositionEventInit #-} foreign import javascript unsafe "window[\"CompositionEventInit\"]" gTypeCompositionEventInit :: GType -- | Functions for this inteface are in "GHCJS.DOM.ConstrainBooleanParameters". -- -- newtype ConstrainBooleanParameters = ConstrainBooleanParameters { unConstrainBooleanParameters :: JSVal } instance Eq (ConstrainBooleanParameters) where (ConstrainBooleanParameters a) == (ConstrainBooleanParameters b) = js_eq a b instance PToJSVal ConstrainBooleanParameters where pToJSVal = unConstrainBooleanParameters {-# INLINE pToJSVal #-} instance PFromJSVal ConstrainBooleanParameters where pFromJSVal = ConstrainBooleanParameters {-# INLINE pFromJSVal #-} instance ToJSVal ConstrainBooleanParameters where toJSVal = return . unConstrainBooleanParameters {-# INLINE toJSVal #-} instance FromJSVal ConstrainBooleanParameters where fromJSVal = return . fmap ConstrainBooleanParameters . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject ConstrainBooleanParameters where typeGType _ = gTypeConstrainBooleanParameters {-# INLINE typeGType #-} noConstrainBooleanParameters :: Maybe ConstrainBooleanParameters noConstrainBooleanParameters = Nothing {-# INLINE noConstrainBooleanParameters #-} foreign import javascript unsafe "window[\"ConstrainBooleanParameters\"]" gTypeConstrainBooleanParameters :: GType -- | Functions for this inteface are in "GHCJS.DOM.ConstrainDOMStringParameters". -- -- newtype ConstrainDOMStringParameters = ConstrainDOMStringParameters { unConstrainDOMStringParameters :: JSVal } instance Eq (ConstrainDOMStringParameters) where (ConstrainDOMStringParameters a) == (ConstrainDOMStringParameters b) = js_eq a b instance PToJSVal ConstrainDOMStringParameters where pToJSVal = unConstrainDOMStringParameters {-# INLINE pToJSVal #-} instance PFromJSVal ConstrainDOMStringParameters where pFromJSVal = ConstrainDOMStringParameters {-# INLINE pFromJSVal #-} instance ToJSVal ConstrainDOMStringParameters where toJSVal = return . unConstrainDOMStringParameters {-# INLINE toJSVal #-} instance FromJSVal ConstrainDOMStringParameters where fromJSVal = return . fmap ConstrainDOMStringParameters . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject ConstrainDOMStringParameters where typeGType _ = gTypeConstrainDOMStringParameters {-# INLINE typeGType #-} noConstrainDOMStringParameters :: Maybe ConstrainDOMStringParameters noConstrainDOMStringParameters = Nothing {-# INLINE noConstrainDOMStringParameters #-} foreign import javascript unsafe "window[\"ConstrainDOMStringParameters\"]" gTypeConstrainDOMStringParameters :: GType -- | Functions for this inteface are in "GHCJS.DOM.ConstrainDoubleRange". -- Base interface functions are in: -- -- * "GHCJS.DOM.DoubleRange" -- -- newtype ConstrainDoubleRange = ConstrainDoubleRange { unConstrainDoubleRange :: JSVal } instance Eq (ConstrainDoubleRange) where (ConstrainDoubleRange a) == (ConstrainDoubleRange b) = js_eq a b instance PToJSVal ConstrainDoubleRange where pToJSVal = unConstrainDoubleRange {-# INLINE pToJSVal #-} instance PFromJSVal ConstrainDoubleRange where pFromJSVal = ConstrainDoubleRange {-# INLINE pFromJSVal #-} instance ToJSVal ConstrainDoubleRange where toJSVal = return . unConstrainDoubleRange {-# INLINE toJSVal #-} instance FromJSVal ConstrainDoubleRange where fromJSVal = return . fmap ConstrainDoubleRange . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsDoubleRange ConstrainDoubleRange instance IsGObject ConstrainDoubleRange where typeGType _ = gTypeConstrainDoubleRange {-# INLINE typeGType #-} noConstrainDoubleRange :: Maybe ConstrainDoubleRange noConstrainDoubleRange = Nothing {-# INLINE noConstrainDoubleRange #-} foreign import javascript unsafe "window[\"ConstrainDoubleRange\"]" gTypeConstrainDoubleRange :: GType -- | Functions for this inteface are in "GHCJS.DOM.ConstrainLongRange". -- Base interface functions are in: -- -- * "GHCJS.DOM.LongRange" -- -- newtype ConstrainLongRange = ConstrainLongRange { unConstrainLongRange :: JSVal } instance Eq (ConstrainLongRange) where (ConstrainLongRange a) == (ConstrainLongRange b) = js_eq a b instance PToJSVal ConstrainLongRange where pToJSVal = unConstrainLongRange {-# INLINE pToJSVal #-} instance PFromJSVal ConstrainLongRange where pFromJSVal = ConstrainLongRange {-# INLINE pFromJSVal #-} instance ToJSVal ConstrainLongRange where toJSVal = return . unConstrainLongRange {-# INLINE toJSVal #-} instance FromJSVal ConstrainLongRange where fromJSVal = return . fmap ConstrainLongRange . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsLongRange ConstrainLongRange instance IsGObject ConstrainLongRange where typeGType _ = gTypeConstrainLongRange {-# INLINE typeGType #-} noConstrainLongRange :: Maybe ConstrainLongRange noConstrainLongRange = Nothing {-# INLINE noConstrainLongRange #-} foreign import javascript unsafe "window[\"ConstrainLongRange\"]" gTypeConstrainLongRange :: GType -- | Functions for this inteface are in "GHCJS.DOM.ConvolverNode". -- Base interface functions are in: -- -- * "GHCJS.DOM.AudioNode" -- * "GHCJS.DOM.EventTarget" -- -- newtype ConvolverNode = ConvolverNode { unConvolverNode :: JSVal } instance Eq (ConvolverNode) where (ConvolverNode a) == (ConvolverNode b) = js_eq a b instance PToJSVal ConvolverNode where pToJSVal = unConvolverNode {-# INLINE pToJSVal #-} instance PFromJSVal ConvolverNode where pFromJSVal = ConvolverNode {-# INLINE pFromJSVal #-} instance ToJSVal ConvolverNode where toJSVal = return . unConvolverNode {-# INLINE toJSVal #-} instance FromJSVal ConvolverNode where fromJSVal = return . fmap ConvolverNode . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsAudioNode ConvolverNode instance IsEventTarget ConvolverNode instance IsGObject ConvolverNode where typeGType _ = gTypeConvolverNode {-# INLINE typeGType #-} noConvolverNode :: Maybe ConvolverNode noConvolverNode = Nothing {-# INLINE noConvolverNode #-} foreign import javascript unsafe "window[\"ConvolverNode\"]" gTypeConvolverNode :: GType -- | Functions for this inteface are in "GHCJS.DOM.Coordinates". -- -- newtype Coordinates = Coordinates { unCoordinates :: JSVal } instance Eq (Coordinates) where (Coordinates a) == (Coordinates b) = js_eq a b instance PToJSVal Coordinates where pToJSVal = unCoordinates {-# INLINE pToJSVal #-} instance PFromJSVal Coordinates where pFromJSVal = Coordinates {-# INLINE pFromJSVal #-} instance ToJSVal Coordinates where toJSVal = return . unCoordinates {-# INLINE toJSVal #-} instance FromJSVal Coordinates where fromJSVal = return . fmap Coordinates . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject Coordinates where typeGType _ = gTypeCoordinates {-# INLINE typeGType #-} noCoordinates :: Maybe Coordinates noCoordinates = Nothing {-# INLINE noCoordinates #-} foreign import javascript unsafe "window[\"Coordinates\"]" gTypeCoordinates :: GType -- | Functions for this inteface are in "GHCJS.DOM.CountQueuingStrategy". -- -- newtype CountQueuingStrategy = CountQueuingStrategy { unCountQueuingStrategy :: JSVal } instance Eq (CountQueuingStrategy) where (CountQueuingStrategy a) == (CountQueuingStrategy b) = js_eq a b instance PToJSVal CountQueuingStrategy where pToJSVal = unCountQueuingStrategy {-# INLINE pToJSVal #-} instance PFromJSVal CountQueuingStrategy where pFromJSVal = CountQueuingStrategy {-# INLINE pFromJSVal #-} instance ToJSVal CountQueuingStrategy where toJSVal = return . unCountQueuingStrategy {-# INLINE toJSVal #-} instance FromJSVal CountQueuingStrategy where fromJSVal = return . fmap CountQueuingStrategy . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject CountQueuingStrategy where typeGType _ = gTypeCountQueuingStrategy {-# INLINE typeGType #-} noCountQueuingStrategy :: Maybe CountQueuingStrategy noCountQueuingStrategy = Nothing {-# INLINE noCountQueuingStrategy #-} foreign import javascript unsafe "window[\"CountQueuingStrategy\"]" gTypeCountQueuingStrategy :: GType -- | Functions for this inteface are in "GHCJS.DOM.Counter". -- -- newtype Counter = Counter { unCounter :: JSVal } instance Eq (Counter) where (Counter a) == (Counter b) = js_eq a b instance PToJSVal Counter where pToJSVal = unCounter {-# INLINE pToJSVal #-} instance PFromJSVal Counter where pFromJSVal = Counter {-# INLINE pFromJSVal #-} instance ToJSVal Counter where toJSVal = return . unCounter {-# INLINE toJSVal #-} instance FromJSVal Counter where fromJSVal = return . fmap Counter . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject Counter where typeGType _ = gTypeCounter {-# INLINE typeGType #-} noCounter :: Maybe Counter noCounter = Nothing {-# INLINE noCounter #-} foreign import javascript unsafe "window[\"Counter\"]" gTypeCounter :: GType -- | Functions for this inteface are in "GHCJS.DOM.CredentialData". -- -- newtype CredentialData = CredentialData { unCredentialData :: JSVal } instance Eq (CredentialData) where (CredentialData a) == (CredentialData b) = js_eq a b instance PToJSVal CredentialData where pToJSVal = unCredentialData {-# INLINE pToJSVal #-} instance PFromJSVal CredentialData where pFromJSVal = CredentialData {-# INLINE pFromJSVal #-} instance ToJSVal CredentialData where toJSVal = return . unCredentialData {-# INLINE toJSVal #-} instance FromJSVal CredentialData where fromJSVal = return . fmap CredentialData . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsGObject o) => IsCredentialData o toCredentialData :: IsCredentialData o => o -> CredentialData toCredentialData = CredentialData . coerce instance IsCredentialData CredentialData instance IsGObject CredentialData where typeGType _ = gTypeCredentialData {-# INLINE typeGType #-} noCredentialData :: Maybe CredentialData noCredentialData = Nothing {-# INLINE noCredentialData #-} foreign import javascript unsafe "window[\"CredentialData\"]" gTypeCredentialData :: GType -- | Functions for this inteface are in "GHCJS.DOM.Crypto". -- -- newtype Crypto = Crypto { unCrypto :: JSVal } instance Eq (Crypto) where (Crypto a) == (Crypto b) = js_eq a b instance PToJSVal Crypto where pToJSVal = unCrypto {-# INLINE pToJSVal #-} instance PFromJSVal Crypto where pFromJSVal = Crypto {-# INLINE pFromJSVal #-} instance ToJSVal Crypto where toJSVal = return . unCrypto {-# INLINE toJSVal #-} instance FromJSVal Crypto where fromJSVal = return . fmap Crypto . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject Crypto where typeGType _ = gTypeCrypto {-# INLINE typeGType #-} noCrypto :: Maybe Crypto noCrypto = Nothing {-# INLINE noCrypto #-} foreign import javascript unsafe "window[\"Crypto\"]" gTypeCrypto :: GType -- | Functions for this inteface are in "GHCJS.DOM.CryptoAlgorithmParameters". -- -- newtype CryptoAlgorithmParameters = CryptoAlgorithmParameters { unCryptoAlgorithmParameters :: JSVal } instance Eq (CryptoAlgorithmParameters) where (CryptoAlgorithmParameters a) == (CryptoAlgorithmParameters b) = js_eq a b instance PToJSVal CryptoAlgorithmParameters where pToJSVal = unCryptoAlgorithmParameters {-# INLINE pToJSVal #-} instance PFromJSVal CryptoAlgorithmParameters where pFromJSVal = CryptoAlgorithmParameters {-# INLINE pFromJSVal #-} instance ToJSVal CryptoAlgorithmParameters where toJSVal = return . unCryptoAlgorithmParameters {-# INLINE toJSVal #-} instance FromJSVal CryptoAlgorithmParameters where fromJSVal = return . fmap CryptoAlgorithmParameters . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsGObject o) => IsCryptoAlgorithmParameters o toCryptoAlgorithmParameters :: IsCryptoAlgorithmParameters o => o -> CryptoAlgorithmParameters toCryptoAlgorithmParameters = CryptoAlgorithmParameters . coerce instance IsCryptoAlgorithmParameters CryptoAlgorithmParameters instance IsGObject CryptoAlgorithmParameters where typeGType _ = gTypeCryptoAlgorithmParameters {-# INLINE typeGType #-} noCryptoAlgorithmParameters :: Maybe CryptoAlgorithmParameters noCryptoAlgorithmParameters = Nothing {-# INLINE noCryptoAlgorithmParameters #-} foreign import javascript unsafe "window[\"CryptoAlgorithmParameters\"]" gTypeCryptoAlgorithmParameters :: GType -- | Functions for this inteface are in "GHCJS.DOM.CryptoKey". -- -- newtype CryptoKey = CryptoKey { unCryptoKey :: JSVal } instance Eq (CryptoKey) where (CryptoKey a) == (CryptoKey b) = js_eq a b instance PToJSVal CryptoKey where pToJSVal = unCryptoKey {-# INLINE pToJSVal #-} instance PFromJSVal CryptoKey where pFromJSVal = CryptoKey {-# INLINE pFromJSVal #-} instance ToJSVal CryptoKey where toJSVal = return . unCryptoKey {-# INLINE toJSVal #-} instance FromJSVal CryptoKey where fromJSVal = return . fmap CryptoKey . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject CryptoKey where typeGType _ = gTypeCryptoKey {-# INLINE typeGType #-} noCryptoKey :: Maybe CryptoKey noCryptoKey = Nothing {-# INLINE noCryptoKey #-} foreign import javascript unsafe "window[\"CryptoKey\"]" gTypeCryptoKey :: GType -- | Functions for this inteface are in "GHCJS.DOM.CryptoKeyPair". -- -- newtype CryptoKeyPair = CryptoKeyPair { unCryptoKeyPair :: JSVal } instance Eq (CryptoKeyPair) where (CryptoKeyPair a) == (CryptoKeyPair b) = js_eq a b instance PToJSVal CryptoKeyPair where pToJSVal = unCryptoKeyPair {-# INLINE pToJSVal #-} instance PFromJSVal CryptoKeyPair where pFromJSVal = CryptoKeyPair {-# INLINE pFromJSVal #-} instance ToJSVal CryptoKeyPair where toJSVal = return . unCryptoKeyPair {-# INLINE toJSVal #-} instance FromJSVal CryptoKeyPair where fromJSVal = return . fmap CryptoKeyPair . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject CryptoKeyPair where typeGType _ = gTypeCryptoKeyPair {-# INLINE typeGType #-} noCryptoKeyPair :: Maybe CryptoKeyPair noCryptoKeyPair = Nothing {-# INLINE noCryptoKeyPair #-} foreign import javascript unsafe "window[\"CryptoKeyPair\"]" gTypeCryptoKeyPair :: GType -- | Functions for this inteface are in "GHCJS.DOM.CustomElementRegistry". -- -- newtype CustomElementRegistry = CustomElementRegistry { unCustomElementRegistry :: JSVal } instance Eq (CustomElementRegistry) where (CustomElementRegistry a) == (CustomElementRegistry b) = js_eq a b instance PToJSVal CustomElementRegistry where pToJSVal = unCustomElementRegistry {-# INLINE pToJSVal #-} instance PFromJSVal CustomElementRegistry where pFromJSVal = CustomElementRegistry {-# INLINE pFromJSVal #-} instance ToJSVal CustomElementRegistry where toJSVal = return . unCustomElementRegistry {-# INLINE toJSVal #-} instance FromJSVal CustomElementRegistry where fromJSVal = return . fmap CustomElementRegistry . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject CustomElementRegistry where typeGType _ = gTypeCustomElementRegistry {-# INLINE typeGType #-} noCustomElementRegistry :: Maybe CustomElementRegistry noCustomElementRegistry = Nothing {-# INLINE noCustomElementRegistry #-} foreign import javascript unsafe "window[\"CustomElementRegistry\"]" gTypeCustomElementRegistry :: GType -- | Functions for this inteface are in "GHCJS.DOM.CustomEvent". -- Base interface functions are in: -- -- * "GHCJS.DOM.Event" -- -- newtype CustomEvent = CustomEvent { unCustomEvent :: JSVal } instance Eq (CustomEvent) where (CustomEvent a) == (CustomEvent b) = js_eq a b instance PToJSVal CustomEvent where pToJSVal = unCustomEvent {-# INLINE pToJSVal #-} instance PFromJSVal CustomEvent where pFromJSVal = CustomEvent {-# INLINE pFromJSVal #-} instance ToJSVal CustomEvent where toJSVal = return . unCustomEvent {-# INLINE toJSVal #-} instance FromJSVal CustomEvent where fromJSVal = return . fmap CustomEvent . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEvent CustomEvent instance IsGObject CustomEvent where typeGType _ = gTypeCustomEvent {-# INLINE typeGType #-} noCustomEvent :: Maybe CustomEvent noCustomEvent = Nothing {-# INLINE noCustomEvent #-} foreign import javascript unsafe "window[\"CustomEvent\"]" gTypeCustomEvent :: GType -- | Functions for this inteface are in "GHCJS.DOM.CustomEventInit". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventInit" -- -- newtype CustomEventInit = CustomEventInit { unCustomEventInit :: JSVal } instance Eq (CustomEventInit) where (CustomEventInit a) == (CustomEventInit b) = js_eq a b instance PToJSVal CustomEventInit where pToJSVal = unCustomEventInit {-# INLINE pToJSVal #-} instance PFromJSVal CustomEventInit where pFromJSVal = CustomEventInit {-# INLINE pFromJSVal #-} instance ToJSVal CustomEventInit where toJSVal = return . unCustomEventInit {-# INLINE toJSVal #-} instance FromJSVal CustomEventInit where fromJSVal = return . fmap CustomEventInit . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventInit CustomEventInit instance IsGObject CustomEventInit where typeGType _ = gTypeCustomEventInit {-# INLINE typeGType #-} noCustomEventInit :: Maybe CustomEventInit noCustomEventInit = Nothing {-# INLINE noCustomEventInit #-} foreign import javascript unsafe "window[\"CustomEventInit\"]" gTypeCustomEventInit :: GType -- | Functions for this inteface are in "GHCJS.DOM.DOMError". -- -- newtype DOMError = DOMError { unDOMError :: JSVal } instance Eq (DOMError) where (DOMError a) == (DOMError b) = js_eq a b instance PToJSVal DOMError where pToJSVal = unDOMError {-# INLINE pToJSVal #-} instance PFromJSVal DOMError where pFromJSVal = DOMError {-# INLINE pFromJSVal #-} instance ToJSVal DOMError where toJSVal = return . unDOMError {-# INLINE toJSVal #-} instance FromJSVal DOMError where fromJSVal = return . fmap DOMError . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsGObject o) => IsDOMError o toDOMError :: IsDOMError o => o -> DOMError toDOMError = DOMError . coerce instance IsDOMError DOMError instance IsGObject DOMError where typeGType _ = gTypeDOMError {-# INLINE typeGType #-} noDOMError :: Maybe DOMError noDOMError = Nothing {-# INLINE noDOMError #-} foreign import javascript unsafe "window[\"DOMError\"]" gTypeDOMError :: GType -- | Functions for this inteface are in "GHCJS.DOM.DOMException". -- -- newtype DOMException = DOMException { unDOMException :: JSVal } instance Eq (DOMException) where (DOMException a) == (DOMException b) = js_eq a b instance PToJSVal DOMException where pToJSVal = unDOMException {-# INLINE pToJSVal #-} instance PFromJSVal DOMException where pFromJSVal = DOMException {-# INLINE pFromJSVal #-} instance ToJSVal DOMException where toJSVal = return . unDOMException {-# INLINE toJSVal #-} instance FromJSVal DOMException where fromJSVal = return . fmap DOMException . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject DOMException where typeGType _ = gTypeDOMException {-# INLINE typeGType #-} noDOMException :: Maybe DOMException noDOMException = Nothing {-# INLINE noDOMException #-} foreign import javascript unsafe "window[\"DOMException\"]" gTypeDOMException :: GType -- | Functions for this inteface are in "GHCJS.DOM.DOMImplementation". -- -- newtype DOMImplementation = DOMImplementation { unDOMImplementation :: JSVal } instance Eq (DOMImplementation) where (DOMImplementation a) == (DOMImplementation b) = js_eq a b instance PToJSVal DOMImplementation where pToJSVal = unDOMImplementation {-# INLINE pToJSVal #-} instance PFromJSVal DOMImplementation where pFromJSVal = DOMImplementation {-# INLINE pFromJSVal #-} instance ToJSVal DOMImplementation where toJSVal = return . unDOMImplementation {-# INLINE toJSVal #-} instance FromJSVal DOMImplementation where fromJSVal = return . fmap DOMImplementation . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject DOMImplementation where typeGType _ = gTypeDOMImplementation {-# INLINE typeGType #-} noDOMImplementation :: Maybe DOMImplementation noDOMImplementation = Nothing {-# INLINE noDOMImplementation #-} foreign import javascript unsafe "window[\"DOMImplementation\"]" gTypeDOMImplementation :: GType -- | Functions for this inteface are in "GHCJS.DOM.DOMNamedFlowCollection". -- -- newtype DOMNamedFlowCollection = DOMNamedFlowCollection { unDOMNamedFlowCollection :: JSVal } instance Eq (DOMNamedFlowCollection) where (DOMNamedFlowCollection a) == (DOMNamedFlowCollection b) = js_eq a b instance PToJSVal DOMNamedFlowCollection where pToJSVal = unDOMNamedFlowCollection {-# INLINE pToJSVal #-} instance PFromJSVal DOMNamedFlowCollection where pFromJSVal = DOMNamedFlowCollection {-# INLINE pFromJSVal #-} instance ToJSVal DOMNamedFlowCollection where toJSVal = return . unDOMNamedFlowCollection {-# INLINE toJSVal #-} instance FromJSVal DOMNamedFlowCollection where fromJSVal = return . fmap DOMNamedFlowCollection . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject DOMNamedFlowCollection where typeGType _ = gTypeDOMNamedFlowCollection {-# INLINE typeGType #-} noDOMNamedFlowCollection :: Maybe DOMNamedFlowCollection noDOMNamedFlowCollection = Nothing {-# INLINE noDOMNamedFlowCollection #-} foreign import javascript unsafe "window[\"WebKitNamedFlowCollection\"]" gTypeDOMNamedFlowCollection :: GType -- | Functions for this inteface are in "GHCJS.DOM.DOMParser". -- -- newtype DOMParser = DOMParser { unDOMParser :: JSVal } instance Eq (DOMParser) where (DOMParser a) == (DOMParser b) = js_eq a b instance PToJSVal DOMParser where pToJSVal = unDOMParser {-# INLINE pToJSVal #-} instance PFromJSVal DOMParser where pFromJSVal = DOMParser {-# INLINE pFromJSVal #-} instance ToJSVal DOMParser where toJSVal = return . unDOMParser {-# INLINE toJSVal #-} instance FromJSVal DOMParser where fromJSVal = return . fmap DOMParser . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject DOMParser where typeGType _ = gTypeDOMParser {-# INLINE typeGType #-} noDOMParser :: Maybe DOMParser noDOMParser = Nothing {-# INLINE noDOMParser #-} foreign import javascript unsafe "window[\"DOMParser\"]" gTypeDOMParser :: GType -- | Functions for this inteface are in "GHCJS.DOM.DOMPoint". -- Base interface functions are in: -- -- * "GHCJS.DOM.DOMPointReadOnly" -- -- newtype DOMPoint = DOMPoint { unDOMPoint :: JSVal } instance Eq (DOMPoint) where (DOMPoint a) == (DOMPoint b) = js_eq a b instance PToJSVal DOMPoint where pToJSVal = unDOMPoint {-# INLINE pToJSVal #-} instance PFromJSVal DOMPoint where pFromJSVal = DOMPoint {-# INLINE pFromJSVal #-} instance ToJSVal DOMPoint where toJSVal = return . unDOMPoint {-# INLINE toJSVal #-} instance FromJSVal DOMPoint where fromJSVal = return . fmap DOMPoint . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsDOMPointReadOnly DOMPoint instance IsGObject DOMPoint where typeGType _ = gTypeDOMPoint {-# INLINE typeGType #-} noDOMPoint :: Maybe DOMPoint noDOMPoint = Nothing {-# INLINE noDOMPoint #-} foreign import javascript unsafe "window[\"DOMPoint\"]" gTypeDOMPoint :: GType -- | Functions for this inteface are in "GHCJS.DOM.DOMPointInit". -- -- newtype DOMPointInit = DOMPointInit { unDOMPointInit :: JSVal } instance Eq (DOMPointInit) where (DOMPointInit a) == (DOMPointInit b) = js_eq a b instance PToJSVal DOMPointInit where pToJSVal = unDOMPointInit {-# INLINE pToJSVal #-} instance PFromJSVal DOMPointInit where pFromJSVal = DOMPointInit {-# INLINE pFromJSVal #-} instance ToJSVal DOMPointInit where toJSVal = return . unDOMPointInit {-# INLINE toJSVal #-} instance FromJSVal DOMPointInit where fromJSVal = return . fmap DOMPointInit . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject DOMPointInit where typeGType _ = gTypeDOMPointInit {-# INLINE typeGType #-} noDOMPointInit :: Maybe DOMPointInit noDOMPointInit = Nothing {-# INLINE noDOMPointInit #-} foreign import javascript unsafe "window[\"DOMPointInit\"]" gTypeDOMPointInit :: GType -- | Functions for this inteface are in "GHCJS.DOM.DOMPointReadOnly". -- -- newtype DOMPointReadOnly = DOMPointReadOnly { unDOMPointReadOnly :: JSVal } instance Eq (DOMPointReadOnly) where (DOMPointReadOnly a) == (DOMPointReadOnly b) = js_eq a b instance PToJSVal DOMPointReadOnly where pToJSVal = unDOMPointReadOnly {-# INLINE pToJSVal #-} instance PFromJSVal DOMPointReadOnly where pFromJSVal = DOMPointReadOnly {-# INLINE pFromJSVal #-} instance ToJSVal DOMPointReadOnly where toJSVal = return . unDOMPointReadOnly {-# INLINE toJSVal #-} instance FromJSVal DOMPointReadOnly where fromJSVal = return . fmap DOMPointReadOnly . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsGObject o) => IsDOMPointReadOnly o toDOMPointReadOnly :: IsDOMPointReadOnly o => o -> DOMPointReadOnly toDOMPointReadOnly = DOMPointReadOnly . coerce instance IsDOMPointReadOnly DOMPointReadOnly instance IsGObject DOMPointReadOnly where typeGType _ = gTypeDOMPointReadOnly {-# INLINE typeGType #-} noDOMPointReadOnly :: Maybe DOMPointReadOnly noDOMPointReadOnly = Nothing {-# INLINE noDOMPointReadOnly #-} foreign import javascript unsafe "window[\"DOMPointReadOnly\"]" gTypeDOMPointReadOnly :: GType -- | Functions for this inteface are in "GHCJS.DOM.DOMRect". -- Base interface functions are in: -- -- * "GHCJS.DOM.DOMRectReadOnly" -- -- newtype DOMRect = DOMRect { unDOMRect :: JSVal } instance Eq (DOMRect) where (DOMRect a) == (DOMRect b) = js_eq a b instance PToJSVal DOMRect where pToJSVal = unDOMRect {-# INLINE pToJSVal #-} instance PFromJSVal DOMRect where pFromJSVal = DOMRect {-# INLINE pFromJSVal #-} instance ToJSVal DOMRect where toJSVal = return . unDOMRect {-# INLINE toJSVal #-} instance FromJSVal DOMRect where fromJSVal = return . fmap DOMRect . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsDOMRectReadOnly DOMRect instance IsGObject DOMRect where typeGType _ = gTypeDOMRect {-# INLINE typeGType #-} noDOMRect :: Maybe DOMRect noDOMRect = Nothing {-# INLINE noDOMRect #-} foreign import javascript unsafe "window[\"DOMRect\"]" gTypeDOMRect :: GType -- | Functions for this inteface are in "GHCJS.DOM.DOMRectInit". -- -- newtype DOMRectInit = DOMRectInit { unDOMRectInit :: JSVal } instance Eq (DOMRectInit) where (DOMRectInit a) == (DOMRectInit b) = js_eq a b instance PToJSVal DOMRectInit where pToJSVal = unDOMRectInit {-# INLINE pToJSVal #-} instance PFromJSVal DOMRectInit where pFromJSVal = DOMRectInit {-# INLINE pFromJSVal #-} instance ToJSVal DOMRectInit where toJSVal = return . unDOMRectInit {-# INLINE toJSVal #-} instance FromJSVal DOMRectInit where fromJSVal = return . fmap DOMRectInit . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject DOMRectInit where typeGType _ = gTypeDOMRectInit {-# INLINE typeGType #-} noDOMRectInit :: Maybe DOMRectInit noDOMRectInit = Nothing {-# INLINE noDOMRectInit #-} foreign import javascript unsafe "window[\"DOMRectInit\"]" gTypeDOMRectInit :: GType -- | Functions for this inteface are in "GHCJS.DOM.DOMRectReadOnly". -- -- newtype DOMRectReadOnly = DOMRectReadOnly { unDOMRectReadOnly :: JSVal } instance Eq (DOMRectReadOnly) where (DOMRectReadOnly a) == (DOMRectReadOnly b) = js_eq a b instance PToJSVal DOMRectReadOnly where pToJSVal = unDOMRectReadOnly {-# INLINE pToJSVal #-} instance PFromJSVal DOMRectReadOnly where pFromJSVal = DOMRectReadOnly {-# INLINE pFromJSVal #-} instance ToJSVal DOMRectReadOnly where toJSVal = return . unDOMRectReadOnly {-# INLINE toJSVal #-} instance FromJSVal DOMRectReadOnly where fromJSVal = return . fmap DOMRectReadOnly . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsGObject o) => IsDOMRectReadOnly o toDOMRectReadOnly :: IsDOMRectReadOnly o => o -> DOMRectReadOnly toDOMRectReadOnly = DOMRectReadOnly . coerce instance IsDOMRectReadOnly DOMRectReadOnly instance IsGObject DOMRectReadOnly where typeGType _ = gTypeDOMRectReadOnly {-# INLINE typeGType #-} noDOMRectReadOnly :: Maybe DOMRectReadOnly noDOMRectReadOnly = Nothing {-# INLINE noDOMRectReadOnly #-} foreign import javascript unsafe "window[\"DOMRectReadOnly\"]" gTypeDOMRectReadOnly :: GType -- | Functions for this inteface are in "GHCJS.DOM.DOMStringList". -- -- newtype DOMStringList = DOMStringList { unDOMStringList :: JSVal } instance Eq (DOMStringList) where (DOMStringList a) == (DOMStringList b) = js_eq a b instance PToJSVal DOMStringList where pToJSVal = unDOMStringList {-# INLINE pToJSVal #-} instance PFromJSVal DOMStringList where pFromJSVal = DOMStringList {-# INLINE pFromJSVal #-} instance ToJSVal DOMStringList where toJSVal = return . unDOMStringList {-# INLINE toJSVal #-} instance FromJSVal DOMStringList where fromJSVal = return . fmap DOMStringList . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject DOMStringList where typeGType _ = gTypeDOMStringList {-# INLINE typeGType #-} noDOMStringList :: Maybe DOMStringList noDOMStringList = Nothing {-# INLINE noDOMStringList #-} foreign import javascript unsafe "window[\"DOMStringList\"]" gTypeDOMStringList :: GType -- | Functions for this inteface are in "GHCJS.DOM.DOMStringMap". -- -- newtype DOMStringMap = DOMStringMap { unDOMStringMap :: JSVal } instance Eq (DOMStringMap) where (DOMStringMap a) == (DOMStringMap b) = js_eq a b instance PToJSVal DOMStringMap where pToJSVal = unDOMStringMap {-# INLINE pToJSVal #-} instance PFromJSVal DOMStringMap where pFromJSVal = DOMStringMap {-# INLINE pFromJSVal #-} instance ToJSVal DOMStringMap where toJSVal = return . unDOMStringMap {-# INLINE toJSVal #-} instance FromJSVal DOMStringMap where fromJSVal = return . fmap DOMStringMap . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject DOMStringMap where typeGType _ = gTypeDOMStringMap {-# INLINE typeGType #-} noDOMStringMap :: Maybe DOMStringMap noDOMStringMap = Nothing {-# INLINE noDOMStringMap #-} foreign import javascript unsafe "window[\"DOMStringMap\"]" gTypeDOMStringMap :: GType -- | Functions for this inteface are in "GHCJS.DOM.DOMTokenList". -- -- newtype DOMTokenList = DOMTokenList { unDOMTokenList :: JSVal } instance Eq (DOMTokenList) where (DOMTokenList a) == (DOMTokenList b) = js_eq a b instance PToJSVal DOMTokenList where pToJSVal = unDOMTokenList {-# INLINE pToJSVal #-} instance PFromJSVal DOMTokenList where pFromJSVal = DOMTokenList {-# INLINE pFromJSVal #-} instance ToJSVal DOMTokenList where toJSVal = return . unDOMTokenList {-# INLINE toJSVal #-} instance FromJSVal DOMTokenList where fromJSVal = return . fmap DOMTokenList . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject DOMTokenList where typeGType _ = gTypeDOMTokenList {-# INLINE typeGType #-} noDOMTokenList :: Maybe DOMTokenList noDOMTokenList = Nothing {-# INLINE noDOMTokenList #-} foreign import javascript unsafe "window[\"DOMTokenList\"]" gTypeDOMTokenList :: GType -- | Functions for this inteface are in "GHCJS.DOM.DataCue". -- Base interface functions are in: -- -- * "GHCJS.DOM.TextTrackCue" -- * "GHCJS.DOM.EventTarget" -- -- newtype DataCue = DataCue { unDataCue :: JSVal } instance Eq (DataCue) where (DataCue a) == (DataCue b) = js_eq a b instance PToJSVal DataCue where pToJSVal = unDataCue {-# INLINE pToJSVal #-} instance PFromJSVal DataCue where pFromJSVal = DataCue {-# INLINE pFromJSVal #-} instance ToJSVal DataCue where toJSVal = return . unDataCue {-# INLINE toJSVal #-} instance FromJSVal DataCue where fromJSVal = return . fmap DataCue . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsTextTrackCue DataCue instance IsEventTarget DataCue instance IsGObject DataCue where typeGType _ = gTypeDataCue {-# INLINE typeGType #-} noDataCue :: Maybe DataCue noDataCue = Nothing {-# INLINE noDataCue #-} foreign import javascript unsafe "window[\"WebKitDataCue\"]" gTypeDataCue :: GType -- | Functions for this inteface are in "GHCJS.DOM.DataTransfer". -- -- newtype DataTransfer = DataTransfer { unDataTransfer :: JSVal } instance Eq (DataTransfer) where (DataTransfer a) == (DataTransfer b) = js_eq a b instance PToJSVal DataTransfer where pToJSVal = unDataTransfer {-# INLINE pToJSVal #-} instance PFromJSVal DataTransfer where pFromJSVal = DataTransfer {-# INLINE pFromJSVal #-} instance ToJSVal DataTransfer where toJSVal = return . unDataTransfer {-# INLINE toJSVal #-} instance FromJSVal DataTransfer where fromJSVal = return . fmap DataTransfer . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject DataTransfer where typeGType _ = gTypeDataTransfer {-# INLINE typeGType #-} noDataTransfer :: Maybe DataTransfer noDataTransfer = Nothing {-# INLINE noDataTransfer #-} foreign import javascript unsafe "window[\"DataTransfer\"]" gTypeDataTransfer :: GType -- | Functions for this inteface are in "GHCJS.DOM.DataTransferItem". -- -- newtype DataTransferItem = DataTransferItem { unDataTransferItem :: JSVal } instance Eq (DataTransferItem) where (DataTransferItem a) == (DataTransferItem b) = js_eq a b instance PToJSVal DataTransferItem where pToJSVal = unDataTransferItem {-# INLINE pToJSVal #-} instance PFromJSVal DataTransferItem where pFromJSVal = DataTransferItem {-# INLINE pFromJSVal #-} instance ToJSVal DataTransferItem where toJSVal = return . unDataTransferItem {-# INLINE toJSVal #-} instance FromJSVal DataTransferItem where fromJSVal = return . fmap DataTransferItem . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject DataTransferItem where typeGType _ = gTypeDataTransferItem {-# INLINE typeGType #-} noDataTransferItem :: Maybe DataTransferItem noDataTransferItem = Nothing {-# INLINE noDataTransferItem #-} foreign import javascript unsafe "window[\"DataTransferItem\"]" gTypeDataTransferItem :: GType -- | Functions for this inteface are in "GHCJS.DOM.DataTransferItemList". -- -- newtype DataTransferItemList = DataTransferItemList { unDataTransferItemList :: JSVal } instance Eq (DataTransferItemList) where (DataTransferItemList a) == (DataTransferItemList b) = js_eq a b instance PToJSVal DataTransferItemList where pToJSVal = unDataTransferItemList {-# INLINE pToJSVal #-} instance PFromJSVal DataTransferItemList where pFromJSVal = DataTransferItemList {-# INLINE pFromJSVal #-} instance ToJSVal DataTransferItemList where toJSVal = return . unDataTransferItemList {-# INLINE toJSVal #-} instance FromJSVal DataTransferItemList where fromJSVal = return . fmap DataTransferItemList . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject DataTransferItemList where typeGType _ = gTypeDataTransferItemList {-# INLINE typeGType #-} noDataTransferItemList :: Maybe DataTransferItemList noDataTransferItemList = Nothing {-# INLINE noDataTransferItemList #-} foreign import javascript unsafe "window[\"DataTransferItemList\"]" gTypeDataTransferItemList :: GType -- | Functions for this inteface are in "GHCJS.DOM.Database". -- -- newtype Database = Database { unDatabase :: JSVal } instance Eq (Database) where (Database a) == (Database b) = js_eq a b instance PToJSVal Database where pToJSVal = unDatabase {-# INLINE pToJSVal #-} instance PFromJSVal Database where pFromJSVal = Database {-# INLINE pFromJSVal #-} instance ToJSVal Database where toJSVal = return . unDatabase {-# INLINE toJSVal #-} instance FromJSVal Database where fromJSVal = return . fmap Database . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject Database where typeGType _ = gTypeDatabase {-# INLINE typeGType #-} noDatabase :: Maybe Database noDatabase = Nothing {-# INLINE noDatabase #-} foreign import javascript unsafe "window[\"Database\"]" gTypeDatabase :: GType -- | Functions for this inteface are in "GHCJS.DOM.DedicatedWorkerGlobalScope". -- Base interface functions are in: -- -- * "GHCJS.DOM.WorkerGlobalScope" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.WindowOrWorkerGlobalScope" -- * "GHCJS.DOM.GlobalPerformance" -- * "GHCJS.DOM.GlobalCrypto" -- -- newtype DedicatedWorkerGlobalScope = DedicatedWorkerGlobalScope { unDedicatedWorkerGlobalScope :: JSVal } instance Eq (DedicatedWorkerGlobalScope) where (DedicatedWorkerGlobalScope a) == (DedicatedWorkerGlobalScope b) = js_eq a b instance PToJSVal DedicatedWorkerGlobalScope where pToJSVal = unDedicatedWorkerGlobalScope {-# INLINE pToJSVal #-} instance PFromJSVal DedicatedWorkerGlobalScope where pFromJSVal = DedicatedWorkerGlobalScope {-# INLINE pFromJSVal #-} instance ToJSVal DedicatedWorkerGlobalScope where toJSVal = return . unDedicatedWorkerGlobalScope {-# INLINE toJSVal #-} instance FromJSVal DedicatedWorkerGlobalScope where fromJSVal = return . fmap DedicatedWorkerGlobalScope . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsWorkerGlobalScope DedicatedWorkerGlobalScope instance IsEventTarget DedicatedWorkerGlobalScope instance IsWindowOrWorkerGlobalScope DedicatedWorkerGlobalScope instance IsGlobalPerformance DedicatedWorkerGlobalScope instance IsGlobalCrypto DedicatedWorkerGlobalScope instance IsGObject DedicatedWorkerGlobalScope where typeGType _ = gTypeDedicatedWorkerGlobalScope {-# INLINE typeGType #-} noDedicatedWorkerGlobalScope :: Maybe DedicatedWorkerGlobalScope noDedicatedWorkerGlobalScope = Nothing {-# INLINE noDedicatedWorkerGlobalScope #-} foreign import javascript unsafe "window[\"DedicatedWorkerGlobalScope\"]" gTypeDedicatedWorkerGlobalScope :: GType -- | Functions for this inteface are in "GHCJS.DOM.DelayNode". -- Base interface functions are in: -- -- * "GHCJS.DOM.AudioNode" -- * "GHCJS.DOM.EventTarget" -- -- newtype DelayNode = DelayNode { unDelayNode :: JSVal } instance Eq (DelayNode) where (DelayNode a) == (DelayNode b) = js_eq a b instance PToJSVal DelayNode where pToJSVal = unDelayNode {-# INLINE pToJSVal #-} instance PFromJSVal DelayNode where pFromJSVal = DelayNode {-# INLINE pFromJSVal #-} instance ToJSVal DelayNode where toJSVal = return . unDelayNode {-# INLINE toJSVal #-} instance FromJSVal DelayNode where fromJSVal = return . fmap DelayNode . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsAudioNode DelayNode instance IsEventTarget DelayNode instance IsGObject DelayNode where typeGType _ = gTypeDelayNode {-# INLINE typeGType #-} noDelayNode :: Maybe DelayNode noDelayNode = Nothing {-# INLINE noDelayNode #-} foreign import javascript unsafe "window[\"DelayNode\"]" gTypeDelayNode :: GType -- | Functions for this inteface are in "GHCJS.DOM.DeviceMotionEvent". -- Base interface functions are in: -- -- * "GHCJS.DOM.Event" -- -- newtype DeviceMotionEvent = DeviceMotionEvent { unDeviceMotionEvent :: JSVal } instance Eq (DeviceMotionEvent) where (DeviceMotionEvent a) == (DeviceMotionEvent b) = js_eq a b instance PToJSVal DeviceMotionEvent where pToJSVal = unDeviceMotionEvent {-# INLINE pToJSVal #-} instance PFromJSVal DeviceMotionEvent where pFromJSVal = DeviceMotionEvent {-# INLINE pFromJSVal #-} instance ToJSVal DeviceMotionEvent where toJSVal = return . unDeviceMotionEvent {-# INLINE toJSVal #-} instance FromJSVal DeviceMotionEvent where fromJSVal = return . fmap DeviceMotionEvent . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEvent DeviceMotionEvent instance IsGObject DeviceMotionEvent where typeGType _ = gTypeDeviceMotionEvent {-# INLINE typeGType #-} noDeviceMotionEvent :: Maybe DeviceMotionEvent noDeviceMotionEvent = Nothing {-# INLINE noDeviceMotionEvent #-} foreign import javascript unsafe "window[\"DeviceMotionEvent\"]" gTypeDeviceMotionEvent :: GType -- | Functions for this inteface are in "GHCJS.DOM.DeviceOrientationEvent". -- Base interface functions are in: -- -- * "GHCJS.DOM.Event" -- -- newtype DeviceOrientationEvent = DeviceOrientationEvent { unDeviceOrientationEvent :: JSVal } instance Eq (DeviceOrientationEvent) where (DeviceOrientationEvent a) == (DeviceOrientationEvent b) = js_eq a b instance PToJSVal DeviceOrientationEvent where pToJSVal = unDeviceOrientationEvent {-# INLINE pToJSVal #-} instance PFromJSVal DeviceOrientationEvent where pFromJSVal = DeviceOrientationEvent {-# INLINE pFromJSVal #-} instance ToJSVal DeviceOrientationEvent where toJSVal = return . unDeviceOrientationEvent {-# INLINE toJSVal #-} instance FromJSVal DeviceOrientationEvent where fromJSVal = return . fmap DeviceOrientationEvent . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEvent DeviceOrientationEvent instance IsGObject DeviceOrientationEvent where typeGType _ = gTypeDeviceOrientationEvent {-# INLINE typeGType #-} noDeviceOrientationEvent :: Maybe DeviceOrientationEvent noDeviceOrientationEvent = Nothing {-# INLINE noDeviceOrientationEvent #-} foreign import javascript unsafe "window[\"DeviceOrientationEvent\"]" gTypeDeviceOrientationEvent :: GType -- | Functions for this inteface are in "GHCJS.DOM.DeviceProximityEvent". -- Base interface functions are in: -- -- * "GHCJS.DOM.Event" -- -- newtype DeviceProximityEvent = DeviceProximityEvent { unDeviceProximityEvent :: JSVal } instance Eq (DeviceProximityEvent) where (DeviceProximityEvent a) == (DeviceProximityEvent b) = js_eq a b instance PToJSVal DeviceProximityEvent where pToJSVal = unDeviceProximityEvent {-# INLINE pToJSVal #-} instance PFromJSVal DeviceProximityEvent where pFromJSVal = DeviceProximityEvent {-# INLINE pFromJSVal #-} instance ToJSVal DeviceProximityEvent where toJSVal = return . unDeviceProximityEvent {-# INLINE toJSVal #-} instance FromJSVal DeviceProximityEvent where fromJSVal = return . fmap DeviceProximityEvent . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEvent DeviceProximityEvent instance IsGObject DeviceProximityEvent where typeGType _ = gTypeDeviceProximityEvent {-# INLINE typeGType #-} noDeviceProximityEvent :: Maybe DeviceProximityEvent noDeviceProximityEvent = Nothing {-# INLINE noDeviceProximityEvent #-} foreign import javascript unsafe "window[\"DeviceProximityEvent\"]" gTypeDeviceProximityEvent :: GType -- | Functions for this inteface are in "GHCJS.DOM.DeviceProximityEventInit". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventInit" -- -- newtype DeviceProximityEventInit = DeviceProximityEventInit { unDeviceProximityEventInit :: JSVal } instance Eq (DeviceProximityEventInit) where (DeviceProximityEventInit a) == (DeviceProximityEventInit b) = js_eq a b instance PToJSVal DeviceProximityEventInit where pToJSVal = unDeviceProximityEventInit {-# INLINE pToJSVal #-} instance PFromJSVal DeviceProximityEventInit where pFromJSVal = DeviceProximityEventInit {-# INLINE pFromJSVal #-} instance ToJSVal DeviceProximityEventInit where toJSVal = return . unDeviceProximityEventInit {-# INLINE toJSVal #-} instance FromJSVal DeviceProximityEventInit where fromJSVal = return . fmap DeviceProximityEventInit . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventInit DeviceProximityEventInit instance IsGObject DeviceProximityEventInit where typeGType _ = gTypeDeviceProximityEventInit {-# INLINE typeGType #-} noDeviceProximityEventInit :: Maybe DeviceProximityEventInit noDeviceProximityEventInit = Nothing {-# INLINE noDeviceProximityEventInit #-} foreign import javascript unsafe "window[\"DeviceProximityEventInit\"]" gTypeDeviceProximityEventInit :: GType -- | Functions for this inteface are in "GHCJS.DOM.Document". -- Base interface functions are in: -- -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.DocumentOrShadowRoot" -- * "GHCJS.DOM.NonElementParentNode" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- -- newtype Document = Document { unDocument :: JSVal } instance Eq (Document) where (Document a) == (Document b) = js_eq a b instance PToJSVal Document where pToJSVal = unDocument {-# INLINE pToJSVal #-} instance PFromJSVal Document where pFromJSVal = Document {-# INLINE pFromJSVal #-} instance ToJSVal Document where toJSVal = return . unDocument {-# INLINE toJSVal #-} instance FromJSVal Document where fromJSVal = return . fmap Document . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsNode o, IsEventTarget o, IsGlobalEventHandlers o, IsDocumentOrShadowRoot o, IsNonElementParentNode o, IsParentNode o, IsDocumentAndElementEventHandlers o, IsGObject o) => IsDocument o toDocument :: IsDocument o => o -> Document toDocument = Document . coerce instance IsDocument Document instance IsNode Document instance IsEventTarget Document instance IsGlobalEventHandlers Document instance IsDocumentOrShadowRoot Document instance IsNonElementParentNode Document instance IsParentNode Document instance IsDocumentAndElementEventHandlers Document instance IsGObject Document where typeGType _ = gTypeDocument {-# INLINE typeGType #-} noDocument :: Maybe Document noDocument = Nothing {-# INLINE noDocument #-} foreign import javascript unsafe "window[\"Document\"]" gTypeDocument :: GType -- | Functions for this inteface are in "GHCJS.DOM.DocumentAndElementEventHandlers". -- -- newtype DocumentAndElementEventHandlers = DocumentAndElementEventHandlers { unDocumentAndElementEventHandlers :: JSVal } instance Eq (DocumentAndElementEventHandlers) where (DocumentAndElementEventHandlers a) == (DocumentAndElementEventHandlers b) = js_eq a b instance PToJSVal DocumentAndElementEventHandlers where pToJSVal = unDocumentAndElementEventHandlers {-# INLINE pToJSVal #-} instance PFromJSVal DocumentAndElementEventHandlers where pFromJSVal = DocumentAndElementEventHandlers {-# INLINE pFromJSVal #-} instance ToJSVal DocumentAndElementEventHandlers where toJSVal = return . unDocumentAndElementEventHandlers {-# INLINE toJSVal #-} instance FromJSVal DocumentAndElementEventHandlers where fromJSVal = return . fmap DocumentAndElementEventHandlers . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsGObject o) => IsDocumentAndElementEventHandlers o toDocumentAndElementEventHandlers :: IsDocumentAndElementEventHandlers o => o -> DocumentAndElementEventHandlers toDocumentAndElementEventHandlers = DocumentAndElementEventHandlers . coerce instance IsDocumentAndElementEventHandlers DocumentAndElementEventHandlers instance IsGObject DocumentAndElementEventHandlers where typeGType _ = gTypeDocumentAndElementEventHandlers {-# INLINE typeGType #-} noDocumentAndElementEventHandlers :: Maybe DocumentAndElementEventHandlers noDocumentAndElementEventHandlers = Nothing {-# INLINE noDocumentAndElementEventHandlers #-} foreign import javascript unsafe "window[\"DocumentAndElementEventHandlers\"]" gTypeDocumentAndElementEventHandlers :: GType -- | Functions for this inteface are in "GHCJS.DOM.DocumentFragment". -- Base interface functions are in: -- -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.NonElementParentNode" -- * "GHCJS.DOM.ParentNode" -- -- newtype DocumentFragment = DocumentFragment { unDocumentFragment :: JSVal } instance Eq (DocumentFragment) where (DocumentFragment a) == (DocumentFragment b) = js_eq a b instance PToJSVal DocumentFragment where pToJSVal = unDocumentFragment {-# INLINE pToJSVal #-} instance PFromJSVal DocumentFragment where pFromJSVal = DocumentFragment {-# INLINE pFromJSVal #-} instance ToJSVal DocumentFragment where toJSVal = return . unDocumentFragment {-# INLINE toJSVal #-} instance FromJSVal DocumentFragment where fromJSVal = return . fmap DocumentFragment . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsNode o, IsEventTarget o, IsNonElementParentNode o, IsParentNode o, IsGObject o) => IsDocumentFragment o toDocumentFragment :: IsDocumentFragment o => o -> DocumentFragment toDocumentFragment = DocumentFragment . coerce instance IsDocumentFragment DocumentFragment instance IsNode DocumentFragment instance IsEventTarget DocumentFragment instance IsNonElementParentNode DocumentFragment instance IsParentNode DocumentFragment instance IsGObject DocumentFragment where typeGType _ = gTypeDocumentFragment {-# INLINE typeGType #-} noDocumentFragment :: Maybe DocumentFragment noDocumentFragment = Nothing {-# INLINE noDocumentFragment #-} foreign import javascript unsafe "window[\"DocumentFragment\"]" gTypeDocumentFragment :: GType -- | Functions for this inteface are in "GHCJS.DOM.DocumentOrShadowRoot". -- -- newtype DocumentOrShadowRoot = DocumentOrShadowRoot { unDocumentOrShadowRoot :: JSVal } instance Eq (DocumentOrShadowRoot) where (DocumentOrShadowRoot a) == (DocumentOrShadowRoot b) = js_eq a b instance PToJSVal DocumentOrShadowRoot where pToJSVal = unDocumentOrShadowRoot {-# INLINE pToJSVal #-} instance PFromJSVal DocumentOrShadowRoot where pFromJSVal = DocumentOrShadowRoot {-# INLINE pFromJSVal #-} instance ToJSVal DocumentOrShadowRoot where toJSVal = return . unDocumentOrShadowRoot {-# INLINE toJSVal #-} instance FromJSVal DocumentOrShadowRoot where fromJSVal = return . fmap DocumentOrShadowRoot . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsGObject o) => IsDocumentOrShadowRoot o toDocumentOrShadowRoot :: IsDocumentOrShadowRoot o => o -> DocumentOrShadowRoot toDocumentOrShadowRoot = DocumentOrShadowRoot . coerce instance IsDocumentOrShadowRoot DocumentOrShadowRoot instance IsGObject DocumentOrShadowRoot where typeGType _ = gTypeDocumentOrShadowRoot {-# INLINE typeGType #-} noDocumentOrShadowRoot :: Maybe DocumentOrShadowRoot noDocumentOrShadowRoot = Nothing {-# INLINE noDocumentOrShadowRoot #-} foreign import javascript unsafe "window[\"DocumentOrShadowRoot\"]" gTypeDocumentOrShadowRoot :: GType -- | Functions for this inteface are in "GHCJS.DOM.DocumentTimeline". -- Base interface functions are in: -- -- * "GHCJS.DOM.AnimationTimeline" -- -- newtype DocumentTimeline = DocumentTimeline { unDocumentTimeline :: JSVal } instance Eq (DocumentTimeline) where (DocumentTimeline a) == (DocumentTimeline b) = js_eq a b instance PToJSVal DocumentTimeline where pToJSVal = unDocumentTimeline {-# INLINE pToJSVal #-} instance PFromJSVal DocumentTimeline where pFromJSVal = DocumentTimeline {-# INLINE pFromJSVal #-} instance ToJSVal DocumentTimeline where toJSVal = return . unDocumentTimeline {-# INLINE toJSVal #-} instance FromJSVal DocumentTimeline where fromJSVal = return . fmap DocumentTimeline . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsAnimationTimeline DocumentTimeline instance IsGObject DocumentTimeline where typeGType _ = gTypeDocumentTimeline {-# INLINE typeGType #-} noDocumentTimeline :: Maybe DocumentTimeline noDocumentTimeline = Nothing {-# INLINE noDocumentTimeline #-} foreign import javascript unsafe "window[\"DocumentTimeline\"]" gTypeDocumentTimeline :: GType -- | Functions for this inteface are in "GHCJS.DOM.DocumentType". -- Base interface functions are in: -- -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.ChildNode" -- -- newtype DocumentType = DocumentType { unDocumentType :: JSVal } instance Eq (DocumentType) where (DocumentType a) == (DocumentType b) = js_eq a b instance PToJSVal DocumentType where pToJSVal = unDocumentType {-# INLINE pToJSVal #-} instance PFromJSVal DocumentType where pFromJSVal = DocumentType {-# INLINE pFromJSVal #-} instance ToJSVal DocumentType where toJSVal = return . unDocumentType {-# INLINE toJSVal #-} instance FromJSVal DocumentType where fromJSVal = return . fmap DocumentType . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsNode DocumentType instance IsEventTarget DocumentType instance IsChildNode DocumentType instance IsGObject DocumentType where typeGType _ = gTypeDocumentType {-# INLINE typeGType #-} noDocumentType :: Maybe DocumentType noDocumentType = Nothing {-# INLINE noDocumentType #-} foreign import javascript unsafe "window[\"DocumentType\"]" gTypeDocumentType :: GType -- | Functions for this inteface are in "GHCJS.DOM.DoubleRange". -- -- newtype DoubleRange = DoubleRange { unDoubleRange :: JSVal } instance Eq (DoubleRange) where (DoubleRange a) == (DoubleRange b) = js_eq a b instance PToJSVal DoubleRange where pToJSVal = unDoubleRange {-# INLINE pToJSVal #-} instance PFromJSVal DoubleRange where pFromJSVal = DoubleRange {-# INLINE pFromJSVal #-} instance ToJSVal DoubleRange where toJSVal = return . unDoubleRange {-# INLINE toJSVal #-} instance FromJSVal DoubleRange where fromJSVal = return . fmap DoubleRange . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsGObject o) => IsDoubleRange o toDoubleRange :: IsDoubleRange o => o -> DoubleRange toDoubleRange = DoubleRange . coerce instance IsDoubleRange DoubleRange instance IsGObject DoubleRange where typeGType _ = gTypeDoubleRange {-# INLINE typeGType #-} noDoubleRange :: Maybe DoubleRange noDoubleRange = Nothing {-# INLINE noDoubleRange #-} foreign import javascript unsafe "window[\"DoubleRange\"]" gTypeDoubleRange :: GType -- | Functions for this inteface are in "GHCJS.DOM.DynamicsCompressorNode". -- Base interface functions are in: -- -- * "GHCJS.DOM.AudioNode" -- * "GHCJS.DOM.EventTarget" -- -- newtype DynamicsCompressorNode = DynamicsCompressorNode { unDynamicsCompressorNode :: JSVal } instance Eq (DynamicsCompressorNode) where (DynamicsCompressorNode a) == (DynamicsCompressorNode b) = js_eq a b instance PToJSVal DynamicsCompressorNode where pToJSVal = unDynamicsCompressorNode {-# INLINE pToJSVal #-} instance PFromJSVal DynamicsCompressorNode where pFromJSVal = DynamicsCompressorNode {-# INLINE pFromJSVal #-} instance ToJSVal DynamicsCompressorNode where toJSVal = return . unDynamicsCompressorNode {-# INLINE toJSVal #-} instance FromJSVal DynamicsCompressorNode where fromJSVal = return . fmap DynamicsCompressorNode . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsAudioNode DynamicsCompressorNode instance IsEventTarget DynamicsCompressorNode instance IsGObject DynamicsCompressorNode where typeGType _ = gTypeDynamicsCompressorNode {-# INLINE typeGType #-} noDynamicsCompressorNode :: Maybe DynamicsCompressorNode noDynamicsCompressorNode = Nothing {-# INLINE noDynamicsCompressorNode #-} foreign import javascript unsafe "window[\"DynamicsCompressorNode\"]" gTypeDynamicsCompressorNode :: GType -- | Functions for this inteface are in "GHCJS.DOM.EXTBlendMinMax". -- -- newtype EXTBlendMinMax = EXTBlendMinMax { unEXTBlendMinMax :: JSVal } instance Eq (EXTBlendMinMax) where (EXTBlendMinMax a) == (EXTBlendMinMax b) = js_eq a b instance PToJSVal EXTBlendMinMax where pToJSVal = unEXTBlendMinMax {-# INLINE pToJSVal #-} instance PFromJSVal EXTBlendMinMax where pFromJSVal = EXTBlendMinMax {-# INLINE pFromJSVal #-} instance ToJSVal EXTBlendMinMax where toJSVal = return . unEXTBlendMinMax {-# INLINE toJSVal #-} instance FromJSVal EXTBlendMinMax where fromJSVal = return . fmap EXTBlendMinMax . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject EXTBlendMinMax where typeGType _ = gTypeEXTBlendMinMax {-# INLINE typeGType #-} noEXTBlendMinMax :: Maybe EXTBlendMinMax noEXTBlendMinMax = Nothing {-# INLINE noEXTBlendMinMax #-} foreign import javascript unsafe "window[\"EXTBlendMinMax\"]" gTypeEXTBlendMinMax :: GType -- | Functions for this inteface are in "GHCJS.DOM.EXTFragDepth". -- -- newtype EXTFragDepth = EXTFragDepth { unEXTFragDepth :: JSVal } instance Eq (EXTFragDepth) where (EXTFragDepth a) == (EXTFragDepth b) = js_eq a b instance PToJSVal EXTFragDepth where pToJSVal = unEXTFragDepth {-# INLINE pToJSVal #-} instance PFromJSVal EXTFragDepth where pFromJSVal = EXTFragDepth {-# INLINE pFromJSVal #-} instance ToJSVal EXTFragDepth where toJSVal = return . unEXTFragDepth {-# INLINE toJSVal #-} instance FromJSVal EXTFragDepth where fromJSVal = return . fmap EXTFragDepth . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject EXTFragDepth where typeGType _ = gTypeEXTFragDepth {-# INLINE typeGType #-} noEXTFragDepth :: Maybe EXTFragDepth noEXTFragDepth = Nothing {-# INLINE noEXTFragDepth #-} foreign import javascript unsafe "window[\"EXTFragDepth\"]" gTypeEXTFragDepth :: GType -- | Functions for this inteface are in "GHCJS.DOM.EXTShaderTextureLOD". -- -- newtype EXTShaderTextureLOD = EXTShaderTextureLOD { unEXTShaderTextureLOD :: JSVal } instance Eq (EXTShaderTextureLOD) where (EXTShaderTextureLOD a) == (EXTShaderTextureLOD b) = js_eq a b instance PToJSVal EXTShaderTextureLOD where pToJSVal = unEXTShaderTextureLOD {-# INLINE pToJSVal #-} instance PFromJSVal EXTShaderTextureLOD where pFromJSVal = EXTShaderTextureLOD {-# INLINE pFromJSVal #-} instance ToJSVal EXTShaderTextureLOD where toJSVal = return . unEXTShaderTextureLOD {-# INLINE toJSVal #-} instance FromJSVal EXTShaderTextureLOD where fromJSVal = return . fmap EXTShaderTextureLOD . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject EXTShaderTextureLOD where typeGType _ = gTypeEXTShaderTextureLOD {-# INLINE typeGType #-} noEXTShaderTextureLOD :: Maybe EXTShaderTextureLOD noEXTShaderTextureLOD = Nothing {-# INLINE noEXTShaderTextureLOD #-} foreign import javascript unsafe "window[\"EXTShaderTextureLOD\"]" gTypeEXTShaderTextureLOD :: GType -- | Functions for this inteface are in "GHCJS.DOM.EXTTextureFilterAnisotropic". -- -- newtype EXTTextureFilterAnisotropic = EXTTextureFilterAnisotropic { unEXTTextureFilterAnisotropic :: JSVal } instance Eq (EXTTextureFilterAnisotropic) where (EXTTextureFilterAnisotropic a) == (EXTTextureFilterAnisotropic b) = js_eq a b instance PToJSVal EXTTextureFilterAnisotropic where pToJSVal = unEXTTextureFilterAnisotropic {-# INLINE pToJSVal #-} instance PFromJSVal EXTTextureFilterAnisotropic where pFromJSVal = EXTTextureFilterAnisotropic {-# INLINE pFromJSVal #-} instance ToJSVal EXTTextureFilterAnisotropic where toJSVal = return . unEXTTextureFilterAnisotropic {-# INLINE toJSVal #-} instance FromJSVal EXTTextureFilterAnisotropic where fromJSVal = return . fmap EXTTextureFilterAnisotropic . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject EXTTextureFilterAnisotropic where typeGType _ = gTypeEXTTextureFilterAnisotropic {-# INLINE typeGType #-} noEXTTextureFilterAnisotropic :: Maybe EXTTextureFilterAnisotropic noEXTTextureFilterAnisotropic = Nothing {-# INLINE noEXTTextureFilterAnisotropic #-} foreign import javascript unsafe "window[\"EXTTextureFilterAnisotropic\"]" gTypeEXTTextureFilterAnisotropic :: GType -- | Functions for this inteface are in "GHCJS.DOM.EXTsRGB". -- -- newtype EXTsRGB = EXTsRGB { unEXTsRGB :: JSVal } instance Eq (EXTsRGB) where (EXTsRGB a) == (EXTsRGB b) = js_eq a b instance PToJSVal EXTsRGB where pToJSVal = unEXTsRGB {-# INLINE pToJSVal #-} instance PFromJSVal EXTsRGB where pFromJSVal = EXTsRGB {-# INLINE pFromJSVal #-} instance ToJSVal EXTsRGB where toJSVal = return . unEXTsRGB {-# INLINE toJSVal #-} instance FromJSVal EXTsRGB where fromJSVal = return . fmap EXTsRGB . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject EXTsRGB where typeGType _ = gTypeEXTsRGB {-# INLINE typeGType #-} noEXTsRGB :: Maybe EXTsRGB noEXTsRGB = Nothing {-# INLINE noEXTsRGB #-} foreign import javascript unsafe "window[\"EXTsRGB\"]" gTypeEXTsRGB :: GType -- | Functions for this inteface are in "GHCJS.DOM.EcKeyParams". -- Base interface functions are in: -- -- * "GHCJS.DOM.CryptoAlgorithmParameters" -- -- newtype EcKeyParams = EcKeyParams { unEcKeyParams :: JSVal } instance Eq (EcKeyParams) where (EcKeyParams a) == (EcKeyParams b) = js_eq a b instance PToJSVal EcKeyParams where pToJSVal = unEcKeyParams {-# INLINE pToJSVal #-} instance PFromJSVal EcKeyParams where pFromJSVal = EcKeyParams {-# INLINE pFromJSVal #-} instance ToJSVal EcKeyParams where toJSVal = return . unEcKeyParams {-# INLINE toJSVal #-} instance FromJSVal EcKeyParams where fromJSVal = return . fmap EcKeyParams . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsCryptoAlgorithmParameters EcKeyParams instance IsGObject EcKeyParams where typeGType _ = gTypeEcKeyParams {-# INLINE typeGType #-} noEcKeyParams :: Maybe EcKeyParams noEcKeyParams = Nothing {-# INLINE noEcKeyParams #-} foreign import javascript unsafe "window[\"EcKeyParams\"]" gTypeEcKeyParams :: GType -- | Functions for this inteface are in "GHCJS.DOM.EcdhKeyDeriveParams". -- Base interface functions are in: -- -- * "GHCJS.DOM.CryptoAlgorithmParameters" -- -- newtype EcdhKeyDeriveParams = EcdhKeyDeriveParams { unEcdhKeyDeriveParams :: JSVal } instance Eq (EcdhKeyDeriveParams) where (EcdhKeyDeriveParams a) == (EcdhKeyDeriveParams b) = js_eq a b instance PToJSVal EcdhKeyDeriveParams where pToJSVal = unEcdhKeyDeriveParams {-# INLINE pToJSVal #-} instance PFromJSVal EcdhKeyDeriveParams where pFromJSVal = EcdhKeyDeriveParams {-# INLINE pFromJSVal #-} instance ToJSVal EcdhKeyDeriveParams where toJSVal = return . unEcdhKeyDeriveParams {-# INLINE toJSVal #-} instance FromJSVal EcdhKeyDeriveParams where fromJSVal = return . fmap EcdhKeyDeriveParams . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsCryptoAlgorithmParameters EcdhKeyDeriveParams instance IsGObject EcdhKeyDeriveParams where typeGType _ = gTypeEcdhKeyDeriveParams {-# INLINE typeGType #-} noEcdhKeyDeriveParams :: Maybe EcdhKeyDeriveParams noEcdhKeyDeriveParams = Nothing {-# INLINE noEcdhKeyDeriveParams #-} foreign import javascript unsafe "window[\"EcdhKeyDeriveParams\"]" gTypeEcdhKeyDeriveParams :: GType -- | Functions for this inteface are in "GHCJS.DOM.EcdsaParams". -- Base interface functions are in: -- -- * "GHCJS.DOM.CryptoAlgorithmParameters" -- -- newtype EcdsaParams = EcdsaParams { unEcdsaParams :: JSVal } instance Eq (EcdsaParams) where (EcdsaParams a) == (EcdsaParams b) = js_eq a b instance PToJSVal EcdsaParams where pToJSVal = unEcdsaParams {-# INLINE pToJSVal #-} instance PFromJSVal EcdsaParams where pFromJSVal = EcdsaParams {-# INLINE pFromJSVal #-} instance ToJSVal EcdsaParams where toJSVal = return . unEcdsaParams {-# INLINE toJSVal #-} instance FromJSVal EcdsaParams where fromJSVal = return . fmap EcdsaParams . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsCryptoAlgorithmParameters EcdsaParams instance IsGObject EcdsaParams where typeGType _ = gTypeEcdsaParams {-# INLINE typeGType #-} noEcdsaParams :: Maybe EcdsaParams noEcdsaParams = Nothing {-# INLINE noEcdsaParams #-} foreign import javascript unsafe "window[\"EcdsaParams\"]" gTypeEcdsaParams :: GType -- | Functions for this inteface are in "GHCJS.DOM.Element". -- Base interface functions are in: -- -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- -- newtype Element = Element { unElement :: JSVal } instance Eq (Element) where (Element a) == (Element b) = js_eq a b instance PToJSVal Element where pToJSVal = unElement {-# INLINE pToJSVal #-} instance PFromJSVal Element where pFromJSVal = Element {-# INLINE pFromJSVal #-} instance ToJSVal Element where toJSVal = return . unElement {-# INLINE toJSVal #-} instance FromJSVal Element where fromJSVal = return . fmap Element . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsNode o, IsEventTarget o, IsSlotable o, IsParentNode o, IsNonDocumentTypeChildNode o, IsDocumentAndElementEventHandlers o, IsChildNode o, IsAnimatable o, IsGObject o) => IsElement o toElement :: IsElement o => o -> Element toElement = Element . coerce instance IsElement Element instance IsNode Element instance IsEventTarget Element instance IsSlotable Element instance IsParentNode Element instance IsNonDocumentTypeChildNode Element instance IsDocumentAndElementEventHandlers Element instance IsChildNode Element instance IsAnimatable Element instance IsGObject Element where typeGType _ = gTypeElement {-# INLINE typeGType #-} noElement :: Maybe Element noElement = Nothing {-# INLINE noElement #-} foreign import javascript unsafe "window[\"Element\"]" gTypeElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.ElementCSSInlineStyle". -- -- newtype ElementCSSInlineStyle = ElementCSSInlineStyle { unElementCSSInlineStyle :: JSVal } instance Eq (ElementCSSInlineStyle) where (ElementCSSInlineStyle a) == (ElementCSSInlineStyle b) = js_eq a b instance PToJSVal ElementCSSInlineStyle where pToJSVal = unElementCSSInlineStyle {-# INLINE pToJSVal #-} instance PFromJSVal ElementCSSInlineStyle where pFromJSVal = ElementCSSInlineStyle {-# INLINE pFromJSVal #-} instance ToJSVal ElementCSSInlineStyle where toJSVal = return . unElementCSSInlineStyle {-# INLINE toJSVal #-} instance FromJSVal ElementCSSInlineStyle where fromJSVal = return . fmap ElementCSSInlineStyle . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsGObject o) => IsElementCSSInlineStyle o toElementCSSInlineStyle :: IsElementCSSInlineStyle o => o -> ElementCSSInlineStyle toElementCSSInlineStyle = ElementCSSInlineStyle . coerce instance IsElementCSSInlineStyle ElementCSSInlineStyle instance IsGObject ElementCSSInlineStyle where typeGType _ = gTypeElementCSSInlineStyle {-# INLINE typeGType #-} noElementCSSInlineStyle :: Maybe ElementCSSInlineStyle noElementCSSInlineStyle = Nothing {-# INLINE noElementCSSInlineStyle #-} foreign import javascript unsafe "window[\"ElementCSSInlineStyle\"]" gTypeElementCSSInlineStyle :: GType -- | Functions for this inteface are in "GHCJS.DOM.ErrorEvent". -- Base interface functions are in: -- -- * "GHCJS.DOM.Event" -- -- newtype ErrorEvent = ErrorEvent { unErrorEvent :: JSVal } instance Eq (ErrorEvent) where (ErrorEvent a) == (ErrorEvent b) = js_eq a b instance PToJSVal ErrorEvent where pToJSVal = unErrorEvent {-# INLINE pToJSVal #-} instance PFromJSVal ErrorEvent where pFromJSVal = ErrorEvent {-# INLINE pFromJSVal #-} instance ToJSVal ErrorEvent where toJSVal = return . unErrorEvent {-# INLINE toJSVal #-} instance FromJSVal ErrorEvent where fromJSVal = return . fmap ErrorEvent . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEvent ErrorEvent instance IsGObject ErrorEvent where typeGType _ = gTypeErrorEvent {-# INLINE typeGType #-} noErrorEvent :: Maybe ErrorEvent noErrorEvent = Nothing {-# INLINE noErrorEvent #-} foreign import javascript unsafe "window[\"ErrorEvent\"]" gTypeErrorEvent :: GType -- | Functions for this inteface are in "GHCJS.DOM.ErrorEventInit". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventInit" -- -- newtype ErrorEventInit = ErrorEventInit { unErrorEventInit :: JSVal } instance Eq (ErrorEventInit) where (ErrorEventInit a) == (ErrorEventInit b) = js_eq a b instance PToJSVal ErrorEventInit where pToJSVal = unErrorEventInit {-# INLINE pToJSVal #-} instance PFromJSVal ErrorEventInit where pFromJSVal = ErrorEventInit {-# INLINE pFromJSVal #-} instance ToJSVal ErrorEventInit where toJSVal = return . unErrorEventInit {-# INLINE toJSVal #-} instance FromJSVal ErrorEventInit where fromJSVal = return . fmap ErrorEventInit . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventInit ErrorEventInit instance IsGObject ErrorEventInit where typeGType _ = gTypeErrorEventInit {-# INLINE typeGType #-} noErrorEventInit :: Maybe ErrorEventInit noErrorEventInit = Nothing {-# INLINE noErrorEventInit #-} foreign import javascript unsafe "window[\"ErrorEventInit\"]" gTypeErrorEventInit :: GType -- | Functions for this inteface are in "GHCJS.DOM.Event". -- -- newtype Event = Event { unEvent :: JSVal } instance Eq (Event) where (Event a) == (Event b) = js_eq a b instance PToJSVal Event where pToJSVal = unEvent {-# INLINE pToJSVal #-} instance PFromJSVal Event where pFromJSVal = Event {-# INLINE pFromJSVal #-} instance ToJSVal Event where toJSVal = return . unEvent {-# INLINE toJSVal #-} instance FromJSVal Event where fromJSVal = return . fmap Event . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsGObject o) => IsEvent o toEvent :: IsEvent o => o -> Event toEvent = Event . coerce instance IsEvent Event instance IsGObject Event where typeGType _ = gTypeEvent {-# INLINE typeGType #-} noEvent :: Maybe Event noEvent = Nothing {-# INLINE noEvent #-} foreign import javascript unsafe "window[\"Event\"]" gTypeEvent :: GType -- | Functions for this inteface are in "GHCJS.DOM.EventInit". -- -- newtype EventInit = EventInit { unEventInit :: JSVal } instance Eq (EventInit) where (EventInit a) == (EventInit b) = js_eq a b instance PToJSVal EventInit where pToJSVal = unEventInit {-# INLINE pToJSVal #-} instance PFromJSVal EventInit where pFromJSVal = EventInit {-# INLINE pFromJSVal #-} instance ToJSVal EventInit where toJSVal = return . unEventInit {-# INLINE toJSVal #-} instance FromJSVal EventInit where fromJSVal = return . fmap EventInit . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsGObject o) => IsEventInit o toEventInit :: IsEventInit o => o -> EventInit toEventInit = EventInit . coerce instance IsEventInit EventInit instance IsGObject EventInit where typeGType _ = gTypeEventInit {-# INLINE typeGType #-} noEventInit :: Maybe EventInit noEventInit = Nothing {-# INLINE noEventInit #-} foreign import javascript unsafe "window[\"EventInit\"]" gTypeEventInit :: GType -- | Functions for this inteface are in "GHCJS.DOM.EventListener". -- -- newtype EventListener = EventListener { unEventListener :: JSVal } instance Eq (EventListener) where (EventListener a) == (EventListener b) = js_eq a b instance PToJSVal EventListener where pToJSVal = unEventListener {-# INLINE pToJSVal #-} instance PFromJSVal EventListener where pFromJSVal = EventListener {-# INLINE pFromJSVal #-} instance ToJSVal EventListener where toJSVal = return . unEventListener {-# INLINE toJSVal #-} instance FromJSVal EventListener where fromJSVal = return . fmap EventListener . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject EventListener where typeGType _ = gTypeEventListener {-# INLINE typeGType #-} noEventListener :: Maybe EventListener noEventListener = Nothing {-# INLINE noEventListener #-} foreign import javascript unsafe "window[\"EventListener\"]" gTypeEventListener :: GType -- | Functions for this inteface are in "GHCJS.DOM.EventListenerOptions". -- -- newtype EventListenerOptions = EventListenerOptions { unEventListenerOptions :: JSVal } instance Eq (EventListenerOptions) where (EventListenerOptions a) == (EventListenerOptions b) = js_eq a b instance PToJSVal EventListenerOptions where pToJSVal = unEventListenerOptions {-# INLINE pToJSVal #-} instance PFromJSVal EventListenerOptions where pFromJSVal = EventListenerOptions {-# INLINE pFromJSVal #-} instance ToJSVal EventListenerOptions where toJSVal = return . unEventListenerOptions {-# INLINE toJSVal #-} instance FromJSVal EventListenerOptions where fromJSVal = return . fmap EventListenerOptions . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsGObject o) => IsEventListenerOptions o toEventListenerOptions :: IsEventListenerOptions o => o -> EventListenerOptions toEventListenerOptions = EventListenerOptions . coerce instance IsEventListenerOptions EventListenerOptions instance IsGObject EventListenerOptions where typeGType _ = gTypeEventListenerOptions {-# INLINE typeGType #-} noEventListenerOptions :: Maybe EventListenerOptions noEventListenerOptions = Nothing {-# INLINE noEventListenerOptions #-} foreign import javascript unsafe "window[\"EventListenerOptions\"]" gTypeEventListenerOptions :: GType -- | Functions for this inteface are in "GHCJS.DOM.EventModifierInit". -- Base interface functions are in: -- -- * "GHCJS.DOM.UIEventInit" -- * "GHCJS.DOM.EventInit" -- -- newtype EventModifierInit = EventModifierInit { unEventModifierInit :: JSVal } instance Eq (EventModifierInit) where (EventModifierInit a) == (EventModifierInit b) = js_eq a b instance PToJSVal EventModifierInit where pToJSVal = unEventModifierInit {-# INLINE pToJSVal #-} instance PFromJSVal EventModifierInit where pFromJSVal = EventModifierInit {-# INLINE pFromJSVal #-} instance ToJSVal EventModifierInit where toJSVal = return . unEventModifierInit {-# INLINE toJSVal #-} instance FromJSVal EventModifierInit where fromJSVal = return . fmap EventModifierInit . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsUIEventInit o, IsEventInit o, IsGObject o) => IsEventModifierInit o toEventModifierInit :: IsEventModifierInit o => o -> EventModifierInit toEventModifierInit = EventModifierInit . coerce instance IsEventModifierInit EventModifierInit instance IsUIEventInit EventModifierInit instance IsEventInit EventModifierInit instance IsGObject EventModifierInit where typeGType _ = gTypeEventModifierInit {-# INLINE typeGType #-} noEventModifierInit :: Maybe EventModifierInit noEventModifierInit = Nothing {-# INLINE noEventModifierInit #-} foreign import javascript unsafe "window[\"EventModifierInit\"]" gTypeEventModifierInit :: GType -- | Functions for this inteface are in "GHCJS.DOM.EventSource". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventTarget" -- -- newtype EventSource = EventSource { unEventSource :: JSVal } instance Eq (EventSource) where (EventSource a) == (EventSource b) = js_eq a b instance PToJSVal EventSource where pToJSVal = unEventSource {-# INLINE pToJSVal #-} instance PFromJSVal EventSource where pFromJSVal = EventSource {-# INLINE pFromJSVal #-} instance ToJSVal EventSource where toJSVal = return . unEventSource {-# INLINE toJSVal #-} instance FromJSVal EventSource where fromJSVal = return . fmap EventSource . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventTarget EventSource instance IsGObject EventSource where typeGType _ = gTypeEventSource {-# INLINE typeGType #-} noEventSource :: Maybe EventSource noEventSource = Nothing {-# INLINE noEventSource #-} foreign import javascript unsafe "window[\"EventSource\"]" gTypeEventSource :: GType -- | Functions for this inteface are in "GHCJS.DOM.EventSourceInit". -- -- newtype EventSourceInit = EventSourceInit { unEventSourceInit :: JSVal } instance Eq (EventSourceInit) where (EventSourceInit a) == (EventSourceInit b) = js_eq a b instance PToJSVal EventSourceInit where pToJSVal = unEventSourceInit {-# INLINE pToJSVal #-} instance PFromJSVal EventSourceInit where pFromJSVal = EventSourceInit {-# INLINE pFromJSVal #-} instance ToJSVal EventSourceInit where toJSVal = return . unEventSourceInit {-# INLINE toJSVal #-} instance FromJSVal EventSourceInit where fromJSVal = return . fmap EventSourceInit . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject EventSourceInit where typeGType _ = gTypeEventSourceInit {-# INLINE typeGType #-} noEventSourceInit :: Maybe EventSourceInit noEventSourceInit = Nothing {-# INLINE noEventSourceInit #-} foreign import javascript unsafe "window[\"EventSourceInit\"]" gTypeEventSourceInit :: GType -- | Functions for this inteface are in "GHCJS.DOM.EventTarget". -- -- newtype EventTarget = EventTarget { unEventTarget :: JSVal } instance Eq (EventTarget) where (EventTarget a) == (EventTarget b) = js_eq a b instance PToJSVal EventTarget where pToJSVal = unEventTarget {-# INLINE pToJSVal #-} instance PFromJSVal EventTarget where pFromJSVal = EventTarget {-# INLINE pFromJSVal #-} instance ToJSVal EventTarget where toJSVal = return . unEventTarget {-# INLINE toJSVal #-} instance FromJSVal EventTarget where fromJSVal = return . fmap EventTarget . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsGObject o) => IsEventTarget o toEventTarget :: IsEventTarget o => o -> EventTarget toEventTarget = EventTarget . coerce instance IsEventTarget EventTarget instance IsGObject EventTarget where typeGType _ = gTypeEventTarget {-# INLINE typeGType #-} noEventTarget :: Maybe EventTarget noEventTarget = Nothing {-# INLINE noEventTarget #-} foreign import javascript unsafe "window[\"EventTarget\"]" gTypeEventTarget :: GType -- | Functions for this inteface are in "GHCJS.DOM.File". -- Base interface functions are in: -- -- * "GHCJS.DOM.Blob" -- -- newtype File = File { unFile :: JSVal } instance Eq (File) where (File a) == (File b) = js_eq a b instance PToJSVal File where pToJSVal = unFile {-# INLINE pToJSVal #-} instance PFromJSVal File where pFromJSVal = File {-# INLINE pFromJSVal #-} instance ToJSVal File where toJSVal = return . unFile {-# INLINE toJSVal #-} instance FromJSVal File where fromJSVal = return . fmap File . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsBlob File instance IsGObject File where typeGType _ = gTypeFile {-# INLINE typeGType #-} noFile :: Maybe File noFile = Nothing {-# INLINE noFile #-} foreign import javascript unsafe "window[\"File\"]" gTypeFile :: GType -- | Functions for this inteface are in "GHCJS.DOM.FileError". -- -- newtype FileError = FileError { unFileError :: JSVal } instance Eq (FileError) where (FileError a) == (FileError b) = js_eq a b instance PToJSVal FileError where pToJSVal = unFileError {-# INLINE pToJSVal #-} instance PFromJSVal FileError where pFromJSVal = FileError {-# INLINE pFromJSVal #-} instance ToJSVal FileError where toJSVal = return . unFileError {-# INLINE toJSVal #-} instance FromJSVal FileError where fromJSVal = return . fmap FileError . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject FileError where typeGType _ = gTypeFileError {-# INLINE typeGType #-} noFileError :: Maybe FileError noFileError = Nothing {-# INLINE noFileError #-} foreign import javascript unsafe "window[\"FileError\"]" gTypeFileError :: GType -- | Functions for this inteface are in "GHCJS.DOM.FileException". -- -- newtype FileException = FileException { unFileException :: JSVal } instance Eq (FileException) where (FileException a) == (FileException b) = js_eq a b instance PToJSVal FileException where pToJSVal = unFileException {-# INLINE pToJSVal #-} instance PFromJSVal FileException where pFromJSVal = FileException {-# INLINE pFromJSVal #-} instance ToJSVal FileException where toJSVal = return . unFileException {-# INLINE toJSVal #-} instance FromJSVal FileException where fromJSVal = return . fmap FileException . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject FileException where typeGType _ = gTypeFileException {-# INLINE typeGType #-} noFileException :: Maybe FileException noFileException = Nothing {-# INLINE noFileException #-} foreign import javascript unsafe "window[\"FileException\"]" gTypeFileException :: GType -- | Functions for this inteface are in "GHCJS.DOM.FileList". -- -- newtype FileList = FileList { unFileList :: JSVal } instance Eq (FileList) where (FileList a) == (FileList b) = js_eq a b instance PToJSVal FileList where pToJSVal = unFileList {-# INLINE pToJSVal #-} instance PFromJSVal FileList where pFromJSVal = FileList {-# INLINE pFromJSVal #-} instance ToJSVal FileList where toJSVal = return . unFileList {-# INLINE toJSVal #-} instance FromJSVal FileList where fromJSVal = return . fmap FileList . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject FileList where typeGType _ = gTypeFileList {-# INLINE typeGType #-} noFileList :: Maybe FileList noFileList = Nothing {-# INLINE noFileList #-} foreign import javascript unsafe "window[\"FileList\"]" gTypeFileList :: GType -- | Functions for this inteface are in "GHCJS.DOM.FilePropertyBag". -- Base interface functions are in: -- -- * "GHCJS.DOM.BlobPropertyBag" -- -- newtype FilePropertyBag = FilePropertyBag { unFilePropertyBag :: JSVal } instance Eq (FilePropertyBag) where (FilePropertyBag a) == (FilePropertyBag b) = js_eq a b instance PToJSVal FilePropertyBag where pToJSVal = unFilePropertyBag {-# INLINE pToJSVal #-} instance PFromJSVal FilePropertyBag where pFromJSVal = FilePropertyBag {-# INLINE pFromJSVal #-} instance ToJSVal FilePropertyBag where toJSVal = return . unFilePropertyBag {-# INLINE toJSVal #-} instance FromJSVal FilePropertyBag where fromJSVal = return . fmap FilePropertyBag . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsBlobPropertyBag FilePropertyBag instance IsGObject FilePropertyBag where typeGType _ = gTypeFilePropertyBag {-# INLINE typeGType #-} noFilePropertyBag :: Maybe FilePropertyBag noFilePropertyBag = Nothing {-# INLINE noFilePropertyBag #-} foreign import javascript unsafe "window[\"FilePropertyBag\"]" gTypeFilePropertyBag :: GType -- | Functions for this inteface are in "GHCJS.DOM.FileReader". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventTarget" -- -- newtype FileReader = FileReader { unFileReader :: JSVal } instance Eq (FileReader) where (FileReader a) == (FileReader b) = js_eq a b instance PToJSVal FileReader where pToJSVal = unFileReader {-# INLINE pToJSVal #-} instance PFromJSVal FileReader where pFromJSVal = FileReader {-# INLINE pFromJSVal #-} instance ToJSVal FileReader where toJSVal = return . unFileReader {-# INLINE toJSVal #-} instance FromJSVal FileReader where fromJSVal = return . fmap FileReader . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventTarget FileReader instance IsGObject FileReader where typeGType _ = gTypeFileReader {-# INLINE typeGType #-} noFileReader :: Maybe FileReader noFileReader = Nothing {-# INLINE noFileReader #-} foreign import javascript unsafe "window[\"FileReader\"]" gTypeFileReader :: GType -- | Functions for this inteface are in "GHCJS.DOM.FileReaderSync". -- -- newtype FileReaderSync = FileReaderSync { unFileReaderSync :: JSVal } instance Eq (FileReaderSync) where (FileReaderSync a) == (FileReaderSync b) = js_eq a b instance PToJSVal FileReaderSync where pToJSVal = unFileReaderSync {-# INLINE pToJSVal #-} instance PFromJSVal FileReaderSync where pFromJSVal = FileReaderSync {-# INLINE pFromJSVal #-} instance ToJSVal FileReaderSync where toJSVal = return . unFileReaderSync {-# INLINE toJSVal #-} instance FromJSVal FileReaderSync where fromJSVal = return . fmap FileReaderSync . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject FileReaderSync where typeGType _ = gTypeFileReaderSync {-# INLINE typeGType #-} noFileReaderSync :: Maybe FileReaderSync noFileReaderSync = Nothing {-# INLINE noFileReaderSync #-} foreign import javascript unsafe "window[\"FileReaderSync\"]" gTypeFileReaderSync :: GType -- | Functions for this inteface are in "GHCJS.DOM.FocusEvent". -- Base interface functions are in: -- -- * "GHCJS.DOM.UIEvent" -- * "GHCJS.DOM.Event" -- -- newtype FocusEvent = FocusEvent { unFocusEvent :: JSVal } instance Eq (FocusEvent) where (FocusEvent a) == (FocusEvent b) = js_eq a b instance PToJSVal FocusEvent where pToJSVal = unFocusEvent {-# INLINE pToJSVal #-} instance PFromJSVal FocusEvent where pFromJSVal = FocusEvent {-# INLINE pFromJSVal #-} instance ToJSVal FocusEvent where toJSVal = return . unFocusEvent {-# INLINE toJSVal #-} instance FromJSVal FocusEvent where fromJSVal = return . fmap FocusEvent . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsUIEvent FocusEvent instance IsEvent FocusEvent instance IsGObject FocusEvent where typeGType _ = gTypeFocusEvent {-# INLINE typeGType #-} noFocusEvent :: Maybe FocusEvent noFocusEvent = Nothing {-# INLINE noFocusEvent #-} foreign import javascript unsafe "window[\"FocusEvent\"]" gTypeFocusEvent :: GType -- | Functions for this inteface are in "GHCJS.DOM.FocusEventInit". -- Base interface functions are in: -- -- * "GHCJS.DOM.UIEventInit" -- * "GHCJS.DOM.EventInit" -- -- newtype FocusEventInit = FocusEventInit { unFocusEventInit :: JSVal } instance Eq (FocusEventInit) where (FocusEventInit a) == (FocusEventInit b) = js_eq a b instance PToJSVal FocusEventInit where pToJSVal = unFocusEventInit {-# INLINE pToJSVal #-} instance PFromJSVal FocusEventInit where pFromJSVal = FocusEventInit {-# INLINE pFromJSVal #-} instance ToJSVal FocusEventInit where toJSVal = return . unFocusEventInit {-# INLINE toJSVal #-} instance FromJSVal FocusEventInit where fromJSVal = return . fmap FocusEventInit . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsUIEventInit FocusEventInit instance IsEventInit FocusEventInit instance IsGObject FocusEventInit where typeGType _ = gTypeFocusEventInit {-# INLINE typeGType #-} noFocusEventInit :: Maybe FocusEventInit noFocusEventInit = Nothing {-# INLINE noFocusEventInit #-} foreign import javascript unsafe "window[\"FocusEventInit\"]" gTypeFocusEventInit :: GType -- | Functions for this inteface are in "GHCJS.DOM.FontFace". -- -- newtype FontFace = FontFace { unFontFace :: JSVal } instance Eq (FontFace) where (FontFace a) == (FontFace b) = js_eq a b instance PToJSVal FontFace where pToJSVal = unFontFace {-# INLINE pToJSVal #-} instance PFromJSVal FontFace where pFromJSVal = FontFace {-# INLINE pFromJSVal #-} instance ToJSVal FontFace where toJSVal = return . unFontFace {-# INLINE toJSVal #-} instance FromJSVal FontFace where fromJSVal = return . fmap FontFace . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject FontFace where typeGType _ = gTypeFontFace {-# INLINE typeGType #-} noFontFace :: Maybe FontFace noFontFace = Nothing {-# INLINE noFontFace #-} foreign import javascript unsafe "window[\"FontFace\"]" gTypeFontFace :: GType -- | Functions for this inteface are in "GHCJS.DOM.FontFaceDescriptors". -- -- newtype FontFaceDescriptors = FontFaceDescriptors { unFontFaceDescriptors :: JSVal } instance Eq (FontFaceDescriptors) where (FontFaceDescriptors a) == (FontFaceDescriptors b) = js_eq a b instance PToJSVal FontFaceDescriptors where pToJSVal = unFontFaceDescriptors {-# INLINE pToJSVal #-} instance PFromJSVal FontFaceDescriptors where pFromJSVal = FontFaceDescriptors {-# INLINE pFromJSVal #-} instance ToJSVal FontFaceDescriptors where toJSVal = return . unFontFaceDescriptors {-# INLINE toJSVal #-} instance FromJSVal FontFaceDescriptors where fromJSVal = return . fmap FontFaceDescriptors . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject FontFaceDescriptors where typeGType _ = gTypeFontFaceDescriptors {-# INLINE typeGType #-} noFontFaceDescriptors :: Maybe FontFaceDescriptors noFontFaceDescriptors = Nothing {-# INLINE noFontFaceDescriptors #-} foreign import javascript unsafe "window[\"FontFaceDescriptors\"]" gTypeFontFaceDescriptors :: GType -- | Functions for this inteface are in "GHCJS.DOM.FontFaceSet". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventTarget" -- -- newtype FontFaceSet = FontFaceSet { unFontFaceSet :: JSVal } instance Eq (FontFaceSet) where (FontFaceSet a) == (FontFaceSet b) = js_eq a b instance PToJSVal FontFaceSet where pToJSVal = unFontFaceSet {-# INLINE pToJSVal #-} instance PFromJSVal FontFaceSet where pFromJSVal = FontFaceSet {-# INLINE pFromJSVal #-} instance ToJSVal FontFaceSet where toJSVal = return . unFontFaceSet {-# INLINE toJSVal #-} instance FromJSVal FontFaceSet where fromJSVal = return . fmap FontFaceSet . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventTarget FontFaceSet instance IsGObject FontFaceSet where typeGType _ = gTypeFontFaceSet {-# INLINE typeGType #-} noFontFaceSet :: Maybe FontFaceSet noFontFaceSet = Nothing {-# INLINE noFontFaceSet #-} foreign import javascript unsafe "window[\"FontFaceSet\"]" gTypeFontFaceSet :: GType -- | Functions for this inteface are in "GHCJS.DOM.FormData". -- -- newtype FormData = FormData { unFormData :: JSVal } instance Eq (FormData) where (FormData a) == (FormData b) = js_eq a b instance PToJSVal FormData where pToJSVal = unFormData {-# INLINE pToJSVal #-} instance PFromJSVal FormData where pFromJSVal = FormData {-# INLINE pFromJSVal #-} instance ToJSVal FormData where toJSVal = return . unFormData {-# INLINE toJSVal #-} instance FromJSVal FormData where fromJSVal = return . fmap FormData . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject FormData where typeGType _ = gTypeFormData {-# INLINE typeGType #-} noFormData :: Maybe FormData noFormData = Nothing {-# INLINE noFormData #-} foreign import javascript unsafe "window[\"FormData\"]" gTypeFormData :: GType -- | Functions for this inteface are in "GHCJS.DOM.GainNode". -- Base interface functions are in: -- -- * "GHCJS.DOM.AudioNode" -- * "GHCJS.DOM.EventTarget" -- -- newtype GainNode = GainNode { unGainNode :: JSVal } instance Eq (GainNode) where (GainNode a) == (GainNode b) = js_eq a b instance PToJSVal GainNode where pToJSVal = unGainNode {-# INLINE pToJSVal #-} instance PFromJSVal GainNode where pFromJSVal = GainNode {-# INLINE pFromJSVal #-} instance ToJSVal GainNode where toJSVal = return . unGainNode {-# INLINE toJSVal #-} instance FromJSVal GainNode where fromJSVal = return . fmap GainNode . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsAudioNode GainNode instance IsEventTarget GainNode instance IsGObject GainNode where typeGType _ = gTypeGainNode {-# INLINE typeGType #-} noGainNode :: Maybe GainNode noGainNode = Nothing {-# INLINE noGainNode #-} foreign import javascript unsafe "window[\"GainNode\"]" gTypeGainNode :: GType -- | Functions for this inteface are in "GHCJS.DOM.Gamepad". -- -- newtype Gamepad = Gamepad { unGamepad :: JSVal } instance Eq (Gamepad) where (Gamepad a) == (Gamepad b) = js_eq a b instance PToJSVal Gamepad where pToJSVal = unGamepad {-# INLINE pToJSVal #-} instance PFromJSVal Gamepad where pFromJSVal = Gamepad {-# INLINE pFromJSVal #-} instance ToJSVal Gamepad where toJSVal = return . unGamepad {-# INLINE toJSVal #-} instance FromJSVal Gamepad where fromJSVal = return . fmap Gamepad . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject Gamepad where typeGType _ = gTypeGamepad {-# INLINE typeGType #-} noGamepad :: Maybe Gamepad noGamepad = Nothing {-# INLINE noGamepad #-} foreign import javascript unsafe "window[\"Gamepad\"]" gTypeGamepad :: GType -- | Functions for this inteface are in "GHCJS.DOM.GamepadButton". -- -- newtype GamepadButton = GamepadButton { unGamepadButton :: JSVal } instance Eq (GamepadButton) where (GamepadButton a) == (GamepadButton b) = js_eq a b instance PToJSVal GamepadButton where pToJSVal = unGamepadButton {-# INLINE pToJSVal #-} instance PFromJSVal GamepadButton where pFromJSVal = GamepadButton {-# INLINE pFromJSVal #-} instance ToJSVal GamepadButton where toJSVal = return . unGamepadButton {-# INLINE toJSVal #-} instance FromJSVal GamepadButton where fromJSVal = return . fmap GamepadButton . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject GamepadButton where typeGType _ = gTypeGamepadButton {-# INLINE typeGType #-} noGamepadButton :: Maybe GamepadButton noGamepadButton = Nothing {-# INLINE noGamepadButton #-} foreign import javascript unsafe "window[\"GamepadButton\"]" gTypeGamepadButton :: GType -- | Functions for this inteface are in "GHCJS.DOM.GamepadEvent". -- Base interface functions are in: -- -- * "GHCJS.DOM.Event" -- -- newtype GamepadEvent = GamepadEvent { unGamepadEvent :: JSVal } instance Eq (GamepadEvent) where (GamepadEvent a) == (GamepadEvent b) = js_eq a b instance PToJSVal GamepadEvent where pToJSVal = unGamepadEvent {-# INLINE pToJSVal #-} instance PFromJSVal GamepadEvent where pFromJSVal = GamepadEvent {-# INLINE pFromJSVal #-} instance ToJSVal GamepadEvent where toJSVal = return . unGamepadEvent {-# INLINE toJSVal #-} instance FromJSVal GamepadEvent where fromJSVal = return . fmap GamepadEvent . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEvent GamepadEvent instance IsGObject GamepadEvent where typeGType _ = gTypeGamepadEvent {-# INLINE typeGType #-} noGamepadEvent :: Maybe GamepadEvent noGamepadEvent = Nothing {-# INLINE noGamepadEvent #-} foreign import javascript unsafe "window[\"GamepadEvent\"]" gTypeGamepadEvent :: GType -- | Functions for this inteface are in "GHCJS.DOM.GamepadEventInit". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventInit" -- -- newtype GamepadEventInit = GamepadEventInit { unGamepadEventInit :: JSVal } instance Eq (GamepadEventInit) where (GamepadEventInit a) == (GamepadEventInit b) = js_eq a b instance PToJSVal GamepadEventInit where pToJSVal = unGamepadEventInit {-# INLINE pToJSVal #-} instance PFromJSVal GamepadEventInit where pFromJSVal = GamepadEventInit {-# INLINE pFromJSVal #-} instance ToJSVal GamepadEventInit where toJSVal = return . unGamepadEventInit {-# INLINE toJSVal #-} instance FromJSVal GamepadEventInit where fromJSVal = return . fmap GamepadEventInit . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventInit GamepadEventInit instance IsGObject GamepadEventInit where typeGType _ = gTypeGamepadEventInit {-# INLINE typeGType #-} noGamepadEventInit :: Maybe GamepadEventInit noGamepadEventInit = Nothing {-# INLINE noGamepadEventInit #-} foreign import javascript unsafe "window[\"GamepadEventInit\"]" gTypeGamepadEventInit :: GType -- | Functions for this inteface are in "GHCJS.DOM.Geolocation". -- -- newtype Geolocation = Geolocation { unGeolocation :: JSVal } instance Eq (Geolocation) where (Geolocation a) == (Geolocation b) = js_eq a b instance PToJSVal Geolocation where pToJSVal = unGeolocation {-# INLINE pToJSVal #-} instance PFromJSVal Geolocation where pFromJSVal = Geolocation {-# INLINE pFromJSVal #-} instance ToJSVal Geolocation where toJSVal = return . unGeolocation {-# INLINE toJSVal #-} instance FromJSVal Geolocation where fromJSVal = return . fmap Geolocation . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject Geolocation where typeGType _ = gTypeGeolocation {-# INLINE typeGType #-} noGeolocation :: Maybe Geolocation noGeolocation = Nothing {-# INLINE noGeolocation #-} foreign import javascript unsafe "window[\"Geolocation\"]" gTypeGeolocation :: GType -- | Functions for this inteface are in "GHCJS.DOM.Geoposition". -- -- newtype Geoposition = Geoposition { unGeoposition :: JSVal } instance Eq (Geoposition) where (Geoposition a) == (Geoposition b) = js_eq a b instance PToJSVal Geoposition where pToJSVal = unGeoposition {-# INLINE pToJSVal #-} instance PFromJSVal Geoposition where pFromJSVal = Geoposition {-# INLINE pFromJSVal #-} instance ToJSVal Geoposition where toJSVal = return . unGeoposition {-# INLINE toJSVal #-} instance FromJSVal Geoposition where fromJSVal = return . fmap Geoposition . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject Geoposition where typeGType _ = gTypeGeoposition {-# INLINE typeGType #-} noGeoposition :: Maybe Geoposition noGeoposition = Nothing {-# INLINE noGeoposition #-} foreign import javascript unsafe "window[\"Geoposition\"]" gTypeGeoposition :: GType -- | Functions for this inteface are in "GHCJS.DOM.GetRootNodeOptions". -- -- newtype GetRootNodeOptions = GetRootNodeOptions { unGetRootNodeOptions :: JSVal } instance Eq (GetRootNodeOptions) where (GetRootNodeOptions a) == (GetRootNodeOptions b) = js_eq a b instance PToJSVal GetRootNodeOptions where pToJSVal = unGetRootNodeOptions {-# INLINE pToJSVal #-} instance PFromJSVal GetRootNodeOptions where pFromJSVal = GetRootNodeOptions {-# INLINE pFromJSVal #-} instance ToJSVal GetRootNodeOptions where toJSVal = return . unGetRootNodeOptions {-# INLINE toJSVal #-} instance FromJSVal GetRootNodeOptions where fromJSVal = return . fmap GetRootNodeOptions . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject GetRootNodeOptions where typeGType _ = gTypeGetRootNodeOptions {-# INLINE typeGType #-} noGetRootNodeOptions :: Maybe GetRootNodeOptions noGetRootNodeOptions = Nothing {-# INLINE noGetRootNodeOptions #-} foreign import javascript unsafe "window[\"GetRootNodeOptions\"]" gTypeGetRootNodeOptions :: GType -- | Functions for this inteface are in "GHCJS.DOM.GlobalCrypto". -- -- newtype GlobalCrypto = GlobalCrypto { unGlobalCrypto :: JSVal } instance Eq (GlobalCrypto) where (GlobalCrypto a) == (GlobalCrypto b) = js_eq a b instance PToJSVal GlobalCrypto where pToJSVal = unGlobalCrypto {-# INLINE pToJSVal #-} instance PFromJSVal GlobalCrypto where pFromJSVal = GlobalCrypto {-# INLINE pFromJSVal #-} instance ToJSVal GlobalCrypto where toJSVal = return . unGlobalCrypto {-# INLINE toJSVal #-} instance FromJSVal GlobalCrypto where fromJSVal = return . fmap GlobalCrypto . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsGObject o) => IsGlobalCrypto o toGlobalCrypto :: IsGlobalCrypto o => o -> GlobalCrypto toGlobalCrypto = GlobalCrypto . coerce instance IsGlobalCrypto GlobalCrypto instance IsGObject GlobalCrypto where typeGType _ = gTypeGlobalCrypto {-# INLINE typeGType #-} noGlobalCrypto :: Maybe GlobalCrypto noGlobalCrypto = Nothing {-# INLINE noGlobalCrypto #-} foreign import javascript unsafe "window[\"GlobalCrypto\"]" gTypeGlobalCrypto :: GType -- | Functions for this inteface are in "GHCJS.DOM.GlobalEventHandlers". -- -- newtype GlobalEventHandlers = GlobalEventHandlers { unGlobalEventHandlers :: JSVal } instance Eq (GlobalEventHandlers) where (GlobalEventHandlers a) == (GlobalEventHandlers b) = js_eq a b instance PToJSVal GlobalEventHandlers where pToJSVal = unGlobalEventHandlers {-# INLINE pToJSVal #-} instance PFromJSVal GlobalEventHandlers where pFromJSVal = GlobalEventHandlers {-# INLINE pFromJSVal #-} instance ToJSVal GlobalEventHandlers where toJSVal = return . unGlobalEventHandlers {-# INLINE toJSVal #-} instance FromJSVal GlobalEventHandlers where fromJSVal = return . fmap GlobalEventHandlers . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsGObject o) => IsGlobalEventHandlers o toGlobalEventHandlers :: IsGlobalEventHandlers o => o -> GlobalEventHandlers toGlobalEventHandlers = GlobalEventHandlers . coerce instance IsGlobalEventHandlers GlobalEventHandlers instance IsGObject GlobalEventHandlers where typeGType _ = gTypeGlobalEventHandlers {-# INLINE typeGType #-} noGlobalEventHandlers :: Maybe GlobalEventHandlers noGlobalEventHandlers = Nothing {-# INLINE noGlobalEventHandlers #-} foreign import javascript unsafe "window[\"GlobalEventHandlers\"]" gTypeGlobalEventHandlers :: GType -- | Functions for this inteface are in "GHCJS.DOM.GlobalPerformance". -- -- newtype GlobalPerformance = GlobalPerformance { unGlobalPerformance :: JSVal } instance Eq (GlobalPerformance) where (GlobalPerformance a) == (GlobalPerformance b) = js_eq a b instance PToJSVal GlobalPerformance where pToJSVal = unGlobalPerformance {-# INLINE pToJSVal #-} instance PFromJSVal GlobalPerformance where pFromJSVal = GlobalPerformance {-# INLINE pFromJSVal #-} instance ToJSVal GlobalPerformance where toJSVal = return . unGlobalPerformance {-# INLINE toJSVal #-} instance FromJSVal GlobalPerformance where fromJSVal = return . fmap GlobalPerformance . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsGObject o) => IsGlobalPerformance o toGlobalPerformance :: IsGlobalPerformance o => o -> GlobalPerformance toGlobalPerformance = GlobalPerformance . coerce instance IsGlobalPerformance GlobalPerformance instance IsGObject GlobalPerformance where typeGType _ = gTypeGlobalPerformance {-# INLINE typeGType #-} noGlobalPerformance :: Maybe GlobalPerformance noGlobalPerformance = Nothing {-# INLINE noGlobalPerformance #-} foreign import javascript unsafe "window[\"GlobalPerformance\"]" gTypeGlobalPerformance :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLAllCollection". -- -- newtype HTMLAllCollection = HTMLAllCollection { unHTMLAllCollection :: JSVal } instance Eq (HTMLAllCollection) where (HTMLAllCollection a) == (HTMLAllCollection b) = js_eq a b instance PToJSVal HTMLAllCollection where pToJSVal = unHTMLAllCollection {-# INLINE pToJSVal #-} instance PFromJSVal HTMLAllCollection where pFromJSVal = HTMLAllCollection {-# INLINE pFromJSVal #-} instance ToJSVal HTMLAllCollection where toJSVal = return . unHTMLAllCollection {-# INLINE toJSVal #-} instance FromJSVal HTMLAllCollection where fromJSVal = return . fmap HTMLAllCollection . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject HTMLAllCollection where typeGType _ = gTypeHTMLAllCollection {-# INLINE typeGType #-} noHTMLAllCollection :: Maybe HTMLAllCollection noHTMLAllCollection = Nothing {-# INLINE noHTMLAllCollection #-} foreign import javascript unsafe "window[\"HTMLAllCollection\"]" gTypeHTMLAllCollection :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLAnchorElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- * "GHCJS.DOM.HTMLHyperlinkElementUtils" -- -- newtype HTMLAnchorElement = HTMLAnchorElement { unHTMLAnchorElement :: JSVal } instance Eq (HTMLAnchorElement) where (HTMLAnchorElement a) == (HTMLAnchorElement b) = js_eq a b instance PToJSVal HTMLAnchorElement where pToJSVal = unHTMLAnchorElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLAnchorElement where pFromJSVal = HTMLAnchorElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLAnchorElement where toJSVal = return . unHTMLAnchorElement {-# INLINE toJSVal #-} instance FromJSVal HTMLAnchorElement where fromJSVal = return . fmap HTMLAnchorElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLAnchorElement instance IsElement HTMLAnchorElement instance IsNode HTMLAnchorElement instance IsEventTarget HTMLAnchorElement instance IsSlotable HTMLAnchorElement instance IsParentNode HTMLAnchorElement instance IsNonDocumentTypeChildNode HTMLAnchorElement instance IsDocumentAndElementEventHandlers HTMLAnchorElement instance IsChildNode HTMLAnchorElement instance IsAnimatable HTMLAnchorElement instance IsGlobalEventHandlers HTMLAnchorElement instance IsElementCSSInlineStyle HTMLAnchorElement instance IsHTMLHyperlinkElementUtils HTMLAnchorElement instance IsGObject HTMLAnchorElement where typeGType _ = gTypeHTMLAnchorElement {-# INLINE typeGType #-} noHTMLAnchorElement :: Maybe HTMLAnchorElement noHTMLAnchorElement = Nothing {-# INLINE noHTMLAnchorElement #-} foreign import javascript unsafe "window[\"HTMLAnchorElement\"]" gTypeHTMLAnchorElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLAppletElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLAppletElement = HTMLAppletElement { unHTMLAppletElement :: JSVal } instance Eq (HTMLAppletElement) where (HTMLAppletElement a) == (HTMLAppletElement b) = js_eq a b instance PToJSVal HTMLAppletElement where pToJSVal = unHTMLAppletElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLAppletElement where pFromJSVal = HTMLAppletElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLAppletElement where toJSVal = return . unHTMLAppletElement {-# INLINE toJSVal #-} instance FromJSVal HTMLAppletElement where fromJSVal = return . fmap HTMLAppletElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLAppletElement instance IsElement HTMLAppletElement instance IsNode HTMLAppletElement instance IsEventTarget HTMLAppletElement instance IsSlotable HTMLAppletElement instance IsParentNode HTMLAppletElement instance IsNonDocumentTypeChildNode HTMLAppletElement instance IsDocumentAndElementEventHandlers HTMLAppletElement instance IsChildNode HTMLAppletElement instance IsAnimatable HTMLAppletElement instance IsGlobalEventHandlers HTMLAppletElement instance IsElementCSSInlineStyle HTMLAppletElement instance IsGObject HTMLAppletElement where typeGType _ = gTypeHTMLAppletElement {-# INLINE typeGType #-} noHTMLAppletElement :: Maybe HTMLAppletElement noHTMLAppletElement = Nothing {-# INLINE noHTMLAppletElement #-} foreign import javascript unsafe "window[\"HTMLAppletElement\"]" gTypeHTMLAppletElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLAreaElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- * "GHCJS.DOM.HTMLHyperlinkElementUtils" -- -- newtype HTMLAreaElement = HTMLAreaElement { unHTMLAreaElement :: JSVal } instance Eq (HTMLAreaElement) where (HTMLAreaElement a) == (HTMLAreaElement b) = js_eq a b instance PToJSVal HTMLAreaElement where pToJSVal = unHTMLAreaElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLAreaElement where pFromJSVal = HTMLAreaElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLAreaElement where toJSVal = return . unHTMLAreaElement {-# INLINE toJSVal #-} instance FromJSVal HTMLAreaElement where fromJSVal = return . fmap HTMLAreaElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLAreaElement instance IsElement HTMLAreaElement instance IsNode HTMLAreaElement instance IsEventTarget HTMLAreaElement instance IsSlotable HTMLAreaElement instance IsParentNode HTMLAreaElement instance IsNonDocumentTypeChildNode HTMLAreaElement instance IsDocumentAndElementEventHandlers HTMLAreaElement instance IsChildNode HTMLAreaElement instance IsAnimatable HTMLAreaElement instance IsGlobalEventHandlers HTMLAreaElement instance IsElementCSSInlineStyle HTMLAreaElement instance IsHTMLHyperlinkElementUtils HTMLAreaElement instance IsGObject HTMLAreaElement where typeGType _ = gTypeHTMLAreaElement {-# INLINE typeGType #-} noHTMLAreaElement :: Maybe HTMLAreaElement noHTMLAreaElement = Nothing {-# INLINE noHTMLAreaElement #-} foreign import javascript unsafe "window[\"HTMLAreaElement\"]" gTypeHTMLAreaElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLAttachmentElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLAttachmentElement = HTMLAttachmentElement { unHTMLAttachmentElement :: JSVal } instance Eq (HTMLAttachmentElement) where (HTMLAttachmentElement a) == (HTMLAttachmentElement b) = js_eq a b instance PToJSVal HTMLAttachmentElement where pToJSVal = unHTMLAttachmentElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLAttachmentElement where pFromJSVal = HTMLAttachmentElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLAttachmentElement where toJSVal = return . unHTMLAttachmentElement {-# INLINE toJSVal #-} instance FromJSVal HTMLAttachmentElement where fromJSVal = return . fmap HTMLAttachmentElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLAttachmentElement instance IsElement HTMLAttachmentElement instance IsNode HTMLAttachmentElement instance IsEventTarget HTMLAttachmentElement instance IsSlotable HTMLAttachmentElement instance IsParentNode HTMLAttachmentElement instance IsNonDocumentTypeChildNode HTMLAttachmentElement instance IsDocumentAndElementEventHandlers HTMLAttachmentElement instance IsChildNode HTMLAttachmentElement instance IsAnimatable HTMLAttachmentElement instance IsGlobalEventHandlers HTMLAttachmentElement instance IsElementCSSInlineStyle HTMLAttachmentElement instance IsGObject HTMLAttachmentElement where typeGType _ = gTypeHTMLAttachmentElement {-# INLINE typeGType #-} noHTMLAttachmentElement :: Maybe HTMLAttachmentElement noHTMLAttachmentElement = Nothing {-# INLINE noHTMLAttachmentElement #-} foreign import javascript unsafe "window[\"HTMLAttachmentElement\"]" gTypeHTMLAttachmentElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLAudioElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLMediaElement" -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLAudioElement = HTMLAudioElement { unHTMLAudioElement :: JSVal } instance Eq (HTMLAudioElement) where (HTMLAudioElement a) == (HTMLAudioElement b) = js_eq a b instance PToJSVal HTMLAudioElement where pToJSVal = unHTMLAudioElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLAudioElement where pFromJSVal = HTMLAudioElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLAudioElement where toJSVal = return . unHTMLAudioElement {-# INLINE toJSVal #-} instance FromJSVal HTMLAudioElement where fromJSVal = return . fmap HTMLAudioElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLMediaElement HTMLAudioElement instance IsHTMLElement HTMLAudioElement instance IsElement HTMLAudioElement instance IsNode HTMLAudioElement instance IsEventTarget HTMLAudioElement instance IsSlotable HTMLAudioElement instance IsParentNode HTMLAudioElement instance IsNonDocumentTypeChildNode HTMLAudioElement instance IsDocumentAndElementEventHandlers HTMLAudioElement instance IsChildNode HTMLAudioElement instance IsAnimatable HTMLAudioElement instance IsGlobalEventHandlers HTMLAudioElement instance IsElementCSSInlineStyle HTMLAudioElement instance IsGObject HTMLAudioElement where typeGType _ = gTypeHTMLAudioElement {-# INLINE typeGType #-} noHTMLAudioElement :: Maybe HTMLAudioElement noHTMLAudioElement = Nothing {-# INLINE noHTMLAudioElement #-} foreign import javascript unsafe "window[\"HTMLAudioElement\"]" gTypeHTMLAudioElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLBRElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLBRElement = HTMLBRElement { unHTMLBRElement :: JSVal } instance Eq (HTMLBRElement) where (HTMLBRElement a) == (HTMLBRElement b) = js_eq a b instance PToJSVal HTMLBRElement where pToJSVal = unHTMLBRElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLBRElement where pFromJSVal = HTMLBRElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLBRElement where toJSVal = return . unHTMLBRElement {-# INLINE toJSVal #-} instance FromJSVal HTMLBRElement where fromJSVal = return . fmap HTMLBRElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLBRElement instance IsElement HTMLBRElement instance IsNode HTMLBRElement instance IsEventTarget HTMLBRElement instance IsSlotable HTMLBRElement instance IsParentNode HTMLBRElement instance IsNonDocumentTypeChildNode HTMLBRElement instance IsDocumentAndElementEventHandlers HTMLBRElement instance IsChildNode HTMLBRElement instance IsAnimatable HTMLBRElement instance IsGlobalEventHandlers HTMLBRElement instance IsElementCSSInlineStyle HTMLBRElement instance IsGObject HTMLBRElement where typeGType _ = gTypeHTMLBRElement {-# INLINE typeGType #-} noHTMLBRElement :: Maybe HTMLBRElement noHTMLBRElement = Nothing {-# INLINE noHTMLBRElement #-} foreign import javascript unsafe "window[\"HTMLBRElement\"]" gTypeHTMLBRElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLBaseElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLBaseElement = HTMLBaseElement { unHTMLBaseElement :: JSVal } instance Eq (HTMLBaseElement) where (HTMLBaseElement a) == (HTMLBaseElement b) = js_eq a b instance PToJSVal HTMLBaseElement where pToJSVal = unHTMLBaseElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLBaseElement where pFromJSVal = HTMLBaseElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLBaseElement where toJSVal = return . unHTMLBaseElement {-# INLINE toJSVal #-} instance FromJSVal HTMLBaseElement where fromJSVal = return . fmap HTMLBaseElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLBaseElement instance IsElement HTMLBaseElement instance IsNode HTMLBaseElement instance IsEventTarget HTMLBaseElement instance IsSlotable HTMLBaseElement instance IsParentNode HTMLBaseElement instance IsNonDocumentTypeChildNode HTMLBaseElement instance IsDocumentAndElementEventHandlers HTMLBaseElement instance IsChildNode HTMLBaseElement instance IsAnimatable HTMLBaseElement instance IsGlobalEventHandlers HTMLBaseElement instance IsElementCSSInlineStyle HTMLBaseElement instance IsGObject HTMLBaseElement where typeGType _ = gTypeHTMLBaseElement {-# INLINE typeGType #-} noHTMLBaseElement :: Maybe HTMLBaseElement noHTMLBaseElement = Nothing {-# INLINE noHTMLBaseElement #-} foreign import javascript unsafe "window[\"HTMLBaseElement\"]" gTypeHTMLBaseElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLBodyElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- * "GHCJS.DOM.WindowEventHandlers" -- -- newtype HTMLBodyElement = HTMLBodyElement { unHTMLBodyElement :: JSVal } instance Eq (HTMLBodyElement) where (HTMLBodyElement a) == (HTMLBodyElement b) = js_eq a b instance PToJSVal HTMLBodyElement where pToJSVal = unHTMLBodyElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLBodyElement where pFromJSVal = HTMLBodyElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLBodyElement where toJSVal = return . unHTMLBodyElement {-# INLINE toJSVal #-} instance FromJSVal HTMLBodyElement where fromJSVal = return . fmap HTMLBodyElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLBodyElement instance IsElement HTMLBodyElement instance IsNode HTMLBodyElement instance IsEventTarget HTMLBodyElement instance IsSlotable HTMLBodyElement instance IsParentNode HTMLBodyElement instance IsNonDocumentTypeChildNode HTMLBodyElement instance IsDocumentAndElementEventHandlers HTMLBodyElement instance IsChildNode HTMLBodyElement instance IsAnimatable HTMLBodyElement instance IsGlobalEventHandlers HTMLBodyElement instance IsElementCSSInlineStyle HTMLBodyElement instance IsWindowEventHandlers HTMLBodyElement instance IsGObject HTMLBodyElement where typeGType _ = gTypeHTMLBodyElement {-# INLINE typeGType #-} noHTMLBodyElement :: Maybe HTMLBodyElement noHTMLBodyElement = Nothing {-# INLINE noHTMLBodyElement #-} foreign import javascript unsafe "window[\"HTMLBodyElement\"]" gTypeHTMLBodyElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLButtonElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLButtonElement = HTMLButtonElement { unHTMLButtonElement :: JSVal } instance Eq (HTMLButtonElement) where (HTMLButtonElement a) == (HTMLButtonElement b) = js_eq a b instance PToJSVal HTMLButtonElement where pToJSVal = unHTMLButtonElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLButtonElement where pFromJSVal = HTMLButtonElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLButtonElement where toJSVal = return . unHTMLButtonElement {-# INLINE toJSVal #-} instance FromJSVal HTMLButtonElement where fromJSVal = return . fmap HTMLButtonElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLButtonElement instance IsElement HTMLButtonElement instance IsNode HTMLButtonElement instance IsEventTarget HTMLButtonElement instance IsSlotable HTMLButtonElement instance IsParentNode HTMLButtonElement instance IsNonDocumentTypeChildNode HTMLButtonElement instance IsDocumentAndElementEventHandlers HTMLButtonElement instance IsChildNode HTMLButtonElement instance IsAnimatable HTMLButtonElement instance IsGlobalEventHandlers HTMLButtonElement instance IsElementCSSInlineStyle HTMLButtonElement instance IsGObject HTMLButtonElement where typeGType _ = gTypeHTMLButtonElement {-# INLINE typeGType #-} noHTMLButtonElement :: Maybe HTMLButtonElement noHTMLButtonElement = Nothing {-# INLINE noHTMLButtonElement #-} foreign import javascript unsafe "window[\"HTMLButtonElement\"]" gTypeHTMLButtonElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLCanvasElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLCanvasElement = HTMLCanvasElement { unHTMLCanvasElement :: JSVal } instance Eq (HTMLCanvasElement) where (HTMLCanvasElement a) == (HTMLCanvasElement b) = js_eq a b instance PToJSVal HTMLCanvasElement where pToJSVal = unHTMLCanvasElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLCanvasElement where pFromJSVal = HTMLCanvasElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLCanvasElement where toJSVal = return . unHTMLCanvasElement {-# INLINE toJSVal #-} instance FromJSVal HTMLCanvasElement where fromJSVal = return . fmap HTMLCanvasElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLCanvasElement instance IsElement HTMLCanvasElement instance IsNode HTMLCanvasElement instance IsEventTarget HTMLCanvasElement instance IsSlotable HTMLCanvasElement instance IsParentNode HTMLCanvasElement instance IsNonDocumentTypeChildNode HTMLCanvasElement instance IsDocumentAndElementEventHandlers HTMLCanvasElement instance IsChildNode HTMLCanvasElement instance IsAnimatable HTMLCanvasElement instance IsGlobalEventHandlers HTMLCanvasElement instance IsElementCSSInlineStyle HTMLCanvasElement instance IsGObject HTMLCanvasElement where typeGType _ = gTypeHTMLCanvasElement {-# INLINE typeGType #-} noHTMLCanvasElement :: Maybe HTMLCanvasElement noHTMLCanvasElement = Nothing {-# INLINE noHTMLCanvasElement #-} foreign import javascript unsafe "window[\"HTMLCanvasElement\"]" gTypeHTMLCanvasElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLCollection". -- -- newtype HTMLCollection = HTMLCollection { unHTMLCollection :: JSVal } instance Eq (HTMLCollection) where (HTMLCollection a) == (HTMLCollection b) = js_eq a b instance PToJSVal HTMLCollection where pToJSVal = unHTMLCollection {-# INLINE pToJSVal #-} instance PFromJSVal HTMLCollection where pFromJSVal = HTMLCollection {-# INLINE pFromJSVal #-} instance ToJSVal HTMLCollection where toJSVal = return . unHTMLCollection {-# INLINE toJSVal #-} instance FromJSVal HTMLCollection where fromJSVal = return . fmap HTMLCollection . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsGObject o) => IsHTMLCollection o toHTMLCollection :: IsHTMLCollection o => o -> HTMLCollection toHTMLCollection = HTMLCollection . coerce instance IsHTMLCollection HTMLCollection instance IsGObject HTMLCollection where typeGType _ = gTypeHTMLCollection {-# INLINE typeGType #-} noHTMLCollection :: Maybe HTMLCollection noHTMLCollection = Nothing {-# INLINE noHTMLCollection #-} foreign import javascript unsafe "window[\"HTMLCollection\"]" gTypeHTMLCollection :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLDListElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLDListElement = HTMLDListElement { unHTMLDListElement :: JSVal } instance Eq (HTMLDListElement) where (HTMLDListElement a) == (HTMLDListElement b) = js_eq a b instance PToJSVal HTMLDListElement where pToJSVal = unHTMLDListElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLDListElement where pFromJSVal = HTMLDListElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLDListElement where toJSVal = return . unHTMLDListElement {-# INLINE toJSVal #-} instance FromJSVal HTMLDListElement where fromJSVal = return . fmap HTMLDListElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLDListElement instance IsElement HTMLDListElement instance IsNode HTMLDListElement instance IsEventTarget HTMLDListElement instance IsSlotable HTMLDListElement instance IsParentNode HTMLDListElement instance IsNonDocumentTypeChildNode HTMLDListElement instance IsDocumentAndElementEventHandlers HTMLDListElement instance IsChildNode HTMLDListElement instance IsAnimatable HTMLDListElement instance IsGlobalEventHandlers HTMLDListElement instance IsElementCSSInlineStyle HTMLDListElement instance IsGObject HTMLDListElement where typeGType _ = gTypeHTMLDListElement {-# INLINE typeGType #-} noHTMLDListElement :: Maybe HTMLDListElement noHTMLDListElement = Nothing {-# INLINE noHTMLDListElement #-} foreign import javascript unsafe "window[\"HTMLDListElement\"]" gTypeHTMLDListElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLDataElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLDataElement = HTMLDataElement { unHTMLDataElement :: JSVal } instance Eq (HTMLDataElement) where (HTMLDataElement a) == (HTMLDataElement b) = js_eq a b instance PToJSVal HTMLDataElement where pToJSVal = unHTMLDataElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLDataElement where pFromJSVal = HTMLDataElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLDataElement where toJSVal = return . unHTMLDataElement {-# INLINE toJSVal #-} instance FromJSVal HTMLDataElement where fromJSVal = return . fmap HTMLDataElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLDataElement instance IsElement HTMLDataElement instance IsNode HTMLDataElement instance IsEventTarget HTMLDataElement instance IsSlotable HTMLDataElement instance IsParentNode HTMLDataElement instance IsNonDocumentTypeChildNode HTMLDataElement instance IsDocumentAndElementEventHandlers HTMLDataElement instance IsChildNode HTMLDataElement instance IsAnimatable HTMLDataElement instance IsGlobalEventHandlers HTMLDataElement instance IsElementCSSInlineStyle HTMLDataElement instance IsGObject HTMLDataElement where typeGType _ = gTypeHTMLDataElement {-# INLINE typeGType #-} noHTMLDataElement :: Maybe HTMLDataElement noHTMLDataElement = Nothing {-# INLINE noHTMLDataElement #-} foreign import javascript unsafe "window[\"HTMLDataElement\"]" gTypeHTMLDataElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLDataListElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLDataListElement = HTMLDataListElement { unHTMLDataListElement :: JSVal } instance Eq (HTMLDataListElement) where (HTMLDataListElement a) == (HTMLDataListElement b) = js_eq a b instance PToJSVal HTMLDataListElement where pToJSVal = unHTMLDataListElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLDataListElement where pFromJSVal = HTMLDataListElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLDataListElement where toJSVal = return . unHTMLDataListElement {-# INLINE toJSVal #-} instance FromJSVal HTMLDataListElement where fromJSVal = return . fmap HTMLDataListElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLDataListElement instance IsElement HTMLDataListElement instance IsNode HTMLDataListElement instance IsEventTarget HTMLDataListElement instance IsSlotable HTMLDataListElement instance IsParentNode HTMLDataListElement instance IsNonDocumentTypeChildNode HTMLDataListElement instance IsDocumentAndElementEventHandlers HTMLDataListElement instance IsChildNode HTMLDataListElement instance IsAnimatable HTMLDataListElement instance IsGlobalEventHandlers HTMLDataListElement instance IsElementCSSInlineStyle HTMLDataListElement instance IsGObject HTMLDataListElement where typeGType _ = gTypeHTMLDataListElement {-# INLINE typeGType #-} noHTMLDataListElement :: Maybe HTMLDataListElement noHTMLDataListElement = Nothing {-# INLINE noHTMLDataListElement #-} foreign import javascript unsafe "window[\"HTMLDataListElement\"]" gTypeHTMLDataListElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLDetailsElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLDetailsElement = HTMLDetailsElement { unHTMLDetailsElement :: JSVal } instance Eq (HTMLDetailsElement) where (HTMLDetailsElement a) == (HTMLDetailsElement b) = js_eq a b instance PToJSVal HTMLDetailsElement where pToJSVal = unHTMLDetailsElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLDetailsElement where pFromJSVal = HTMLDetailsElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLDetailsElement where toJSVal = return . unHTMLDetailsElement {-# INLINE toJSVal #-} instance FromJSVal HTMLDetailsElement where fromJSVal = return . fmap HTMLDetailsElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLDetailsElement instance IsElement HTMLDetailsElement instance IsNode HTMLDetailsElement instance IsEventTarget HTMLDetailsElement instance IsSlotable HTMLDetailsElement instance IsParentNode HTMLDetailsElement instance IsNonDocumentTypeChildNode HTMLDetailsElement instance IsDocumentAndElementEventHandlers HTMLDetailsElement instance IsChildNode HTMLDetailsElement instance IsAnimatable HTMLDetailsElement instance IsGlobalEventHandlers HTMLDetailsElement instance IsElementCSSInlineStyle HTMLDetailsElement instance IsGObject HTMLDetailsElement where typeGType _ = gTypeHTMLDetailsElement {-# INLINE typeGType #-} noHTMLDetailsElement :: Maybe HTMLDetailsElement noHTMLDetailsElement = Nothing {-# INLINE noHTMLDetailsElement #-} foreign import javascript unsafe "window[\"HTMLDetailsElement\"]" gTypeHTMLDetailsElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLDirectoryElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLDirectoryElement = HTMLDirectoryElement { unHTMLDirectoryElement :: JSVal } instance Eq (HTMLDirectoryElement) where (HTMLDirectoryElement a) == (HTMLDirectoryElement b) = js_eq a b instance PToJSVal HTMLDirectoryElement where pToJSVal = unHTMLDirectoryElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLDirectoryElement where pFromJSVal = HTMLDirectoryElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLDirectoryElement where toJSVal = return . unHTMLDirectoryElement {-# INLINE toJSVal #-} instance FromJSVal HTMLDirectoryElement where fromJSVal = return . fmap HTMLDirectoryElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLDirectoryElement instance IsElement HTMLDirectoryElement instance IsNode HTMLDirectoryElement instance IsEventTarget HTMLDirectoryElement instance IsSlotable HTMLDirectoryElement instance IsParentNode HTMLDirectoryElement instance IsNonDocumentTypeChildNode HTMLDirectoryElement instance IsDocumentAndElementEventHandlers HTMLDirectoryElement instance IsChildNode HTMLDirectoryElement instance IsAnimatable HTMLDirectoryElement instance IsGlobalEventHandlers HTMLDirectoryElement instance IsElementCSSInlineStyle HTMLDirectoryElement instance IsGObject HTMLDirectoryElement where typeGType _ = gTypeHTMLDirectoryElement {-# INLINE typeGType #-} noHTMLDirectoryElement :: Maybe HTMLDirectoryElement noHTMLDirectoryElement = Nothing {-# INLINE noHTMLDirectoryElement #-} foreign import javascript unsafe "window[\"HTMLDirectoryElement\"]" gTypeHTMLDirectoryElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLDivElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLDivElement = HTMLDivElement { unHTMLDivElement :: JSVal } instance Eq (HTMLDivElement) where (HTMLDivElement a) == (HTMLDivElement b) = js_eq a b instance PToJSVal HTMLDivElement where pToJSVal = unHTMLDivElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLDivElement where pFromJSVal = HTMLDivElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLDivElement where toJSVal = return . unHTMLDivElement {-# INLINE toJSVal #-} instance FromJSVal HTMLDivElement where fromJSVal = return . fmap HTMLDivElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLDivElement instance IsElement HTMLDivElement instance IsNode HTMLDivElement instance IsEventTarget HTMLDivElement instance IsSlotable HTMLDivElement instance IsParentNode HTMLDivElement instance IsNonDocumentTypeChildNode HTMLDivElement instance IsDocumentAndElementEventHandlers HTMLDivElement instance IsChildNode HTMLDivElement instance IsAnimatable HTMLDivElement instance IsGlobalEventHandlers HTMLDivElement instance IsElementCSSInlineStyle HTMLDivElement instance IsGObject HTMLDivElement where typeGType _ = gTypeHTMLDivElement {-# INLINE typeGType #-} noHTMLDivElement :: Maybe HTMLDivElement noHTMLDivElement = Nothing {-# INLINE noHTMLDivElement #-} foreign import javascript unsafe "window[\"HTMLDivElement\"]" gTypeHTMLDivElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLDocument". -- Base interface functions are in: -- -- * "GHCJS.DOM.Document" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.DocumentOrShadowRoot" -- * "GHCJS.DOM.NonElementParentNode" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- -- newtype HTMLDocument = HTMLDocument { unHTMLDocument :: JSVal } instance Eq (HTMLDocument) where (HTMLDocument a) == (HTMLDocument b) = js_eq a b instance PToJSVal HTMLDocument where pToJSVal = unHTMLDocument {-# INLINE pToJSVal #-} instance PFromJSVal HTMLDocument where pFromJSVal = HTMLDocument {-# INLINE pFromJSVal #-} instance ToJSVal HTMLDocument where toJSVal = return . unHTMLDocument {-# INLINE toJSVal #-} instance FromJSVal HTMLDocument where fromJSVal = return . fmap HTMLDocument . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsDocument HTMLDocument instance IsNode HTMLDocument instance IsEventTarget HTMLDocument instance IsGlobalEventHandlers HTMLDocument instance IsDocumentOrShadowRoot HTMLDocument instance IsNonElementParentNode HTMLDocument instance IsParentNode HTMLDocument instance IsDocumentAndElementEventHandlers HTMLDocument instance IsGObject HTMLDocument where typeGType _ = gTypeHTMLDocument {-# INLINE typeGType #-} noHTMLDocument :: Maybe HTMLDocument noHTMLDocument = Nothing {-# INLINE noHTMLDocument #-} foreign import javascript unsafe "window[\"HTMLDocument\"]" gTypeHTMLDocument :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLElement = HTMLElement { unHTMLElement :: JSVal } instance Eq (HTMLElement) where (HTMLElement a) == (HTMLElement b) = js_eq a b instance PToJSVal HTMLElement where pToJSVal = unHTMLElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLElement where pFromJSVal = HTMLElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLElement where toJSVal = return . unHTMLElement {-# INLINE toJSVal #-} instance FromJSVal HTMLElement where fromJSVal = return . fmap HTMLElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsElement o, IsNode o, IsEventTarget o, IsSlotable o, IsParentNode o, IsNonDocumentTypeChildNode o, IsDocumentAndElementEventHandlers o, IsChildNode o, IsAnimatable o, IsGlobalEventHandlers o, IsElementCSSInlineStyle o, IsGObject o) => IsHTMLElement o toHTMLElement :: IsHTMLElement o => o -> HTMLElement toHTMLElement = HTMLElement . coerce instance IsHTMLElement HTMLElement instance IsElement HTMLElement instance IsNode HTMLElement instance IsEventTarget HTMLElement instance IsSlotable HTMLElement instance IsParentNode HTMLElement instance IsNonDocumentTypeChildNode HTMLElement instance IsDocumentAndElementEventHandlers HTMLElement instance IsChildNode HTMLElement instance IsAnimatable HTMLElement instance IsGlobalEventHandlers HTMLElement instance IsElementCSSInlineStyle HTMLElement instance IsGObject HTMLElement where typeGType _ = gTypeHTMLElement {-# INLINE typeGType #-} noHTMLElement :: Maybe HTMLElement noHTMLElement = Nothing {-# INLINE noHTMLElement #-} foreign import javascript unsafe "window[\"HTMLElement\"]" gTypeHTMLElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLEmbedElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLEmbedElement = HTMLEmbedElement { unHTMLEmbedElement :: JSVal } instance Eq (HTMLEmbedElement) where (HTMLEmbedElement a) == (HTMLEmbedElement b) = js_eq a b instance PToJSVal HTMLEmbedElement where pToJSVal = unHTMLEmbedElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLEmbedElement where pFromJSVal = HTMLEmbedElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLEmbedElement where toJSVal = return . unHTMLEmbedElement {-# INLINE toJSVal #-} instance FromJSVal HTMLEmbedElement where fromJSVal = return . fmap HTMLEmbedElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLEmbedElement instance IsElement HTMLEmbedElement instance IsNode HTMLEmbedElement instance IsEventTarget HTMLEmbedElement instance IsSlotable HTMLEmbedElement instance IsParentNode HTMLEmbedElement instance IsNonDocumentTypeChildNode HTMLEmbedElement instance IsDocumentAndElementEventHandlers HTMLEmbedElement instance IsChildNode HTMLEmbedElement instance IsAnimatable HTMLEmbedElement instance IsGlobalEventHandlers HTMLEmbedElement instance IsElementCSSInlineStyle HTMLEmbedElement instance IsGObject HTMLEmbedElement where typeGType _ = gTypeHTMLEmbedElement {-# INLINE typeGType #-} noHTMLEmbedElement :: Maybe HTMLEmbedElement noHTMLEmbedElement = Nothing {-# INLINE noHTMLEmbedElement #-} foreign import javascript unsafe "window[\"HTMLEmbedElement\"]" gTypeHTMLEmbedElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLFieldSetElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLFieldSetElement = HTMLFieldSetElement { unHTMLFieldSetElement :: JSVal } instance Eq (HTMLFieldSetElement) where (HTMLFieldSetElement a) == (HTMLFieldSetElement b) = js_eq a b instance PToJSVal HTMLFieldSetElement where pToJSVal = unHTMLFieldSetElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLFieldSetElement where pFromJSVal = HTMLFieldSetElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLFieldSetElement where toJSVal = return . unHTMLFieldSetElement {-# INLINE toJSVal #-} instance FromJSVal HTMLFieldSetElement where fromJSVal = return . fmap HTMLFieldSetElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLFieldSetElement instance IsElement HTMLFieldSetElement instance IsNode HTMLFieldSetElement instance IsEventTarget HTMLFieldSetElement instance IsSlotable HTMLFieldSetElement instance IsParentNode HTMLFieldSetElement instance IsNonDocumentTypeChildNode HTMLFieldSetElement instance IsDocumentAndElementEventHandlers HTMLFieldSetElement instance IsChildNode HTMLFieldSetElement instance IsAnimatable HTMLFieldSetElement instance IsGlobalEventHandlers HTMLFieldSetElement instance IsElementCSSInlineStyle HTMLFieldSetElement instance IsGObject HTMLFieldSetElement where typeGType _ = gTypeHTMLFieldSetElement {-# INLINE typeGType #-} noHTMLFieldSetElement :: Maybe HTMLFieldSetElement noHTMLFieldSetElement = Nothing {-# INLINE noHTMLFieldSetElement #-} foreign import javascript unsafe "window[\"HTMLFieldSetElement\"]" gTypeHTMLFieldSetElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLFontElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLFontElement = HTMLFontElement { unHTMLFontElement :: JSVal } instance Eq (HTMLFontElement) where (HTMLFontElement a) == (HTMLFontElement b) = js_eq a b instance PToJSVal HTMLFontElement where pToJSVal = unHTMLFontElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLFontElement where pFromJSVal = HTMLFontElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLFontElement where toJSVal = return . unHTMLFontElement {-# INLINE toJSVal #-} instance FromJSVal HTMLFontElement where fromJSVal = return . fmap HTMLFontElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLFontElement instance IsElement HTMLFontElement instance IsNode HTMLFontElement instance IsEventTarget HTMLFontElement instance IsSlotable HTMLFontElement instance IsParentNode HTMLFontElement instance IsNonDocumentTypeChildNode HTMLFontElement instance IsDocumentAndElementEventHandlers HTMLFontElement instance IsChildNode HTMLFontElement instance IsAnimatable HTMLFontElement instance IsGlobalEventHandlers HTMLFontElement instance IsElementCSSInlineStyle HTMLFontElement instance IsGObject HTMLFontElement where typeGType _ = gTypeHTMLFontElement {-# INLINE typeGType #-} noHTMLFontElement :: Maybe HTMLFontElement noHTMLFontElement = Nothing {-# INLINE noHTMLFontElement #-} foreign import javascript unsafe "window[\"HTMLFontElement\"]" gTypeHTMLFontElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLFormControlsCollection". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLCollection" -- -- newtype HTMLFormControlsCollection = HTMLFormControlsCollection { unHTMLFormControlsCollection :: JSVal } instance Eq (HTMLFormControlsCollection) where (HTMLFormControlsCollection a) == (HTMLFormControlsCollection b) = js_eq a b instance PToJSVal HTMLFormControlsCollection where pToJSVal = unHTMLFormControlsCollection {-# INLINE pToJSVal #-} instance PFromJSVal HTMLFormControlsCollection where pFromJSVal = HTMLFormControlsCollection {-# INLINE pFromJSVal #-} instance ToJSVal HTMLFormControlsCollection where toJSVal = return . unHTMLFormControlsCollection {-# INLINE toJSVal #-} instance FromJSVal HTMLFormControlsCollection where fromJSVal = return . fmap HTMLFormControlsCollection . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLCollection HTMLFormControlsCollection instance IsGObject HTMLFormControlsCollection where typeGType _ = gTypeHTMLFormControlsCollection {-# INLINE typeGType #-} noHTMLFormControlsCollection :: Maybe HTMLFormControlsCollection noHTMLFormControlsCollection = Nothing {-# INLINE noHTMLFormControlsCollection #-} foreign import javascript unsafe "window[\"HTMLFormControlsCollection\"]" gTypeHTMLFormControlsCollection :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLFormElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLFormElement = HTMLFormElement { unHTMLFormElement :: JSVal } instance Eq (HTMLFormElement) where (HTMLFormElement a) == (HTMLFormElement b) = js_eq a b instance PToJSVal HTMLFormElement where pToJSVal = unHTMLFormElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLFormElement where pFromJSVal = HTMLFormElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLFormElement where toJSVal = return . unHTMLFormElement {-# INLINE toJSVal #-} instance FromJSVal HTMLFormElement where fromJSVal = return . fmap HTMLFormElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLFormElement instance IsElement HTMLFormElement instance IsNode HTMLFormElement instance IsEventTarget HTMLFormElement instance IsSlotable HTMLFormElement instance IsParentNode HTMLFormElement instance IsNonDocumentTypeChildNode HTMLFormElement instance IsDocumentAndElementEventHandlers HTMLFormElement instance IsChildNode HTMLFormElement instance IsAnimatable HTMLFormElement instance IsGlobalEventHandlers HTMLFormElement instance IsElementCSSInlineStyle HTMLFormElement instance IsGObject HTMLFormElement where typeGType _ = gTypeHTMLFormElement {-# INLINE typeGType #-} noHTMLFormElement :: Maybe HTMLFormElement noHTMLFormElement = Nothing {-# INLINE noHTMLFormElement #-} foreign import javascript unsafe "window[\"HTMLFormElement\"]" gTypeHTMLFormElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLFrameElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLFrameElement = HTMLFrameElement { unHTMLFrameElement :: JSVal } instance Eq (HTMLFrameElement) where (HTMLFrameElement a) == (HTMLFrameElement b) = js_eq a b instance PToJSVal HTMLFrameElement where pToJSVal = unHTMLFrameElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLFrameElement where pFromJSVal = HTMLFrameElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLFrameElement where toJSVal = return . unHTMLFrameElement {-# INLINE toJSVal #-} instance FromJSVal HTMLFrameElement where fromJSVal = return . fmap HTMLFrameElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLFrameElement instance IsElement HTMLFrameElement instance IsNode HTMLFrameElement instance IsEventTarget HTMLFrameElement instance IsSlotable HTMLFrameElement instance IsParentNode HTMLFrameElement instance IsNonDocumentTypeChildNode HTMLFrameElement instance IsDocumentAndElementEventHandlers HTMLFrameElement instance IsChildNode HTMLFrameElement instance IsAnimatable HTMLFrameElement instance IsGlobalEventHandlers HTMLFrameElement instance IsElementCSSInlineStyle HTMLFrameElement instance IsGObject HTMLFrameElement where typeGType _ = gTypeHTMLFrameElement {-# INLINE typeGType #-} noHTMLFrameElement :: Maybe HTMLFrameElement noHTMLFrameElement = Nothing {-# INLINE noHTMLFrameElement #-} foreign import javascript unsafe "window[\"HTMLFrameElement\"]" gTypeHTMLFrameElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLFrameSetElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- * "GHCJS.DOM.WindowEventHandlers" -- -- newtype HTMLFrameSetElement = HTMLFrameSetElement { unHTMLFrameSetElement :: JSVal } instance Eq (HTMLFrameSetElement) where (HTMLFrameSetElement a) == (HTMLFrameSetElement b) = js_eq a b instance PToJSVal HTMLFrameSetElement where pToJSVal = unHTMLFrameSetElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLFrameSetElement where pFromJSVal = HTMLFrameSetElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLFrameSetElement where toJSVal = return . unHTMLFrameSetElement {-# INLINE toJSVal #-} instance FromJSVal HTMLFrameSetElement where fromJSVal = return . fmap HTMLFrameSetElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLFrameSetElement instance IsElement HTMLFrameSetElement instance IsNode HTMLFrameSetElement instance IsEventTarget HTMLFrameSetElement instance IsSlotable HTMLFrameSetElement instance IsParentNode HTMLFrameSetElement instance IsNonDocumentTypeChildNode HTMLFrameSetElement instance IsDocumentAndElementEventHandlers HTMLFrameSetElement instance IsChildNode HTMLFrameSetElement instance IsAnimatable HTMLFrameSetElement instance IsGlobalEventHandlers HTMLFrameSetElement instance IsElementCSSInlineStyle HTMLFrameSetElement instance IsWindowEventHandlers HTMLFrameSetElement instance IsGObject HTMLFrameSetElement where typeGType _ = gTypeHTMLFrameSetElement {-# INLINE typeGType #-} noHTMLFrameSetElement :: Maybe HTMLFrameSetElement noHTMLFrameSetElement = Nothing {-# INLINE noHTMLFrameSetElement #-} foreign import javascript unsafe "window[\"HTMLFrameSetElement\"]" gTypeHTMLFrameSetElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLHRElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLHRElement = HTMLHRElement { unHTMLHRElement :: JSVal } instance Eq (HTMLHRElement) where (HTMLHRElement a) == (HTMLHRElement b) = js_eq a b instance PToJSVal HTMLHRElement where pToJSVal = unHTMLHRElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLHRElement where pFromJSVal = HTMLHRElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLHRElement where toJSVal = return . unHTMLHRElement {-# INLINE toJSVal #-} instance FromJSVal HTMLHRElement where fromJSVal = return . fmap HTMLHRElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLHRElement instance IsElement HTMLHRElement instance IsNode HTMLHRElement instance IsEventTarget HTMLHRElement instance IsSlotable HTMLHRElement instance IsParentNode HTMLHRElement instance IsNonDocumentTypeChildNode HTMLHRElement instance IsDocumentAndElementEventHandlers HTMLHRElement instance IsChildNode HTMLHRElement instance IsAnimatable HTMLHRElement instance IsGlobalEventHandlers HTMLHRElement instance IsElementCSSInlineStyle HTMLHRElement instance IsGObject HTMLHRElement where typeGType _ = gTypeHTMLHRElement {-# INLINE typeGType #-} noHTMLHRElement :: Maybe HTMLHRElement noHTMLHRElement = Nothing {-# INLINE noHTMLHRElement #-} foreign import javascript unsafe "window[\"HTMLHRElement\"]" gTypeHTMLHRElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLHeadElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLHeadElement = HTMLHeadElement { unHTMLHeadElement :: JSVal } instance Eq (HTMLHeadElement) where (HTMLHeadElement a) == (HTMLHeadElement b) = js_eq a b instance PToJSVal HTMLHeadElement where pToJSVal = unHTMLHeadElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLHeadElement where pFromJSVal = HTMLHeadElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLHeadElement where toJSVal = return . unHTMLHeadElement {-# INLINE toJSVal #-} instance FromJSVal HTMLHeadElement where fromJSVal = return . fmap HTMLHeadElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLHeadElement instance IsElement HTMLHeadElement instance IsNode HTMLHeadElement instance IsEventTarget HTMLHeadElement instance IsSlotable HTMLHeadElement instance IsParentNode HTMLHeadElement instance IsNonDocumentTypeChildNode HTMLHeadElement instance IsDocumentAndElementEventHandlers HTMLHeadElement instance IsChildNode HTMLHeadElement instance IsAnimatable HTMLHeadElement instance IsGlobalEventHandlers HTMLHeadElement instance IsElementCSSInlineStyle HTMLHeadElement instance IsGObject HTMLHeadElement where typeGType _ = gTypeHTMLHeadElement {-# INLINE typeGType #-} noHTMLHeadElement :: Maybe HTMLHeadElement noHTMLHeadElement = Nothing {-# INLINE noHTMLHeadElement #-} foreign import javascript unsafe "window[\"HTMLHeadElement\"]" gTypeHTMLHeadElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLHeadingElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLHeadingElement = HTMLHeadingElement { unHTMLHeadingElement :: JSVal } instance Eq (HTMLHeadingElement) where (HTMLHeadingElement a) == (HTMLHeadingElement b) = js_eq a b instance PToJSVal HTMLHeadingElement where pToJSVal = unHTMLHeadingElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLHeadingElement where pFromJSVal = HTMLHeadingElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLHeadingElement where toJSVal = return . unHTMLHeadingElement {-# INLINE toJSVal #-} instance FromJSVal HTMLHeadingElement where fromJSVal = return . fmap HTMLHeadingElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLHeadingElement instance IsElement HTMLHeadingElement instance IsNode HTMLHeadingElement instance IsEventTarget HTMLHeadingElement instance IsSlotable HTMLHeadingElement instance IsParentNode HTMLHeadingElement instance IsNonDocumentTypeChildNode HTMLHeadingElement instance IsDocumentAndElementEventHandlers HTMLHeadingElement instance IsChildNode HTMLHeadingElement instance IsAnimatable HTMLHeadingElement instance IsGlobalEventHandlers HTMLHeadingElement instance IsElementCSSInlineStyle HTMLHeadingElement instance IsGObject HTMLHeadingElement where typeGType _ = gTypeHTMLHeadingElement {-# INLINE typeGType #-} noHTMLHeadingElement :: Maybe HTMLHeadingElement noHTMLHeadingElement = Nothing {-# INLINE noHTMLHeadingElement #-} foreign import javascript unsafe "window[\"HTMLHeadingElement\"]" gTypeHTMLHeadingElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLHtmlElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLHtmlElement = HTMLHtmlElement { unHTMLHtmlElement :: JSVal } instance Eq (HTMLHtmlElement) where (HTMLHtmlElement a) == (HTMLHtmlElement b) = js_eq a b instance PToJSVal HTMLHtmlElement where pToJSVal = unHTMLHtmlElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLHtmlElement where pFromJSVal = HTMLHtmlElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLHtmlElement where toJSVal = return . unHTMLHtmlElement {-# INLINE toJSVal #-} instance FromJSVal HTMLHtmlElement where fromJSVal = return . fmap HTMLHtmlElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLHtmlElement instance IsElement HTMLHtmlElement instance IsNode HTMLHtmlElement instance IsEventTarget HTMLHtmlElement instance IsSlotable HTMLHtmlElement instance IsParentNode HTMLHtmlElement instance IsNonDocumentTypeChildNode HTMLHtmlElement instance IsDocumentAndElementEventHandlers HTMLHtmlElement instance IsChildNode HTMLHtmlElement instance IsAnimatable HTMLHtmlElement instance IsGlobalEventHandlers HTMLHtmlElement instance IsElementCSSInlineStyle HTMLHtmlElement instance IsGObject HTMLHtmlElement where typeGType _ = gTypeHTMLHtmlElement {-# INLINE typeGType #-} noHTMLHtmlElement :: Maybe HTMLHtmlElement noHTMLHtmlElement = Nothing {-# INLINE noHTMLHtmlElement #-} foreign import javascript unsafe "window[\"HTMLHtmlElement\"]" gTypeHTMLHtmlElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLHyperlinkElementUtils". -- -- newtype HTMLHyperlinkElementUtils = HTMLHyperlinkElementUtils { unHTMLHyperlinkElementUtils :: JSVal } instance Eq (HTMLHyperlinkElementUtils) where (HTMLHyperlinkElementUtils a) == (HTMLHyperlinkElementUtils b) = js_eq a b instance PToJSVal HTMLHyperlinkElementUtils where pToJSVal = unHTMLHyperlinkElementUtils {-# INLINE pToJSVal #-} instance PFromJSVal HTMLHyperlinkElementUtils where pFromJSVal = HTMLHyperlinkElementUtils {-# INLINE pFromJSVal #-} instance ToJSVal HTMLHyperlinkElementUtils where toJSVal = return . unHTMLHyperlinkElementUtils {-# INLINE toJSVal #-} instance FromJSVal HTMLHyperlinkElementUtils where fromJSVal = return . fmap HTMLHyperlinkElementUtils . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsGObject o) => IsHTMLHyperlinkElementUtils o toHTMLHyperlinkElementUtils :: IsHTMLHyperlinkElementUtils o => o -> HTMLHyperlinkElementUtils toHTMLHyperlinkElementUtils = HTMLHyperlinkElementUtils . coerce instance IsHTMLHyperlinkElementUtils HTMLHyperlinkElementUtils instance IsGObject HTMLHyperlinkElementUtils where typeGType _ = gTypeHTMLHyperlinkElementUtils {-# INLINE typeGType #-} noHTMLHyperlinkElementUtils :: Maybe HTMLHyperlinkElementUtils noHTMLHyperlinkElementUtils = Nothing {-# INLINE noHTMLHyperlinkElementUtils #-} foreign import javascript unsafe "window[\"HTMLHyperlinkElementUtils\"]" gTypeHTMLHyperlinkElementUtils :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLIFrameElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLIFrameElement = HTMLIFrameElement { unHTMLIFrameElement :: JSVal } instance Eq (HTMLIFrameElement) where (HTMLIFrameElement a) == (HTMLIFrameElement b) = js_eq a b instance PToJSVal HTMLIFrameElement where pToJSVal = unHTMLIFrameElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLIFrameElement where pFromJSVal = HTMLIFrameElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLIFrameElement where toJSVal = return . unHTMLIFrameElement {-# INLINE toJSVal #-} instance FromJSVal HTMLIFrameElement where fromJSVal = return . fmap HTMLIFrameElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLIFrameElement instance IsElement HTMLIFrameElement instance IsNode HTMLIFrameElement instance IsEventTarget HTMLIFrameElement instance IsSlotable HTMLIFrameElement instance IsParentNode HTMLIFrameElement instance IsNonDocumentTypeChildNode HTMLIFrameElement instance IsDocumentAndElementEventHandlers HTMLIFrameElement instance IsChildNode HTMLIFrameElement instance IsAnimatable HTMLIFrameElement instance IsGlobalEventHandlers HTMLIFrameElement instance IsElementCSSInlineStyle HTMLIFrameElement instance IsGObject HTMLIFrameElement where typeGType _ = gTypeHTMLIFrameElement {-# INLINE typeGType #-} noHTMLIFrameElement :: Maybe HTMLIFrameElement noHTMLIFrameElement = Nothing {-# INLINE noHTMLIFrameElement #-} foreign import javascript unsafe "window[\"HTMLIFrameElement\"]" gTypeHTMLIFrameElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLImageElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLImageElement = HTMLImageElement { unHTMLImageElement :: JSVal } instance Eq (HTMLImageElement) where (HTMLImageElement a) == (HTMLImageElement b) = js_eq a b instance PToJSVal HTMLImageElement where pToJSVal = unHTMLImageElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLImageElement where pFromJSVal = HTMLImageElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLImageElement where toJSVal = return . unHTMLImageElement {-# INLINE toJSVal #-} instance FromJSVal HTMLImageElement where fromJSVal = return . fmap HTMLImageElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLImageElement instance IsElement HTMLImageElement instance IsNode HTMLImageElement instance IsEventTarget HTMLImageElement instance IsSlotable HTMLImageElement instance IsParentNode HTMLImageElement instance IsNonDocumentTypeChildNode HTMLImageElement instance IsDocumentAndElementEventHandlers HTMLImageElement instance IsChildNode HTMLImageElement instance IsAnimatable HTMLImageElement instance IsGlobalEventHandlers HTMLImageElement instance IsElementCSSInlineStyle HTMLImageElement instance IsGObject HTMLImageElement where typeGType _ = gTypeHTMLImageElement {-# INLINE typeGType #-} noHTMLImageElement :: Maybe HTMLImageElement noHTMLImageElement = Nothing {-# INLINE noHTMLImageElement #-} foreign import javascript unsafe "window[\"HTMLImageElement\"]" gTypeHTMLImageElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLInputElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLInputElement = HTMLInputElement { unHTMLInputElement :: JSVal } instance Eq (HTMLInputElement) where (HTMLInputElement a) == (HTMLInputElement b) = js_eq a b instance PToJSVal HTMLInputElement where pToJSVal = unHTMLInputElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLInputElement where pFromJSVal = HTMLInputElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLInputElement where toJSVal = return . unHTMLInputElement {-# INLINE toJSVal #-} instance FromJSVal HTMLInputElement where fromJSVal = return . fmap HTMLInputElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLInputElement instance IsElement HTMLInputElement instance IsNode HTMLInputElement instance IsEventTarget HTMLInputElement instance IsSlotable HTMLInputElement instance IsParentNode HTMLInputElement instance IsNonDocumentTypeChildNode HTMLInputElement instance IsDocumentAndElementEventHandlers HTMLInputElement instance IsChildNode HTMLInputElement instance IsAnimatable HTMLInputElement instance IsGlobalEventHandlers HTMLInputElement instance IsElementCSSInlineStyle HTMLInputElement instance IsGObject HTMLInputElement where typeGType _ = gTypeHTMLInputElement {-# INLINE typeGType #-} noHTMLInputElement :: Maybe HTMLInputElement noHTMLInputElement = Nothing {-# INLINE noHTMLInputElement #-} foreign import javascript unsafe "window[\"HTMLInputElement\"]" gTypeHTMLInputElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLKeygenElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLKeygenElement = HTMLKeygenElement { unHTMLKeygenElement :: JSVal } instance Eq (HTMLKeygenElement) where (HTMLKeygenElement a) == (HTMLKeygenElement b) = js_eq a b instance PToJSVal HTMLKeygenElement where pToJSVal = unHTMLKeygenElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLKeygenElement where pFromJSVal = HTMLKeygenElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLKeygenElement where toJSVal = return . unHTMLKeygenElement {-# INLINE toJSVal #-} instance FromJSVal HTMLKeygenElement where fromJSVal = return . fmap HTMLKeygenElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLKeygenElement instance IsElement HTMLKeygenElement instance IsNode HTMLKeygenElement instance IsEventTarget HTMLKeygenElement instance IsSlotable HTMLKeygenElement instance IsParentNode HTMLKeygenElement instance IsNonDocumentTypeChildNode HTMLKeygenElement instance IsDocumentAndElementEventHandlers HTMLKeygenElement instance IsChildNode HTMLKeygenElement instance IsAnimatable HTMLKeygenElement instance IsGlobalEventHandlers HTMLKeygenElement instance IsElementCSSInlineStyle HTMLKeygenElement instance IsGObject HTMLKeygenElement where typeGType _ = gTypeHTMLKeygenElement {-# INLINE typeGType #-} noHTMLKeygenElement :: Maybe HTMLKeygenElement noHTMLKeygenElement = Nothing {-# INLINE noHTMLKeygenElement #-} foreign import javascript unsafe "window[\"HTMLKeygenElement\"]" gTypeHTMLKeygenElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLLIElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLLIElement = HTMLLIElement { unHTMLLIElement :: JSVal } instance Eq (HTMLLIElement) where (HTMLLIElement a) == (HTMLLIElement b) = js_eq a b instance PToJSVal HTMLLIElement where pToJSVal = unHTMLLIElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLLIElement where pFromJSVal = HTMLLIElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLLIElement where toJSVal = return . unHTMLLIElement {-# INLINE toJSVal #-} instance FromJSVal HTMLLIElement where fromJSVal = return . fmap HTMLLIElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLLIElement instance IsElement HTMLLIElement instance IsNode HTMLLIElement instance IsEventTarget HTMLLIElement instance IsSlotable HTMLLIElement instance IsParentNode HTMLLIElement instance IsNonDocumentTypeChildNode HTMLLIElement instance IsDocumentAndElementEventHandlers HTMLLIElement instance IsChildNode HTMLLIElement instance IsAnimatable HTMLLIElement instance IsGlobalEventHandlers HTMLLIElement instance IsElementCSSInlineStyle HTMLLIElement instance IsGObject HTMLLIElement where typeGType _ = gTypeHTMLLIElement {-# INLINE typeGType #-} noHTMLLIElement :: Maybe HTMLLIElement noHTMLLIElement = Nothing {-# INLINE noHTMLLIElement #-} foreign import javascript unsafe "window[\"HTMLLIElement\"]" gTypeHTMLLIElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLLabelElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLLabelElement = HTMLLabelElement { unHTMLLabelElement :: JSVal } instance Eq (HTMLLabelElement) where (HTMLLabelElement a) == (HTMLLabelElement b) = js_eq a b instance PToJSVal HTMLLabelElement where pToJSVal = unHTMLLabelElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLLabelElement where pFromJSVal = HTMLLabelElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLLabelElement where toJSVal = return . unHTMLLabelElement {-# INLINE toJSVal #-} instance FromJSVal HTMLLabelElement where fromJSVal = return . fmap HTMLLabelElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLLabelElement instance IsElement HTMLLabelElement instance IsNode HTMLLabelElement instance IsEventTarget HTMLLabelElement instance IsSlotable HTMLLabelElement instance IsParentNode HTMLLabelElement instance IsNonDocumentTypeChildNode HTMLLabelElement instance IsDocumentAndElementEventHandlers HTMLLabelElement instance IsChildNode HTMLLabelElement instance IsAnimatable HTMLLabelElement instance IsGlobalEventHandlers HTMLLabelElement instance IsElementCSSInlineStyle HTMLLabelElement instance IsGObject HTMLLabelElement where typeGType _ = gTypeHTMLLabelElement {-# INLINE typeGType #-} noHTMLLabelElement :: Maybe HTMLLabelElement noHTMLLabelElement = Nothing {-# INLINE noHTMLLabelElement #-} foreign import javascript unsafe "window[\"HTMLLabelElement\"]" gTypeHTMLLabelElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLLegendElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLLegendElement = HTMLLegendElement { unHTMLLegendElement :: JSVal } instance Eq (HTMLLegendElement) where (HTMLLegendElement a) == (HTMLLegendElement b) = js_eq a b instance PToJSVal HTMLLegendElement where pToJSVal = unHTMLLegendElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLLegendElement where pFromJSVal = HTMLLegendElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLLegendElement where toJSVal = return . unHTMLLegendElement {-# INLINE toJSVal #-} instance FromJSVal HTMLLegendElement where fromJSVal = return . fmap HTMLLegendElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLLegendElement instance IsElement HTMLLegendElement instance IsNode HTMLLegendElement instance IsEventTarget HTMLLegendElement instance IsSlotable HTMLLegendElement instance IsParentNode HTMLLegendElement instance IsNonDocumentTypeChildNode HTMLLegendElement instance IsDocumentAndElementEventHandlers HTMLLegendElement instance IsChildNode HTMLLegendElement instance IsAnimatable HTMLLegendElement instance IsGlobalEventHandlers HTMLLegendElement instance IsElementCSSInlineStyle HTMLLegendElement instance IsGObject HTMLLegendElement where typeGType _ = gTypeHTMLLegendElement {-# INLINE typeGType #-} noHTMLLegendElement :: Maybe HTMLLegendElement noHTMLLegendElement = Nothing {-# INLINE noHTMLLegendElement #-} foreign import javascript unsafe "window[\"HTMLLegendElement\"]" gTypeHTMLLegendElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLLinkElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLLinkElement = HTMLLinkElement { unHTMLLinkElement :: JSVal } instance Eq (HTMLLinkElement) where (HTMLLinkElement a) == (HTMLLinkElement b) = js_eq a b instance PToJSVal HTMLLinkElement where pToJSVal = unHTMLLinkElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLLinkElement where pFromJSVal = HTMLLinkElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLLinkElement where toJSVal = return . unHTMLLinkElement {-# INLINE toJSVal #-} instance FromJSVal HTMLLinkElement where fromJSVal = return . fmap HTMLLinkElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLLinkElement instance IsElement HTMLLinkElement instance IsNode HTMLLinkElement instance IsEventTarget HTMLLinkElement instance IsSlotable HTMLLinkElement instance IsParentNode HTMLLinkElement instance IsNonDocumentTypeChildNode HTMLLinkElement instance IsDocumentAndElementEventHandlers HTMLLinkElement instance IsChildNode HTMLLinkElement instance IsAnimatable HTMLLinkElement instance IsGlobalEventHandlers HTMLLinkElement instance IsElementCSSInlineStyle HTMLLinkElement instance IsGObject HTMLLinkElement where typeGType _ = gTypeHTMLLinkElement {-# INLINE typeGType #-} noHTMLLinkElement :: Maybe HTMLLinkElement noHTMLLinkElement = Nothing {-# INLINE noHTMLLinkElement #-} foreign import javascript unsafe "window[\"HTMLLinkElement\"]" gTypeHTMLLinkElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLMapElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLMapElement = HTMLMapElement { unHTMLMapElement :: JSVal } instance Eq (HTMLMapElement) where (HTMLMapElement a) == (HTMLMapElement b) = js_eq a b instance PToJSVal HTMLMapElement where pToJSVal = unHTMLMapElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLMapElement where pFromJSVal = HTMLMapElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLMapElement where toJSVal = return . unHTMLMapElement {-# INLINE toJSVal #-} instance FromJSVal HTMLMapElement where fromJSVal = return . fmap HTMLMapElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLMapElement instance IsElement HTMLMapElement instance IsNode HTMLMapElement instance IsEventTarget HTMLMapElement instance IsSlotable HTMLMapElement instance IsParentNode HTMLMapElement instance IsNonDocumentTypeChildNode HTMLMapElement instance IsDocumentAndElementEventHandlers HTMLMapElement instance IsChildNode HTMLMapElement instance IsAnimatable HTMLMapElement instance IsGlobalEventHandlers HTMLMapElement instance IsElementCSSInlineStyle HTMLMapElement instance IsGObject HTMLMapElement where typeGType _ = gTypeHTMLMapElement {-# INLINE typeGType #-} noHTMLMapElement :: Maybe HTMLMapElement noHTMLMapElement = Nothing {-# INLINE noHTMLMapElement #-} foreign import javascript unsafe "window[\"HTMLMapElement\"]" gTypeHTMLMapElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLMarqueeElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLMarqueeElement = HTMLMarqueeElement { unHTMLMarqueeElement :: JSVal } instance Eq (HTMLMarqueeElement) where (HTMLMarqueeElement a) == (HTMLMarqueeElement b) = js_eq a b instance PToJSVal HTMLMarqueeElement where pToJSVal = unHTMLMarqueeElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLMarqueeElement where pFromJSVal = HTMLMarqueeElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLMarqueeElement where toJSVal = return . unHTMLMarqueeElement {-# INLINE toJSVal #-} instance FromJSVal HTMLMarqueeElement where fromJSVal = return . fmap HTMLMarqueeElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLMarqueeElement instance IsElement HTMLMarqueeElement instance IsNode HTMLMarqueeElement instance IsEventTarget HTMLMarqueeElement instance IsSlotable HTMLMarqueeElement instance IsParentNode HTMLMarqueeElement instance IsNonDocumentTypeChildNode HTMLMarqueeElement instance IsDocumentAndElementEventHandlers HTMLMarqueeElement instance IsChildNode HTMLMarqueeElement instance IsAnimatable HTMLMarqueeElement instance IsGlobalEventHandlers HTMLMarqueeElement instance IsElementCSSInlineStyle HTMLMarqueeElement instance IsGObject HTMLMarqueeElement where typeGType _ = gTypeHTMLMarqueeElement {-# INLINE typeGType #-} noHTMLMarqueeElement :: Maybe HTMLMarqueeElement noHTMLMarqueeElement = Nothing {-# INLINE noHTMLMarqueeElement #-} foreign import javascript unsafe "window[\"HTMLMarqueeElement\"]" gTypeHTMLMarqueeElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLMediaElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLMediaElement = HTMLMediaElement { unHTMLMediaElement :: JSVal } instance Eq (HTMLMediaElement) where (HTMLMediaElement a) == (HTMLMediaElement b) = js_eq a b instance PToJSVal HTMLMediaElement where pToJSVal = unHTMLMediaElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLMediaElement where pFromJSVal = HTMLMediaElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLMediaElement where toJSVal = return . unHTMLMediaElement {-# INLINE toJSVal #-} instance FromJSVal HTMLMediaElement where fromJSVal = return . fmap HTMLMediaElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsHTMLElement o, IsElement o, IsNode o, IsEventTarget o, IsSlotable o, IsParentNode o, IsNonDocumentTypeChildNode o, IsDocumentAndElementEventHandlers o, IsChildNode o, IsAnimatable o, IsGlobalEventHandlers o, IsElementCSSInlineStyle o, IsGObject o) => IsHTMLMediaElement o toHTMLMediaElement :: IsHTMLMediaElement o => o -> HTMLMediaElement toHTMLMediaElement = HTMLMediaElement . coerce instance IsHTMLMediaElement HTMLMediaElement instance IsHTMLElement HTMLMediaElement instance IsElement HTMLMediaElement instance IsNode HTMLMediaElement instance IsEventTarget HTMLMediaElement instance IsSlotable HTMLMediaElement instance IsParentNode HTMLMediaElement instance IsNonDocumentTypeChildNode HTMLMediaElement instance IsDocumentAndElementEventHandlers HTMLMediaElement instance IsChildNode HTMLMediaElement instance IsAnimatable HTMLMediaElement instance IsGlobalEventHandlers HTMLMediaElement instance IsElementCSSInlineStyle HTMLMediaElement instance IsGObject HTMLMediaElement where typeGType _ = gTypeHTMLMediaElement {-# INLINE typeGType #-} noHTMLMediaElement :: Maybe HTMLMediaElement noHTMLMediaElement = Nothing {-# INLINE noHTMLMediaElement #-} foreign import javascript unsafe "window[\"HTMLMediaElement\"]" gTypeHTMLMediaElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLMenuElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLMenuElement = HTMLMenuElement { unHTMLMenuElement :: JSVal } instance Eq (HTMLMenuElement) where (HTMLMenuElement a) == (HTMLMenuElement b) = js_eq a b instance PToJSVal HTMLMenuElement where pToJSVal = unHTMLMenuElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLMenuElement where pFromJSVal = HTMLMenuElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLMenuElement where toJSVal = return . unHTMLMenuElement {-# INLINE toJSVal #-} instance FromJSVal HTMLMenuElement where fromJSVal = return . fmap HTMLMenuElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLMenuElement instance IsElement HTMLMenuElement instance IsNode HTMLMenuElement instance IsEventTarget HTMLMenuElement instance IsSlotable HTMLMenuElement instance IsParentNode HTMLMenuElement instance IsNonDocumentTypeChildNode HTMLMenuElement instance IsDocumentAndElementEventHandlers HTMLMenuElement instance IsChildNode HTMLMenuElement instance IsAnimatable HTMLMenuElement instance IsGlobalEventHandlers HTMLMenuElement instance IsElementCSSInlineStyle HTMLMenuElement instance IsGObject HTMLMenuElement where typeGType _ = gTypeHTMLMenuElement {-# INLINE typeGType #-} noHTMLMenuElement :: Maybe HTMLMenuElement noHTMLMenuElement = Nothing {-# INLINE noHTMLMenuElement #-} foreign import javascript unsafe "window[\"HTMLMenuElement\"]" gTypeHTMLMenuElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLMetaElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLMetaElement = HTMLMetaElement { unHTMLMetaElement :: JSVal } instance Eq (HTMLMetaElement) where (HTMLMetaElement a) == (HTMLMetaElement b) = js_eq a b instance PToJSVal HTMLMetaElement where pToJSVal = unHTMLMetaElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLMetaElement where pFromJSVal = HTMLMetaElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLMetaElement where toJSVal = return . unHTMLMetaElement {-# INLINE toJSVal #-} instance FromJSVal HTMLMetaElement where fromJSVal = return . fmap HTMLMetaElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLMetaElement instance IsElement HTMLMetaElement instance IsNode HTMLMetaElement instance IsEventTarget HTMLMetaElement instance IsSlotable HTMLMetaElement instance IsParentNode HTMLMetaElement instance IsNonDocumentTypeChildNode HTMLMetaElement instance IsDocumentAndElementEventHandlers HTMLMetaElement instance IsChildNode HTMLMetaElement instance IsAnimatable HTMLMetaElement instance IsGlobalEventHandlers HTMLMetaElement instance IsElementCSSInlineStyle HTMLMetaElement instance IsGObject HTMLMetaElement where typeGType _ = gTypeHTMLMetaElement {-# INLINE typeGType #-} noHTMLMetaElement :: Maybe HTMLMetaElement noHTMLMetaElement = Nothing {-# INLINE noHTMLMetaElement #-} foreign import javascript unsafe "window[\"HTMLMetaElement\"]" gTypeHTMLMetaElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLMeterElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLMeterElement = HTMLMeterElement { unHTMLMeterElement :: JSVal } instance Eq (HTMLMeterElement) where (HTMLMeterElement a) == (HTMLMeterElement b) = js_eq a b instance PToJSVal HTMLMeterElement where pToJSVal = unHTMLMeterElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLMeterElement where pFromJSVal = HTMLMeterElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLMeterElement where toJSVal = return . unHTMLMeterElement {-# INLINE toJSVal #-} instance FromJSVal HTMLMeterElement where fromJSVal = return . fmap HTMLMeterElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLMeterElement instance IsElement HTMLMeterElement instance IsNode HTMLMeterElement instance IsEventTarget HTMLMeterElement instance IsSlotable HTMLMeterElement instance IsParentNode HTMLMeterElement instance IsNonDocumentTypeChildNode HTMLMeterElement instance IsDocumentAndElementEventHandlers HTMLMeterElement instance IsChildNode HTMLMeterElement instance IsAnimatable HTMLMeterElement instance IsGlobalEventHandlers HTMLMeterElement instance IsElementCSSInlineStyle HTMLMeterElement instance IsGObject HTMLMeterElement where typeGType _ = gTypeHTMLMeterElement {-# INLINE typeGType #-} noHTMLMeterElement :: Maybe HTMLMeterElement noHTMLMeterElement = Nothing {-# INLINE noHTMLMeterElement #-} foreign import javascript unsafe "window[\"HTMLMeterElement\"]" gTypeHTMLMeterElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLModElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLModElement = HTMLModElement { unHTMLModElement :: JSVal } instance Eq (HTMLModElement) where (HTMLModElement a) == (HTMLModElement b) = js_eq a b instance PToJSVal HTMLModElement where pToJSVal = unHTMLModElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLModElement where pFromJSVal = HTMLModElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLModElement where toJSVal = return . unHTMLModElement {-# INLINE toJSVal #-} instance FromJSVal HTMLModElement where fromJSVal = return . fmap HTMLModElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLModElement instance IsElement HTMLModElement instance IsNode HTMLModElement instance IsEventTarget HTMLModElement instance IsSlotable HTMLModElement instance IsParentNode HTMLModElement instance IsNonDocumentTypeChildNode HTMLModElement instance IsDocumentAndElementEventHandlers HTMLModElement instance IsChildNode HTMLModElement instance IsAnimatable HTMLModElement instance IsGlobalEventHandlers HTMLModElement instance IsElementCSSInlineStyle HTMLModElement instance IsGObject HTMLModElement where typeGType _ = gTypeHTMLModElement {-# INLINE typeGType #-} noHTMLModElement :: Maybe HTMLModElement noHTMLModElement = Nothing {-# INLINE noHTMLModElement #-} foreign import javascript unsafe "window[\"HTMLModElement\"]" gTypeHTMLModElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLOListElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLOListElement = HTMLOListElement { unHTMLOListElement :: JSVal } instance Eq (HTMLOListElement) where (HTMLOListElement a) == (HTMLOListElement b) = js_eq a b instance PToJSVal HTMLOListElement where pToJSVal = unHTMLOListElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLOListElement where pFromJSVal = HTMLOListElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLOListElement where toJSVal = return . unHTMLOListElement {-# INLINE toJSVal #-} instance FromJSVal HTMLOListElement where fromJSVal = return . fmap HTMLOListElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLOListElement instance IsElement HTMLOListElement instance IsNode HTMLOListElement instance IsEventTarget HTMLOListElement instance IsSlotable HTMLOListElement instance IsParentNode HTMLOListElement instance IsNonDocumentTypeChildNode HTMLOListElement instance IsDocumentAndElementEventHandlers HTMLOListElement instance IsChildNode HTMLOListElement instance IsAnimatable HTMLOListElement instance IsGlobalEventHandlers HTMLOListElement instance IsElementCSSInlineStyle HTMLOListElement instance IsGObject HTMLOListElement where typeGType _ = gTypeHTMLOListElement {-# INLINE typeGType #-} noHTMLOListElement :: Maybe HTMLOListElement noHTMLOListElement = Nothing {-# INLINE noHTMLOListElement #-} foreign import javascript unsafe "window[\"HTMLOListElement\"]" gTypeHTMLOListElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLObjectElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLObjectElement = HTMLObjectElement { unHTMLObjectElement :: JSVal } instance Eq (HTMLObjectElement) where (HTMLObjectElement a) == (HTMLObjectElement b) = js_eq a b instance PToJSVal HTMLObjectElement where pToJSVal = unHTMLObjectElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLObjectElement where pFromJSVal = HTMLObjectElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLObjectElement where toJSVal = return . unHTMLObjectElement {-# INLINE toJSVal #-} instance FromJSVal HTMLObjectElement where fromJSVal = return . fmap HTMLObjectElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLObjectElement instance IsElement HTMLObjectElement instance IsNode HTMLObjectElement instance IsEventTarget HTMLObjectElement instance IsSlotable HTMLObjectElement instance IsParentNode HTMLObjectElement instance IsNonDocumentTypeChildNode HTMLObjectElement instance IsDocumentAndElementEventHandlers HTMLObjectElement instance IsChildNode HTMLObjectElement instance IsAnimatable HTMLObjectElement instance IsGlobalEventHandlers HTMLObjectElement instance IsElementCSSInlineStyle HTMLObjectElement instance IsGObject HTMLObjectElement where typeGType _ = gTypeHTMLObjectElement {-# INLINE typeGType #-} noHTMLObjectElement :: Maybe HTMLObjectElement noHTMLObjectElement = Nothing {-# INLINE noHTMLObjectElement #-} foreign import javascript unsafe "window[\"HTMLObjectElement\"]" gTypeHTMLObjectElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLOptGroupElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLOptGroupElement = HTMLOptGroupElement { unHTMLOptGroupElement :: JSVal } instance Eq (HTMLOptGroupElement) where (HTMLOptGroupElement a) == (HTMLOptGroupElement b) = js_eq a b instance PToJSVal HTMLOptGroupElement where pToJSVal = unHTMLOptGroupElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLOptGroupElement where pFromJSVal = HTMLOptGroupElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLOptGroupElement where toJSVal = return . unHTMLOptGroupElement {-# INLINE toJSVal #-} instance FromJSVal HTMLOptGroupElement where fromJSVal = return . fmap HTMLOptGroupElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLOptGroupElement instance IsElement HTMLOptGroupElement instance IsNode HTMLOptGroupElement instance IsEventTarget HTMLOptGroupElement instance IsSlotable HTMLOptGroupElement instance IsParentNode HTMLOptGroupElement instance IsNonDocumentTypeChildNode HTMLOptGroupElement instance IsDocumentAndElementEventHandlers HTMLOptGroupElement instance IsChildNode HTMLOptGroupElement instance IsAnimatable HTMLOptGroupElement instance IsGlobalEventHandlers HTMLOptGroupElement instance IsElementCSSInlineStyle HTMLOptGroupElement instance IsGObject HTMLOptGroupElement where typeGType _ = gTypeHTMLOptGroupElement {-# INLINE typeGType #-} noHTMLOptGroupElement :: Maybe HTMLOptGroupElement noHTMLOptGroupElement = Nothing {-# INLINE noHTMLOptGroupElement #-} foreign import javascript unsafe "window[\"HTMLOptGroupElement\"]" gTypeHTMLOptGroupElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLOptionElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLOptionElement = HTMLOptionElement { unHTMLOptionElement :: JSVal } instance Eq (HTMLOptionElement) where (HTMLOptionElement a) == (HTMLOptionElement b) = js_eq a b instance PToJSVal HTMLOptionElement where pToJSVal = unHTMLOptionElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLOptionElement where pFromJSVal = HTMLOptionElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLOptionElement where toJSVal = return . unHTMLOptionElement {-# INLINE toJSVal #-} instance FromJSVal HTMLOptionElement where fromJSVal = return . fmap HTMLOptionElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLOptionElement instance IsElement HTMLOptionElement instance IsNode HTMLOptionElement instance IsEventTarget HTMLOptionElement instance IsSlotable HTMLOptionElement instance IsParentNode HTMLOptionElement instance IsNonDocumentTypeChildNode HTMLOptionElement instance IsDocumentAndElementEventHandlers HTMLOptionElement instance IsChildNode HTMLOptionElement instance IsAnimatable HTMLOptionElement instance IsGlobalEventHandlers HTMLOptionElement instance IsElementCSSInlineStyle HTMLOptionElement instance IsGObject HTMLOptionElement where typeGType _ = gTypeHTMLOptionElement {-# INLINE typeGType #-} noHTMLOptionElement :: Maybe HTMLOptionElement noHTMLOptionElement = Nothing {-# INLINE noHTMLOptionElement #-} foreign import javascript unsafe "window[\"HTMLOptionElement\"]" gTypeHTMLOptionElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLOptionsCollection". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLCollection" -- -- newtype HTMLOptionsCollection = HTMLOptionsCollection { unHTMLOptionsCollection :: JSVal } instance Eq (HTMLOptionsCollection) where (HTMLOptionsCollection a) == (HTMLOptionsCollection b) = js_eq a b instance PToJSVal HTMLOptionsCollection where pToJSVal = unHTMLOptionsCollection {-# INLINE pToJSVal #-} instance PFromJSVal HTMLOptionsCollection where pFromJSVal = HTMLOptionsCollection {-# INLINE pFromJSVal #-} instance ToJSVal HTMLOptionsCollection where toJSVal = return . unHTMLOptionsCollection {-# INLINE toJSVal #-} instance FromJSVal HTMLOptionsCollection where fromJSVal = return . fmap HTMLOptionsCollection . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLCollection HTMLOptionsCollection instance IsGObject HTMLOptionsCollection where typeGType _ = gTypeHTMLOptionsCollection {-# INLINE typeGType #-} noHTMLOptionsCollection :: Maybe HTMLOptionsCollection noHTMLOptionsCollection = Nothing {-# INLINE noHTMLOptionsCollection #-} foreign import javascript unsafe "window[\"HTMLOptionsCollection\"]" gTypeHTMLOptionsCollection :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLOutputElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLOutputElement = HTMLOutputElement { unHTMLOutputElement :: JSVal } instance Eq (HTMLOutputElement) where (HTMLOutputElement a) == (HTMLOutputElement b) = js_eq a b instance PToJSVal HTMLOutputElement where pToJSVal = unHTMLOutputElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLOutputElement where pFromJSVal = HTMLOutputElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLOutputElement where toJSVal = return . unHTMLOutputElement {-# INLINE toJSVal #-} instance FromJSVal HTMLOutputElement where fromJSVal = return . fmap HTMLOutputElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLOutputElement instance IsElement HTMLOutputElement instance IsNode HTMLOutputElement instance IsEventTarget HTMLOutputElement instance IsSlotable HTMLOutputElement instance IsParentNode HTMLOutputElement instance IsNonDocumentTypeChildNode HTMLOutputElement instance IsDocumentAndElementEventHandlers HTMLOutputElement instance IsChildNode HTMLOutputElement instance IsAnimatable HTMLOutputElement instance IsGlobalEventHandlers HTMLOutputElement instance IsElementCSSInlineStyle HTMLOutputElement instance IsGObject HTMLOutputElement where typeGType _ = gTypeHTMLOutputElement {-# INLINE typeGType #-} noHTMLOutputElement :: Maybe HTMLOutputElement noHTMLOutputElement = Nothing {-# INLINE noHTMLOutputElement #-} foreign import javascript unsafe "window[\"HTMLOutputElement\"]" gTypeHTMLOutputElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLParagraphElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLParagraphElement = HTMLParagraphElement { unHTMLParagraphElement :: JSVal } instance Eq (HTMLParagraphElement) where (HTMLParagraphElement a) == (HTMLParagraphElement b) = js_eq a b instance PToJSVal HTMLParagraphElement where pToJSVal = unHTMLParagraphElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLParagraphElement where pFromJSVal = HTMLParagraphElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLParagraphElement where toJSVal = return . unHTMLParagraphElement {-# INLINE toJSVal #-} instance FromJSVal HTMLParagraphElement where fromJSVal = return . fmap HTMLParagraphElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLParagraphElement instance IsElement HTMLParagraphElement instance IsNode HTMLParagraphElement instance IsEventTarget HTMLParagraphElement instance IsSlotable HTMLParagraphElement instance IsParentNode HTMLParagraphElement instance IsNonDocumentTypeChildNode HTMLParagraphElement instance IsDocumentAndElementEventHandlers HTMLParagraphElement instance IsChildNode HTMLParagraphElement instance IsAnimatable HTMLParagraphElement instance IsGlobalEventHandlers HTMLParagraphElement instance IsElementCSSInlineStyle HTMLParagraphElement instance IsGObject HTMLParagraphElement where typeGType _ = gTypeHTMLParagraphElement {-# INLINE typeGType #-} noHTMLParagraphElement :: Maybe HTMLParagraphElement noHTMLParagraphElement = Nothing {-# INLINE noHTMLParagraphElement #-} foreign import javascript unsafe "window[\"HTMLParagraphElement\"]" gTypeHTMLParagraphElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLParamElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLParamElement = HTMLParamElement { unHTMLParamElement :: JSVal } instance Eq (HTMLParamElement) where (HTMLParamElement a) == (HTMLParamElement b) = js_eq a b instance PToJSVal HTMLParamElement where pToJSVal = unHTMLParamElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLParamElement where pFromJSVal = HTMLParamElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLParamElement where toJSVal = return . unHTMLParamElement {-# INLINE toJSVal #-} instance FromJSVal HTMLParamElement where fromJSVal = return . fmap HTMLParamElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLParamElement instance IsElement HTMLParamElement instance IsNode HTMLParamElement instance IsEventTarget HTMLParamElement instance IsSlotable HTMLParamElement instance IsParentNode HTMLParamElement instance IsNonDocumentTypeChildNode HTMLParamElement instance IsDocumentAndElementEventHandlers HTMLParamElement instance IsChildNode HTMLParamElement instance IsAnimatable HTMLParamElement instance IsGlobalEventHandlers HTMLParamElement instance IsElementCSSInlineStyle HTMLParamElement instance IsGObject HTMLParamElement where typeGType _ = gTypeHTMLParamElement {-# INLINE typeGType #-} noHTMLParamElement :: Maybe HTMLParamElement noHTMLParamElement = Nothing {-# INLINE noHTMLParamElement #-} foreign import javascript unsafe "window[\"HTMLParamElement\"]" gTypeHTMLParamElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLPictureElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLPictureElement = HTMLPictureElement { unHTMLPictureElement :: JSVal } instance Eq (HTMLPictureElement) where (HTMLPictureElement a) == (HTMLPictureElement b) = js_eq a b instance PToJSVal HTMLPictureElement where pToJSVal = unHTMLPictureElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLPictureElement where pFromJSVal = HTMLPictureElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLPictureElement where toJSVal = return . unHTMLPictureElement {-# INLINE toJSVal #-} instance FromJSVal HTMLPictureElement where fromJSVal = return . fmap HTMLPictureElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLPictureElement instance IsElement HTMLPictureElement instance IsNode HTMLPictureElement instance IsEventTarget HTMLPictureElement instance IsSlotable HTMLPictureElement instance IsParentNode HTMLPictureElement instance IsNonDocumentTypeChildNode HTMLPictureElement instance IsDocumentAndElementEventHandlers HTMLPictureElement instance IsChildNode HTMLPictureElement instance IsAnimatable HTMLPictureElement instance IsGlobalEventHandlers HTMLPictureElement instance IsElementCSSInlineStyle HTMLPictureElement instance IsGObject HTMLPictureElement where typeGType _ = gTypeHTMLPictureElement {-# INLINE typeGType #-} noHTMLPictureElement :: Maybe HTMLPictureElement noHTMLPictureElement = Nothing {-# INLINE noHTMLPictureElement #-} foreign import javascript unsafe "window[\"HTMLPictureElement\"]" gTypeHTMLPictureElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLPreElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLPreElement = HTMLPreElement { unHTMLPreElement :: JSVal } instance Eq (HTMLPreElement) where (HTMLPreElement a) == (HTMLPreElement b) = js_eq a b instance PToJSVal HTMLPreElement where pToJSVal = unHTMLPreElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLPreElement where pFromJSVal = HTMLPreElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLPreElement where toJSVal = return . unHTMLPreElement {-# INLINE toJSVal #-} instance FromJSVal HTMLPreElement where fromJSVal = return . fmap HTMLPreElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLPreElement instance IsElement HTMLPreElement instance IsNode HTMLPreElement instance IsEventTarget HTMLPreElement instance IsSlotable HTMLPreElement instance IsParentNode HTMLPreElement instance IsNonDocumentTypeChildNode HTMLPreElement instance IsDocumentAndElementEventHandlers HTMLPreElement instance IsChildNode HTMLPreElement instance IsAnimatable HTMLPreElement instance IsGlobalEventHandlers HTMLPreElement instance IsElementCSSInlineStyle HTMLPreElement instance IsGObject HTMLPreElement where typeGType _ = gTypeHTMLPreElement {-# INLINE typeGType #-} noHTMLPreElement :: Maybe HTMLPreElement noHTMLPreElement = Nothing {-# INLINE noHTMLPreElement #-} foreign import javascript unsafe "window[\"HTMLPreElement\"]" gTypeHTMLPreElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLProgressElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLProgressElement = HTMLProgressElement { unHTMLProgressElement :: JSVal } instance Eq (HTMLProgressElement) where (HTMLProgressElement a) == (HTMLProgressElement b) = js_eq a b instance PToJSVal HTMLProgressElement where pToJSVal = unHTMLProgressElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLProgressElement where pFromJSVal = HTMLProgressElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLProgressElement where toJSVal = return . unHTMLProgressElement {-# INLINE toJSVal #-} instance FromJSVal HTMLProgressElement where fromJSVal = return . fmap HTMLProgressElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLProgressElement instance IsElement HTMLProgressElement instance IsNode HTMLProgressElement instance IsEventTarget HTMLProgressElement instance IsSlotable HTMLProgressElement instance IsParentNode HTMLProgressElement instance IsNonDocumentTypeChildNode HTMLProgressElement instance IsDocumentAndElementEventHandlers HTMLProgressElement instance IsChildNode HTMLProgressElement instance IsAnimatable HTMLProgressElement instance IsGlobalEventHandlers HTMLProgressElement instance IsElementCSSInlineStyle HTMLProgressElement instance IsGObject HTMLProgressElement where typeGType _ = gTypeHTMLProgressElement {-# INLINE typeGType #-} noHTMLProgressElement :: Maybe HTMLProgressElement noHTMLProgressElement = Nothing {-# INLINE noHTMLProgressElement #-} foreign import javascript unsafe "window[\"HTMLProgressElement\"]" gTypeHTMLProgressElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLQuoteElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLQuoteElement = HTMLQuoteElement { unHTMLQuoteElement :: JSVal } instance Eq (HTMLQuoteElement) where (HTMLQuoteElement a) == (HTMLQuoteElement b) = js_eq a b instance PToJSVal HTMLQuoteElement where pToJSVal = unHTMLQuoteElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLQuoteElement where pFromJSVal = HTMLQuoteElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLQuoteElement where toJSVal = return . unHTMLQuoteElement {-# INLINE toJSVal #-} instance FromJSVal HTMLQuoteElement where fromJSVal = return . fmap HTMLQuoteElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLQuoteElement instance IsElement HTMLQuoteElement instance IsNode HTMLQuoteElement instance IsEventTarget HTMLQuoteElement instance IsSlotable HTMLQuoteElement instance IsParentNode HTMLQuoteElement instance IsNonDocumentTypeChildNode HTMLQuoteElement instance IsDocumentAndElementEventHandlers HTMLQuoteElement instance IsChildNode HTMLQuoteElement instance IsAnimatable HTMLQuoteElement instance IsGlobalEventHandlers HTMLQuoteElement instance IsElementCSSInlineStyle HTMLQuoteElement instance IsGObject HTMLQuoteElement where typeGType _ = gTypeHTMLQuoteElement {-# INLINE typeGType #-} noHTMLQuoteElement :: Maybe HTMLQuoteElement noHTMLQuoteElement = Nothing {-# INLINE noHTMLQuoteElement #-} foreign import javascript unsafe "window[\"HTMLQuoteElement\"]" gTypeHTMLQuoteElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLScriptElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLScriptElement = HTMLScriptElement { unHTMLScriptElement :: JSVal } instance Eq (HTMLScriptElement) where (HTMLScriptElement a) == (HTMLScriptElement b) = js_eq a b instance PToJSVal HTMLScriptElement where pToJSVal = unHTMLScriptElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLScriptElement where pFromJSVal = HTMLScriptElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLScriptElement where toJSVal = return . unHTMLScriptElement {-# INLINE toJSVal #-} instance FromJSVal HTMLScriptElement where fromJSVal = return . fmap HTMLScriptElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLScriptElement instance IsElement HTMLScriptElement instance IsNode HTMLScriptElement instance IsEventTarget HTMLScriptElement instance IsSlotable HTMLScriptElement instance IsParentNode HTMLScriptElement instance IsNonDocumentTypeChildNode HTMLScriptElement instance IsDocumentAndElementEventHandlers HTMLScriptElement instance IsChildNode HTMLScriptElement instance IsAnimatable HTMLScriptElement instance IsGlobalEventHandlers HTMLScriptElement instance IsElementCSSInlineStyle HTMLScriptElement instance IsGObject HTMLScriptElement where typeGType _ = gTypeHTMLScriptElement {-# INLINE typeGType #-} noHTMLScriptElement :: Maybe HTMLScriptElement noHTMLScriptElement = Nothing {-# INLINE noHTMLScriptElement #-} foreign import javascript unsafe "window[\"HTMLScriptElement\"]" gTypeHTMLScriptElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLSelectElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLSelectElement = HTMLSelectElement { unHTMLSelectElement :: JSVal } instance Eq (HTMLSelectElement) where (HTMLSelectElement a) == (HTMLSelectElement b) = js_eq a b instance PToJSVal HTMLSelectElement where pToJSVal = unHTMLSelectElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLSelectElement where pFromJSVal = HTMLSelectElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLSelectElement where toJSVal = return . unHTMLSelectElement {-# INLINE toJSVal #-} instance FromJSVal HTMLSelectElement where fromJSVal = return . fmap HTMLSelectElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLSelectElement instance IsElement HTMLSelectElement instance IsNode HTMLSelectElement instance IsEventTarget HTMLSelectElement instance IsSlotable HTMLSelectElement instance IsParentNode HTMLSelectElement instance IsNonDocumentTypeChildNode HTMLSelectElement instance IsDocumentAndElementEventHandlers HTMLSelectElement instance IsChildNode HTMLSelectElement instance IsAnimatable HTMLSelectElement instance IsGlobalEventHandlers HTMLSelectElement instance IsElementCSSInlineStyle HTMLSelectElement instance IsGObject HTMLSelectElement where typeGType _ = gTypeHTMLSelectElement {-# INLINE typeGType #-} noHTMLSelectElement :: Maybe HTMLSelectElement noHTMLSelectElement = Nothing {-# INLINE noHTMLSelectElement #-} foreign import javascript unsafe "window[\"HTMLSelectElement\"]" gTypeHTMLSelectElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLSlotElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLSlotElement = HTMLSlotElement { unHTMLSlotElement :: JSVal } instance Eq (HTMLSlotElement) where (HTMLSlotElement a) == (HTMLSlotElement b) = js_eq a b instance PToJSVal HTMLSlotElement where pToJSVal = unHTMLSlotElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLSlotElement where pFromJSVal = HTMLSlotElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLSlotElement where toJSVal = return . unHTMLSlotElement {-# INLINE toJSVal #-} instance FromJSVal HTMLSlotElement where fromJSVal = return . fmap HTMLSlotElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLSlotElement instance IsElement HTMLSlotElement instance IsNode HTMLSlotElement instance IsEventTarget HTMLSlotElement instance IsSlotable HTMLSlotElement instance IsParentNode HTMLSlotElement instance IsNonDocumentTypeChildNode HTMLSlotElement instance IsDocumentAndElementEventHandlers HTMLSlotElement instance IsChildNode HTMLSlotElement instance IsAnimatable HTMLSlotElement instance IsGlobalEventHandlers HTMLSlotElement instance IsElementCSSInlineStyle HTMLSlotElement instance IsGObject HTMLSlotElement where typeGType _ = gTypeHTMLSlotElement {-# INLINE typeGType #-} noHTMLSlotElement :: Maybe HTMLSlotElement noHTMLSlotElement = Nothing {-# INLINE noHTMLSlotElement #-} foreign import javascript unsafe "window[\"HTMLSlotElement\"]" gTypeHTMLSlotElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLSourceElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLSourceElement = HTMLSourceElement { unHTMLSourceElement :: JSVal } instance Eq (HTMLSourceElement) where (HTMLSourceElement a) == (HTMLSourceElement b) = js_eq a b instance PToJSVal HTMLSourceElement where pToJSVal = unHTMLSourceElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLSourceElement where pFromJSVal = HTMLSourceElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLSourceElement where toJSVal = return . unHTMLSourceElement {-# INLINE toJSVal #-} instance FromJSVal HTMLSourceElement where fromJSVal = return . fmap HTMLSourceElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLSourceElement instance IsElement HTMLSourceElement instance IsNode HTMLSourceElement instance IsEventTarget HTMLSourceElement instance IsSlotable HTMLSourceElement instance IsParentNode HTMLSourceElement instance IsNonDocumentTypeChildNode HTMLSourceElement instance IsDocumentAndElementEventHandlers HTMLSourceElement instance IsChildNode HTMLSourceElement instance IsAnimatable HTMLSourceElement instance IsGlobalEventHandlers HTMLSourceElement instance IsElementCSSInlineStyle HTMLSourceElement instance IsGObject HTMLSourceElement where typeGType _ = gTypeHTMLSourceElement {-# INLINE typeGType #-} noHTMLSourceElement :: Maybe HTMLSourceElement noHTMLSourceElement = Nothing {-# INLINE noHTMLSourceElement #-} foreign import javascript unsafe "window[\"HTMLSourceElement\"]" gTypeHTMLSourceElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLSpanElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLSpanElement = HTMLSpanElement { unHTMLSpanElement :: JSVal } instance Eq (HTMLSpanElement) where (HTMLSpanElement a) == (HTMLSpanElement b) = js_eq a b instance PToJSVal HTMLSpanElement where pToJSVal = unHTMLSpanElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLSpanElement where pFromJSVal = HTMLSpanElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLSpanElement where toJSVal = return . unHTMLSpanElement {-# INLINE toJSVal #-} instance FromJSVal HTMLSpanElement where fromJSVal = return . fmap HTMLSpanElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLSpanElement instance IsElement HTMLSpanElement instance IsNode HTMLSpanElement instance IsEventTarget HTMLSpanElement instance IsSlotable HTMLSpanElement instance IsParentNode HTMLSpanElement instance IsNonDocumentTypeChildNode HTMLSpanElement instance IsDocumentAndElementEventHandlers HTMLSpanElement instance IsChildNode HTMLSpanElement instance IsAnimatable HTMLSpanElement instance IsGlobalEventHandlers HTMLSpanElement instance IsElementCSSInlineStyle HTMLSpanElement instance IsGObject HTMLSpanElement where typeGType _ = gTypeHTMLSpanElement {-# INLINE typeGType #-} noHTMLSpanElement :: Maybe HTMLSpanElement noHTMLSpanElement = Nothing {-# INLINE noHTMLSpanElement #-} foreign import javascript unsafe "window[\"HTMLSpanElement\"]" gTypeHTMLSpanElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLStyleElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLStyleElement = HTMLStyleElement { unHTMLStyleElement :: JSVal } instance Eq (HTMLStyleElement) where (HTMLStyleElement a) == (HTMLStyleElement b) = js_eq a b instance PToJSVal HTMLStyleElement where pToJSVal = unHTMLStyleElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLStyleElement where pFromJSVal = HTMLStyleElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLStyleElement where toJSVal = return . unHTMLStyleElement {-# INLINE toJSVal #-} instance FromJSVal HTMLStyleElement where fromJSVal = return . fmap HTMLStyleElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLStyleElement instance IsElement HTMLStyleElement instance IsNode HTMLStyleElement instance IsEventTarget HTMLStyleElement instance IsSlotable HTMLStyleElement instance IsParentNode HTMLStyleElement instance IsNonDocumentTypeChildNode HTMLStyleElement instance IsDocumentAndElementEventHandlers HTMLStyleElement instance IsChildNode HTMLStyleElement instance IsAnimatable HTMLStyleElement instance IsGlobalEventHandlers HTMLStyleElement instance IsElementCSSInlineStyle HTMLStyleElement instance IsGObject HTMLStyleElement where typeGType _ = gTypeHTMLStyleElement {-# INLINE typeGType #-} noHTMLStyleElement :: Maybe HTMLStyleElement noHTMLStyleElement = Nothing {-# INLINE noHTMLStyleElement #-} foreign import javascript unsafe "window[\"HTMLStyleElement\"]" gTypeHTMLStyleElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLTableCaptionElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLTableCaptionElement = HTMLTableCaptionElement { unHTMLTableCaptionElement :: JSVal } instance Eq (HTMLTableCaptionElement) where (HTMLTableCaptionElement a) == (HTMLTableCaptionElement b) = js_eq a b instance PToJSVal HTMLTableCaptionElement where pToJSVal = unHTMLTableCaptionElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLTableCaptionElement where pFromJSVal = HTMLTableCaptionElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLTableCaptionElement where toJSVal = return . unHTMLTableCaptionElement {-# INLINE toJSVal #-} instance FromJSVal HTMLTableCaptionElement where fromJSVal = return . fmap HTMLTableCaptionElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLTableCaptionElement instance IsElement HTMLTableCaptionElement instance IsNode HTMLTableCaptionElement instance IsEventTarget HTMLTableCaptionElement instance IsSlotable HTMLTableCaptionElement instance IsParentNode HTMLTableCaptionElement instance IsNonDocumentTypeChildNode HTMLTableCaptionElement instance IsDocumentAndElementEventHandlers HTMLTableCaptionElement instance IsChildNode HTMLTableCaptionElement instance IsAnimatable HTMLTableCaptionElement instance IsGlobalEventHandlers HTMLTableCaptionElement instance IsElementCSSInlineStyle HTMLTableCaptionElement instance IsGObject HTMLTableCaptionElement where typeGType _ = gTypeHTMLTableCaptionElement {-# INLINE typeGType #-} noHTMLTableCaptionElement :: Maybe HTMLTableCaptionElement noHTMLTableCaptionElement = Nothing {-# INLINE noHTMLTableCaptionElement #-} foreign import javascript unsafe "window[\"HTMLTableCaptionElement\"]" gTypeHTMLTableCaptionElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLTableCellElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLTableCellElement = HTMLTableCellElement { unHTMLTableCellElement :: JSVal } instance Eq (HTMLTableCellElement) where (HTMLTableCellElement a) == (HTMLTableCellElement b) = js_eq a b instance PToJSVal HTMLTableCellElement where pToJSVal = unHTMLTableCellElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLTableCellElement where pFromJSVal = HTMLTableCellElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLTableCellElement where toJSVal = return . unHTMLTableCellElement {-# INLINE toJSVal #-} instance FromJSVal HTMLTableCellElement where fromJSVal = return . fmap HTMLTableCellElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLTableCellElement instance IsElement HTMLTableCellElement instance IsNode HTMLTableCellElement instance IsEventTarget HTMLTableCellElement instance IsSlotable HTMLTableCellElement instance IsParentNode HTMLTableCellElement instance IsNonDocumentTypeChildNode HTMLTableCellElement instance IsDocumentAndElementEventHandlers HTMLTableCellElement instance IsChildNode HTMLTableCellElement instance IsAnimatable HTMLTableCellElement instance IsGlobalEventHandlers HTMLTableCellElement instance IsElementCSSInlineStyle HTMLTableCellElement instance IsGObject HTMLTableCellElement where typeGType _ = gTypeHTMLTableCellElement {-# INLINE typeGType #-} noHTMLTableCellElement :: Maybe HTMLTableCellElement noHTMLTableCellElement = Nothing {-# INLINE noHTMLTableCellElement #-} foreign import javascript unsafe "window[\"HTMLTableCellElement\"]" gTypeHTMLTableCellElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLTableColElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLTableColElement = HTMLTableColElement { unHTMLTableColElement :: JSVal } instance Eq (HTMLTableColElement) where (HTMLTableColElement a) == (HTMLTableColElement b) = js_eq a b instance PToJSVal HTMLTableColElement where pToJSVal = unHTMLTableColElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLTableColElement where pFromJSVal = HTMLTableColElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLTableColElement where toJSVal = return . unHTMLTableColElement {-# INLINE toJSVal #-} instance FromJSVal HTMLTableColElement where fromJSVal = return . fmap HTMLTableColElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLTableColElement instance IsElement HTMLTableColElement instance IsNode HTMLTableColElement instance IsEventTarget HTMLTableColElement instance IsSlotable HTMLTableColElement instance IsParentNode HTMLTableColElement instance IsNonDocumentTypeChildNode HTMLTableColElement instance IsDocumentAndElementEventHandlers HTMLTableColElement instance IsChildNode HTMLTableColElement instance IsAnimatable HTMLTableColElement instance IsGlobalEventHandlers HTMLTableColElement instance IsElementCSSInlineStyle HTMLTableColElement instance IsGObject HTMLTableColElement where typeGType _ = gTypeHTMLTableColElement {-# INLINE typeGType #-} noHTMLTableColElement :: Maybe HTMLTableColElement noHTMLTableColElement = Nothing {-# INLINE noHTMLTableColElement #-} foreign import javascript unsafe "window[\"HTMLTableColElement\"]" gTypeHTMLTableColElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLTableElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLTableElement = HTMLTableElement { unHTMLTableElement :: JSVal } instance Eq (HTMLTableElement) where (HTMLTableElement a) == (HTMLTableElement b) = js_eq a b instance PToJSVal HTMLTableElement where pToJSVal = unHTMLTableElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLTableElement where pFromJSVal = HTMLTableElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLTableElement where toJSVal = return . unHTMLTableElement {-# INLINE toJSVal #-} instance FromJSVal HTMLTableElement where fromJSVal = return . fmap HTMLTableElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLTableElement instance IsElement HTMLTableElement instance IsNode HTMLTableElement instance IsEventTarget HTMLTableElement instance IsSlotable HTMLTableElement instance IsParentNode HTMLTableElement instance IsNonDocumentTypeChildNode HTMLTableElement instance IsDocumentAndElementEventHandlers HTMLTableElement instance IsChildNode HTMLTableElement instance IsAnimatable HTMLTableElement instance IsGlobalEventHandlers HTMLTableElement instance IsElementCSSInlineStyle HTMLTableElement instance IsGObject HTMLTableElement where typeGType _ = gTypeHTMLTableElement {-# INLINE typeGType #-} noHTMLTableElement :: Maybe HTMLTableElement noHTMLTableElement = Nothing {-# INLINE noHTMLTableElement #-} foreign import javascript unsafe "window[\"HTMLTableElement\"]" gTypeHTMLTableElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLTableRowElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLTableRowElement = HTMLTableRowElement { unHTMLTableRowElement :: JSVal } instance Eq (HTMLTableRowElement) where (HTMLTableRowElement a) == (HTMLTableRowElement b) = js_eq a b instance PToJSVal HTMLTableRowElement where pToJSVal = unHTMLTableRowElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLTableRowElement where pFromJSVal = HTMLTableRowElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLTableRowElement where toJSVal = return . unHTMLTableRowElement {-# INLINE toJSVal #-} instance FromJSVal HTMLTableRowElement where fromJSVal = return . fmap HTMLTableRowElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLTableRowElement instance IsElement HTMLTableRowElement instance IsNode HTMLTableRowElement instance IsEventTarget HTMLTableRowElement instance IsSlotable HTMLTableRowElement instance IsParentNode HTMLTableRowElement instance IsNonDocumentTypeChildNode HTMLTableRowElement instance IsDocumentAndElementEventHandlers HTMLTableRowElement instance IsChildNode HTMLTableRowElement instance IsAnimatable HTMLTableRowElement instance IsGlobalEventHandlers HTMLTableRowElement instance IsElementCSSInlineStyle HTMLTableRowElement instance IsGObject HTMLTableRowElement where typeGType _ = gTypeHTMLTableRowElement {-# INLINE typeGType #-} noHTMLTableRowElement :: Maybe HTMLTableRowElement noHTMLTableRowElement = Nothing {-# INLINE noHTMLTableRowElement #-} foreign import javascript unsafe "window[\"HTMLTableRowElement\"]" gTypeHTMLTableRowElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLTableSectionElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLTableSectionElement = HTMLTableSectionElement { unHTMLTableSectionElement :: JSVal } instance Eq (HTMLTableSectionElement) where (HTMLTableSectionElement a) == (HTMLTableSectionElement b) = js_eq a b instance PToJSVal HTMLTableSectionElement where pToJSVal = unHTMLTableSectionElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLTableSectionElement where pFromJSVal = HTMLTableSectionElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLTableSectionElement where toJSVal = return . unHTMLTableSectionElement {-# INLINE toJSVal #-} instance FromJSVal HTMLTableSectionElement where fromJSVal = return . fmap HTMLTableSectionElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLTableSectionElement instance IsElement HTMLTableSectionElement instance IsNode HTMLTableSectionElement instance IsEventTarget HTMLTableSectionElement instance IsSlotable HTMLTableSectionElement instance IsParentNode HTMLTableSectionElement instance IsNonDocumentTypeChildNode HTMLTableSectionElement instance IsDocumentAndElementEventHandlers HTMLTableSectionElement instance IsChildNode HTMLTableSectionElement instance IsAnimatable HTMLTableSectionElement instance IsGlobalEventHandlers HTMLTableSectionElement instance IsElementCSSInlineStyle HTMLTableSectionElement instance IsGObject HTMLTableSectionElement where typeGType _ = gTypeHTMLTableSectionElement {-# INLINE typeGType #-} noHTMLTableSectionElement :: Maybe HTMLTableSectionElement noHTMLTableSectionElement = Nothing {-# INLINE noHTMLTableSectionElement #-} foreign import javascript unsafe "window[\"HTMLTableSectionElement\"]" gTypeHTMLTableSectionElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLTemplateElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLTemplateElement = HTMLTemplateElement { unHTMLTemplateElement :: JSVal } instance Eq (HTMLTemplateElement) where (HTMLTemplateElement a) == (HTMLTemplateElement b) = js_eq a b instance PToJSVal HTMLTemplateElement where pToJSVal = unHTMLTemplateElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLTemplateElement where pFromJSVal = HTMLTemplateElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLTemplateElement where toJSVal = return . unHTMLTemplateElement {-# INLINE toJSVal #-} instance FromJSVal HTMLTemplateElement where fromJSVal = return . fmap HTMLTemplateElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLTemplateElement instance IsElement HTMLTemplateElement instance IsNode HTMLTemplateElement instance IsEventTarget HTMLTemplateElement instance IsSlotable HTMLTemplateElement instance IsParentNode HTMLTemplateElement instance IsNonDocumentTypeChildNode HTMLTemplateElement instance IsDocumentAndElementEventHandlers HTMLTemplateElement instance IsChildNode HTMLTemplateElement instance IsAnimatable HTMLTemplateElement instance IsGlobalEventHandlers HTMLTemplateElement instance IsElementCSSInlineStyle HTMLTemplateElement instance IsGObject HTMLTemplateElement where typeGType _ = gTypeHTMLTemplateElement {-# INLINE typeGType #-} noHTMLTemplateElement :: Maybe HTMLTemplateElement noHTMLTemplateElement = Nothing {-# INLINE noHTMLTemplateElement #-} foreign import javascript unsafe "window[\"HTMLTemplateElement\"]" gTypeHTMLTemplateElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLTextAreaElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLTextAreaElement = HTMLTextAreaElement { unHTMLTextAreaElement :: JSVal } instance Eq (HTMLTextAreaElement) where (HTMLTextAreaElement a) == (HTMLTextAreaElement b) = js_eq a b instance PToJSVal HTMLTextAreaElement where pToJSVal = unHTMLTextAreaElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLTextAreaElement where pFromJSVal = HTMLTextAreaElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLTextAreaElement where toJSVal = return . unHTMLTextAreaElement {-# INLINE toJSVal #-} instance FromJSVal HTMLTextAreaElement where fromJSVal = return . fmap HTMLTextAreaElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLTextAreaElement instance IsElement HTMLTextAreaElement instance IsNode HTMLTextAreaElement instance IsEventTarget HTMLTextAreaElement instance IsSlotable HTMLTextAreaElement instance IsParentNode HTMLTextAreaElement instance IsNonDocumentTypeChildNode HTMLTextAreaElement instance IsDocumentAndElementEventHandlers HTMLTextAreaElement instance IsChildNode HTMLTextAreaElement instance IsAnimatable HTMLTextAreaElement instance IsGlobalEventHandlers HTMLTextAreaElement instance IsElementCSSInlineStyle HTMLTextAreaElement instance IsGObject HTMLTextAreaElement where typeGType _ = gTypeHTMLTextAreaElement {-# INLINE typeGType #-} noHTMLTextAreaElement :: Maybe HTMLTextAreaElement noHTMLTextAreaElement = Nothing {-# INLINE noHTMLTextAreaElement #-} foreign import javascript unsafe "window[\"HTMLTextAreaElement\"]" gTypeHTMLTextAreaElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLTimeElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLTimeElement = HTMLTimeElement { unHTMLTimeElement :: JSVal } instance Eq (HTMLTimeElement) where (HTMLTimeElement a) == (HTMLTimeElement b) = js_eq a b instance PToJSVal HTMLTimeElement where pToJSVal = unHTMLTimeElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLTimeElement where pFromJSVal = HTMLTimeElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLTimeElement where toJSVal = return . unHTMLTimeElement {-# INLINE toJSVal #-} instance FromJSVal HTMLTimeElement where fromJSVal = return . fmap HTMLTimeElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLTimeElement instance IsElement HTMLTimeElement instance IsNode HTMLTimeElement instance IsEventTarget HTMLTimeElement instance IsSlotable HTMLTimeElement instance IsParentNode HTMLTimeElement instance IsNonDocumentTypeChildNode HTMLTimeElement instance IsDocumentAndElementEventHandlers HTMLTimeElement instance IsChildNode HTMLTimeElement instance IsAnimatable HTMLTimeElement instance IsGlobalEventHandlers HTMLTimeElement instance IsElementCSSInlineStyle HTMLTimeElement instance IsGObject HTMLTimeElement where typeGType _ = gTypeHTMLTimeElement {-# INLINE typeGType #-} noHTMLTimeElement :: Maybe HTMLTimeElement noHTMLTimeElement = Nothing {-# INLINE noHTMLTimeElement #-} foreign import javascript unsafe "window[\"HTMLTimeElement\"]" gTypeHTMLTimeElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLTitleElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLTitleElement = HTMLTitleElement { unHTMLTitleElement :: JSVal } instance Eq (HTMLTitleElement) where (HTMLTitleElement a) == (HTMLTitleElement b) = js_eq a b instance PToJSVal HTMLTitleElement where pToJSVal = unHTMLTitleElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLTitleElement where pFromJSVal = HTMLTitleElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLTitleElement where toJSVal = return . unHTMLTitleElement {-# INLINE toJSVal #-} instance FromJSVal HTMLTitleElement where fromJSVal = return . fmap HTMLTitleElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLTitleElement instance IsElement HTMLTitleElement instance IsNode HTMLTitleElement instance IsEventTarget HTMLTitleElement instance IsSlotable HTMLTitleElement instance IsParentNode HTMLTitleElement instance IsNonDocumentTypeChildNode HTMLTitleElement instance IsDocumentAndElementEventHandlers HTMLTitleElement instance IsChildNode HTMLTitleElement instance IsAnimatable HTMLTitleElement instance IsGlobalEventHandlers HTMLTitleElement instance IsElementCSSInlineStyle HTMLTitleElement instance IsGObject HTMLTitleElement where typeGType _ = gTypeHTMLTitleElement {-# INLINE typeGType #-} noHTMLTitleElement :: Maybe HTMLTitleElement noHTMLTitleElement = Nothing {-# INLINE noHTMLTitleElement #-} foreign import javascript unsafe "window[\"HTMLTitleElement\"]" gTypeHTMLTitleElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLTrackElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLTrackElement = HTMLTrackElement { unHTMLTrackElement :: JSVal } instance Eq (HTMLTrackElement) where (HTMLTrackElement a) == (HTMLTrackElement b) = js_eq a b instance PToJSVal HTMLTrackElement where pToJSVal = unHTMLTrackElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLTrackElement where pFromJSVal = HTMLTrackElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLTrackElement where toJSVal = return . unHTMLTrackElement {-# INLINE toJSVal #-} instance FromJSVal HTMLTrackElement where fromJSVal = return . fmap HTMLTrackElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLTrackElement instance IsElement HTMLTrackElement instance IsNode HTMLTrackElement instance IsEventTarget HTMLTrackElement instance IsSlotable HTMLTrackElement instance IsParentNode HTMLTrackElement instance IsNonDocumentTypeChildNode HTMLTrackElement instance IsDocumentAndElementEventHandlers HTMLTrackElement instance IsChildNode HTMLTrackElement instance IsAnimatable HTMLTrackElement instance IsGlobalEventHandlers HTMLTrackElement instance IsElementCSSInlineStyle HTMLTrackElement instance IsGObject HTMLTrackElement where typeGType _ = gTypeHTMLTrackElement {-# INLINE typeGType #-} noHTMLTrackElement :: Maybe HTMLTrackElement noHTMLTrackElement = Nothing {-# INLINE noHTMLTrackElement #-} foreign import javascript unsafe "window[\"HTMLTrackElement\"]" gTypeHTMLTrackElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLUListElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLUListElement = HTMLUListElement { unHTMLUListElement :: JSVal } instance Eq (HTMLUListElement) where (HTMLUListElement a) == (HTMLUListElement b) = js_eq a b instance PToJSVal HTMLUListElement where pToJSVal = unHTMLUListElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLUListElement where pFromJSVal = HTMLUListElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLUListElement where toJSVal = return . unHTMLUListElement {-# INLINE toJSVal #-} instance FromJSVal HTMLUListElement where fromJSVal = return . fmap HTMLUListElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLUListElement instance IsElement HTMLUListElement instance IsNode HTMLUListElement instance IsEventTarget HTMLUListElement instance IsSlotable HTMLUListElement instance IsParentNode HTMLUListElement instance IsNonDocumentTypeChildNode HTMLUListElement instance IsDocumentAndElementEventHandlers HTMLUListElement instance IsChildNode HTMLUListElement instance IsAnimatable HTMLUListElement instance IsGlobalEventHandlers HTMLUListElement instance IsElementCSSInlineStyle HTMLUListElement instance IsGObject HTMLUListElement where typeGType _ = gTypeHTMLUListElement {-# INLINE typeGType #-} noHTMLUListElement :: Maybe HTMLUListElement noHTMLUListElement = Nothing {-# INLINE noHTMLUListElement #-} foreign import javascript unsafe "window[\"HTMLUListElement\"]" gTypeHTMLUListElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLUnknownElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLUnknownElement = HTMLUnknownElement { unHTMLUnknownElement :: JSVal } instance Eq (HTMLUnknownElement) where (HTMLUnknownElement a) == (HTMLUnknownElement b) = js_eq a b instance PToJSVal HTMLUnknownElement where pToJSVal = unHTMLUnknownElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLUnknownElement where pFromJSVal = HTMLUnknownElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLUnknownElement where toJSVal = return . unHTMLUnknownElement {-# INLINE toJSVal #-} instance FromJSVal HTMLUnknownElement where fromJSVal = return . fmap HTMLUnknownElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLElement HTMLUnknownElement instance IsElement HTMLUnknownElement instance IsNode HTMLUnknownElement instance IsEventTarget HTMLUnknownElement instance IsSlotable HTMLUnknownElement instance IsParentNode HTMLUnknownElement instance IsNonDocumentTypeChildNode HTMLUnknownElement instance IsDocumentAndElementEventHandlers HTMLUnknownElement instance IsChildNode HTMLUnknownElement instance IsAnimatable HTMLUnknownElement instance IsGlobalEventHandlers HTMLUnknownElement instance IsElementCSSInlineStyle HTMLUnknownElement instance IsGObject HTMLUnknownElement where typeGType _ = gTypeHTMLUnknownElement {-# INLINE typeGType #-} noHTMLUnknownElement :: Maybe HTMLUnknownElement noHTMLUnknownElement = Nothing {-# INLINE noHTMLUnknownElement #-} foreign import javascript unsafe "window[\"HTMLUnknownElement\"]" gTypeHTMLUnknownElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HTMLVideoElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.HTMLMediaElement" -- * "GHCJS.DOM.HTMLElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype HTMLVideoElement = HTMLVideoElement { unHTMLVideoElement :: JSVal } instance Eq (HTMLVideoElement) where (HTMLVideoElement a) == (HTMLVideoElement b) = js_eq a b instance PToJSVal HTMLVideoElement where pToJSVal = unHTMLVideoElement {-# INLINE pToJSVal #-} instance PFromJSVal HTMLVideoElement where pFromJSVal = HTMLVideoElement {-# INLINE pFromJSVal #-} instance ToJSVal HTMLVideoElement where toJSVal = return . unHTMLVideoElement {-# INLINE toJSVal #-} instance FromJSVal HTMLVideoElement where fromJSVal = return . fmap HTMLVideoElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsHTMLMediaElement HTMLVideoElement instance IsHTMLElement HTMLVideoElement instance IsElement HTMLVideoElement instance IsNode HTMLVideoElement instance IsEventTarget HTMLVideoElement instance IsSlotable HTMLVideoElement instance IsParentNode HTMLVideoElement instance IsNonDocumentTypeChildNode HTMLVideoElement instance IsDocumentAndElementEventHandlers HTMLVideoElement instance IsChildNode HTMLVideoElement instance IsAnimatable HTMLVideoElement instance IsGlobalEventHandlers HTMLVideoElement instance IsElementCSSInlineStyle HTMLVideoElement instance IsGObject HTMLVideoElement where typeGType _ = gTypeHTMLVideoElement {-# INLINE typeGType #-} noHTMLVideoElement :: Maybe HTMLVideoElement noHTMLVideoElement = Nothing {-# INLINE noHTMLVideoElement #-} foreign import javascript unsafe "window[\"HTMLVideoElement\"]" gTypeHTMLVideoElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.HashChangeEvent". -- Base interface functions are in: -- -- * "GHCJS.DOM.Event" -- -- newtype HashChangeEvent = HashChangeEvent { unHashChangeEvent :: JSVal } instance Eq (HashChangeEvent) where (HashChangeEvent a) == (HashChangeEvent b) = js_eq a b instance PToJSVal HashChangeEvent where pToJSVal = unHashChangeEvent {-# INLINE pToJSVal #-} instance PFromJSVal HashChangeEvent where pFromJSVal = HashChangeEvent {-# INLINE pFromJSVal #-} instance ToJSVal HashChangeEvent where toJSVal = return . unHashChangeEvent {-# INLINE toJSVal #-} instance FromJSVal HashChangeEvent where fromJSVal = return . fmap HashChangeEvent . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEvent HashChangeEvent instance IsGObject HashChangeEvent where typeGType _ = gTypeHashChangeEvent {-# INLINE typeGType #-} noHashChangeEvent :: Maybe HashChangeEvent noHashChangeEvent = Nothing {-# INLINE noHashChangeEvent #-} foreign import javascript unsafe "window[\"HashChangeEvent\"]" gTypeHashChangeEvent :: GType -- | Functions for this inteface are in "GHCJS.DOM.HashChangeEventInit". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventInit" -- -- newtype HashChangeEventInit = HashChangeEventInit { unHashChangeEventInit :: JSVal } instance Eq (HashChangeEventInit) where (HashChangeEventInit a) == (HashChangeEventInit b) = js_eq a b instance PToJSVal HashChangeEventInit where pToJSVal = unHashChangeEventInit {-# INLINE pToJSVal #-} instance PFromJSVal HashChangeEventInit where pFromJSVal = HashChangeEventInit {-# INLINE pFromJSVal #-} instance ToJSVal HashChangeEventInit where toJSVal = return . unHashChangeEventInit {-# INLINE toJSVal #-} instance FromJSVal HashChangeEventInit where fromJSVal = return . fmap HashChangeEventInit . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventInit HashChangeEventInit instance IsGObject HashChangeEventInit where typeGType _ = gTypeHashChangeEventInit {-# INLINE typeGType #-} noHashChangeEventInit :: Maybe HashChangeEventInit noHashChangeEventInit = Nothing {-# INLINE noHashChangeEventInit #-} foreign import javascript unsafe "window[\"HashChangeEventInit\"]" gTypeHashChangeEventInit :: GType -- | Functions for this inteface are in "GHCJS.DOM.Headers". -- -- newtype Headers = Headers { unHeaders :: JSVal } instance Eq (Headers) where (Headers a) == (Headers b) = js_eq a b instance PToJSVal Headers where pToJSVal = unHeaders {-# INLINE pToJSVal #-} instance PFromJSVal Headers where pFromJSVal = Headers {-# INLINE pFromJSVal #-} instance ToJSVal Headers where toJSVal = return . unHeaders {-# INLINE toJSVal #-} instance FromJSVal Headers where fromJSVal = return . fmap Headers . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject Headers where typeGType _ = gTypeHeaders {-# INLINE typeGType #-} noHeaders :: Maybe Headers noHeaders = Nothing {-# INLINE noHeaders #-} foreign import javascript unsafe "window[\"Headers\"]" gTypeHeaders :: GType -- | Functions for this inteface are in "GHCJS.DOM.History". -- -- newtype History = History { unHistory :: JSVal } instance Eq (History) where (History a) == (History b) = js_eq a b instance PToJSVal History where pToJSVal = unHistory {-# INLINE pToJSVal #-} instance PFromJSVal History where pFromJSVal = History {-# INLINE pFromJSVal #-} instance ToJSVal History where toJSVal = return . unHistory {-# INLINE toJSVal #-} instance FromJSVal History where fromJSVal = return . fmap History . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject History where typeGType _ = gTypeHistory {-# INLINE typeGType #-} noHistory :: Maybe History noHistory = Nothing {-# INLINE noHistory #-} foreign import javascript unsafe "window[\"History\"]" gTypeHistory :: GType -- | Functions for this inteface are in "GHCJS.DOM.HkdfParams". -- Base interface functions are in: -- -- * "GHCJS.DOM.CryptoAlgorithmParameters" -- -- newtype HkdfParams = HkdfParams { unHkdfParams :: JSVal } instance Eq (HkdfParams) where (HkdfParams a) == (HkdfParams b) = js_eq a b instance PToJSVal HkdfParams where pToJSVal = unHkdfParams {-# INLINE pToJSVal #-} instance PFromJSVal HkdfParams where pFromJSVal = HkdfParams {-# INLINE pFromJSVal #-} instance ToJSVal HkdfParams where toJSVal = return . unHkdfParams {-# INLINE toJSVal #-} instance FromJSVal HkdfParams where fromJSVal = return . fmap HkdfParams . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsCryptoAlgorithmParameters HkdfParams instance IsGObject HkdfParams where typeGType _ = gTypeHkdfParams {-# INLINE typeGType #-} noHkdfParams :: Maybe HkdfParams noHkdfParams = Nothing {-# INLINE noHkdfParams #-} foreign import javascript unsafe "window[\"HkdfParams\"]" gTypeHkdfParams :: GType -- | Functions for this inteface are in "GHCJS.DOM.HmacKeyParams". -- Base interface functions are in: -- -- * "GHCJS.DOM.CryptoAlgorithmParameters" -- -- newtype HmacKeyParams = HmacKeyParams { unHmacKeyParams :: JSVal } instance Eq (HmacKeyParams) where (HmacKeyParams a) == (HmacKeyParams b) = js_eq a b instance PToJSVal HmacKeyParams where pToJSVal = unHmacKeyParams {-# INLINE pToJSVal #-} instance PFromJSVal HmacKeyParams where pFromJSVal = HmacKeyParams {-# INLINE pFromJSVal #-} instance ToJSVal HmacKeyParams where toJSVal = return . unHmacKeyParams {-# INLINE toJSVal #-} instance FromJSVal HmacKeyParams where fromJSVal = return . fmap HmacKeyParams . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsCryptoAlgorithmParameters HmacKeyParams instance IsGObject HmacKeyParams where typeGType _ = gTypeHmacKeyParams {-# INLINE typeGType #-} noHmacKeyParams :: Maybe HmacKeyParams noHmacKeyParams = Nothing {-# INLINE noHmacKeyParams #-} foreign import javascript unsafe "window[\"HmacKeyParams\"]" gTypeHmacKeyParams :: GType -- | Functions for this inteface are in "GHCJS.DOM.IDBCursor". -- -- newtype IDBCursor = IDBCursor { unIDBCursor :: JSVal } instance Eq (IDBCursor) where (IDBCursor a) == (IDBCursor b) = js_eq a b instance PToJSVal IDBCursor where pToJSVal = unIDBCursor {-# INLINE pToJSVal #-} instance PFromJSVal IDBCursor where pFromJSVal = IDBCursor {-# INLINE pFromJSVal #-} instance ToJSVal IDBCursor where toJSVal = return . unIDBCursor {-# INLINE toJSVal #-} instance FromJSVal IDBCursor where fromJSVal = return . fmap IDBCursor . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsGObject o) => IsIDBCursor o toIDBCursor :: IsIDBCursor o => o -> IDBCursor toIDBCursor = IDBCursor . coerce instance IsIDBCursor IDBCursor instance IsGObject IDBCursor where typeGType _ = gTypeIDBCursor {-# INLINE typeGType #-} noIDBCursor :: Maybe IDBCursor noIDBCursor = Nothing {-# INLINE noIDBCursor #-} foreign import javascript unsafe "window[\"IDBCursor\"]" gTypeIDBCursor :: GType -- | Functions for this inteface are in "GHCJS.DOM.IDBCursorWithValue". -- Base interface functions are in: -- -- * "GHCJS.DOM.IDBCursor" -- -- newtype IDBCursorWithValue = IDBCursorWithValue { unIDBCursorWithValue :: JSVal } instance Eq (IDBCursorWithValue) where (IDBCursorWithValue a) == (IDBCursorWithValue b) = js_eq a b instance PToJSVal IDBCursorWithValue where pToJSVal = unIDBCursorWithValue {-# INLINE pToJSVal #-} instance PFromJSVal IDBCursorWithValue where pFromJSVal = IDBCursorWithValue {-# INLINE pFromJSVal #-} instance ToJSVal IDBCursorWithValue where toJSVal = return . unIDBCursorWithValue {-# INLINE toJSVal #-} instance FromJSVal IDBCursorWithValue where fromJSVal = return . fmap IDBCursorWithValue . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsIDBCursor IDBCursorWithValue instance IsGObject IDBCursorWithValue where typeGType _ = gTypeIDBCursorWithValue {-# INLINE typeGType #-} noIDBCursorWithValue :: Maybe IDBCursorWithValue noIDBCursorWithValue = Nothing {-# INLINE noIDBCursorWithValue #-} foreign import javascript unsafe "window[\"IDBCursorWithValue\"]" gTypeIDBCursorWithValue :: GType -- | Functions for this inteface are in "GHCJS.DOM.IDBDatabase". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventTarget" -- -- newtype IDBDatabase = IDBDatabase { unIDBDatabase :: JSVal } instance Eq (IDBDatabase) where (IDBDatabase a) == (IDBDatabase b) = js_eq a b instance PToJSVal IDBDatabase where pToJSVal = unIDBDatabase {-# INLINE pToJSVal #-} instance PFromJSVal IDBDatabase where pFromJSVal = IDBDatabase {-# INLINE pFromJSVal #-} instance ToJSVal IDBDatabase where toJSVal = return . unIDBDatabase {-# INLINE toJSVal #-} instance FromJSVal IDBDatabase where fromJSVal = return . fmap IDBDatabase . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventTarget IDBDatabase instance IsGObject IDBDatabase where typeGType _ = gTypeIDBDatabase {-# INLINE typeGType #-} noIDBDatabase :: Maybe IDBDatabase noIDBDatabase = Nothing {-# INLINE noIDBDatabase #-} foreign import javascript unsafe "window[\"IDBDatabase\"]" gTypeIDBDatabase :: GType -- | Functions for this inteface are in "GHCJS.DOM.IDBFactory". -- -- newtype IDBFactory = IDBFactory { unIDBFactory :: JSVal } instance Eq (IDBFactory) where (IDBFactory a) == (IDBFactory b) = js_eq a b instance PToJSVal IDBFactory where pToJSVal = unIDBFactory {-# INLINE pToJSVal #-} instance PFromJSVal IDBFactory where pFromJSVal = IDBFactory {-# INLINE pFromJSVal #-} instance ToJSVal IDBFactory where toJSVal = return . unIDBFactory {-# INLINE toJSVal #-} instance FromJSVal IDBFactory where fromJSVal = return . fmap IDBFactory . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject IDBFactory where typeGType _ = gTypeIDBFactory {-# INLINE typeGType #-} noIDBFactory :: Maybe IDBFactory noIDBFactory = Nothing {-# INLINE noIDBFactory #-} foreign import javascript unsafe "window[\"IDBFactory\"]" gTypeIDBFactory :: GType -- | Functions for this inteface are in "GHCJS.DOM.IDBIndex". -- -- newtype IDBIndex = IDBIndex { unIDBIndex :: JSVal } instance Eq (IDBIndex) where (IDBIndex a) == (IDBIndex b) = js_eq a b instance PToJSVal IDBIndex where pToJSVal = unIDBIndex {-# INLINE pToJSVal #-} instance PFromJSVal IDBIndex where pFromJSVal = IDBIndex {-# INLINE pFromJSVal #-} instance ToJSVal IDBIndex where toJSVal = return . unIDBIndex {-# INLINE toJSVal #-} instance FromJSVal IDBIndex where fromJSVal = return . fmap IDBIndex . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject IDBIndex where typeGType _ = gTypeIDBIndex {-# INLINE typeGType #-} noIDBIndex :: Maybe IDBIndex noIDBIndex = Nothing {-# INLINE noIDBIndex #-} foreign import javascript unsafe "window[\"IDBIndex\"]" gTypeIDBIndex :: GType -- | Functions for this inteface are in "GHCJS.DOM.IDBIndexParameters". -- -- newtype IDBIndexParameters = IDBIndexParameters { unIDBIndexParameters :: JSVal } instance Eq (IDBIndexParameters) where (IDBIndexParameters a) == (IDBIndexParameters b) = js_eq a b instance PToJSVal IDBIndexParameters where pToJSVal = unIDBIndexParameters {-# INLINE pToJSVal #-} instance PFromJSVal IDBIndexParameters where pFromJSVal = IDBIndexParameters {-# INLINE pFromJSVal #-} instance ToJSVal IDBIndexParameters where toJSVal = return . unIDBIndexParameters {-# INLINE toJSVal #-} instance FromJSVal IDBIndexParameters where fromJSVal = return . fmap IDBIndexParameters . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject IDBIndexParameters where typeGType _ = gTypeIDBIndexParameters {-# INLINE typeGType #-} noIDBIndexParameters :: Maybe IDBIndexParameters noIDBIndexParameters = Nothing {-# INLINE noIDBIndexParameters #-} foreign import javascript unsafe "window[\"IDBIndexParameters\"]" gTypeIDBIndexParameters :: GType -- | Functions for this inteface are in "GHCJS.DOM.IDBKeyRange". -- -- newtype IDBKeyRange = IDBKeyRange { unIDBKeyRange :: JSVal } instance Eq (IDBKeyRange) where (IDBKeyRange a) == (IDBKeyRange b) = js_eq a b instance PToJSVal IDBKeyRange where pToJSVal = unIDBKeyRange {-# INLINE pToJSVal #-} instance PFromJSVal IDBKeyRange where pFromJSVal = IDBKeyRange {-# INLINE pFromJSVal #-} instance ToJSVal IDBKeyRange where toJSVal = return . unIDBKeyRange {-# INLINE toJSVal #-} instance FromJSVal IDBKeyRange where fromJSVal = return . fmap IDBKeyRange . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject IDBKeyRange where typeGType _ = gTypeIDBKeyRange {-# INLINE typeGType #-} noIDBKeyRange :: Maybe IDBKeyRange noIDBKeyRange = Nothing {-# INLINE noIDBKeyRange #-} foreign import javascript unsafe "window[\"IDBKeyRange\"]" gTypeIDBKeyRange :: GType -- | Functions for this inteface are in "GHCJS.DOM.IDBObjectStore". -- -- newtype IDBObjectStore = IDBObjectStore { unIDBObjectStore :: JSVal } instance Eq (IDBObjectStore) where (IDBObjectStore a) == (IDBObjectStore b) = js_eq a b instance PToJSVal IDBObjectStore where pToJSVal = unIDBObjectStore {-# INLINE pToJSVal #-} instance PFromJSVal IDBObjectStore where pFromJSVal = IDBObjectStore {-# INLINE pFromJSVal #-} instance ToJSVal IDBObjectStore where toJSVal = return . unIDBObjectStore {-# INLINE toJSVal #-} instance FromJSVal IDBObjectStore where fromJSVal = return . fmap IDBObjectStore . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject IDBObjectStore where typeGType _ = gTypeIDBObjectStore {-# INLINE typeGType #-} noIDBObjectStore :: Maybe IDBObjectStore noIDBObjectStore = Nothing {-# INLINE noIDBObjectStore #-} foreign import javascript unsafe "window[\"IDBObjectStore\"]" gTypeIDBObjectStore :: GType -- | Functions for this inteface are in "GHCJS.DOM.IDBObjectStoreParameters". -- -- newtype IDBObjectStoreParameters = IDBObjectStoreParameters { unIDBObjectStoreParameters :: JSVal } instance Eq (IDBObjectStoreParameters) where (IDBObjectStoreParameters a) == (IDBObjectStoreParameters b) = js_eq a b instance PToJSVal IDBObjectStoreParameters where pToJSVal = unIDBObjectStoreParameters {-# INLINE pToJSVal #-} instance PFromJSVal IDBObjectStoreParameters where pFromJSVal = IDBObjectStoreParameters {-# INLINE pFromJSVal #-} instance ToJSVal IDBObjectStoreParameters where toJSVal = return . unIDBObjectStoreParameters {-# INLINE toJSVal #-} instance FromJSVal IDBObjectStoreParameters where fromJSVal = return . fmap IDBObjectStoreParameters . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject IDBObjectStoreParameters where typeGType _ = gTypeIDBObjectStoreParameters {-# INLINE typeGType #-} noIDBObjectStoreParameters :: Maybe IDBObjectStoreParameters noIDBObjectStoreParameters = Nothing {-# INLINE noIDBObjectStoreParameters #-} foreign import javascript unsafe "window[\"IDBObjectStoreParameters\"]" gTypeIDBObjectStoreParameters :: GType -- | Functions for this inteface are in "GHCJS.DOM.IDBOpenDBRequest". -- Base interface functions are in: -- -- * "GHCJS.DOM.IDBRequest" -- * "GHCJS.DOM.EventTarget" -- -- newtype IDBOpenDBRequest = IDBOpenDBRequest { unIDBOpenDBRequest :: JSVal } instance Eq (IDBOpenDBRequest) where (IDBOpenDBRequest a) == (IDBOpenDBRequest b) = js_eq a b instance PToJSVal IDBOpenDBRequest where pToJSVal = unIDBOpenDBRequest {-# INLINE pToJSVal #-} instance PFromJSVal IDBOpenDBRequest where pFromJSVal = IDBOpenDBRequest {-# INLINE pFromJSVal #-} instance ToJSVal IDBOpenDBRequest where toJSVal = return . unIDBOpenDBRequest {-# INLINE toJSVal #-} instance FromJSVal IDBOpenDBRequest where fromJSVal = return . fmap IDBOpenDBRequest . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsIDBRequest IDBOpenDBRequest instance IsEventTarget IDBOpenDBRequest instance IsGObject IDBOpenDBRequest where typeGType _ = gTypeIDBOpenDBRequest {-# INLINE typeGType #-} noIDBOpenDBRequest :: Maybe IDBOpenDBRequest noIDBOpenDBRequest = Nothing {-# INLINE noIDBOpenDBRequest #-} foreign import javascript unsafe "window[\"IDBOpenDBRequest\"]" gTypeIDBOpenDBRequest :: GType -- | Functions for this inteface are in "GHCJS.DOM.IDBRequest". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventTarget" -- -- newtype IDBRequest = IDBRequest { unIDBRequest :: JSVal } instance Eq (IDBRequest) where (IDBRequest a) == (IDBRequest b) = js_eq a b instance PToJSVal IDBRequest where pToJSVal = unIDBRequest {-# INLINE pToJSVal #-} instance PFromJSVal IDBRequest where pFromJSVal = IDBRequest {-# INLINE pFromJSVal #-} instance ToJSVal IDBRequest where toJSVal = return . unIDBRequest {-# INLINE toJSVal #-} instance FromJSVal IDBRequest where fromJSVal = return . fmap IDBRequest . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsEventTarget o, IsGObject o) => IsIDBRequest o toIDBRequest :: IsIDBRequest o => o -> IDBRequest toIDBRequest = IDBRequest . coerce instance IsIDBRequest IDBRequest instance IsEventTarget IDBRequest instance IsGObject IDBRequest where typeGType _ = gTypeIDBRequest {-# INLINE typeGType #-} noIDBRequest :: Maybe IDBRequest noIDBRequest = Nothing {-# INLINE noIDBRequest #-} foreign import javascript unsafe "window[\"IDBRequest\"]" gTypeIDBRequest :: GType -- | Functions for this inteface are in "GHCJS.DOM.IDBTransaction". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventTarget" -- -- newtype IDBTransaction = IDBTransaction { unIDBTransaction :: JSVal } instance Eq (IDBTransaction) where (IDBTransaction a) == (IDBTransaction b) = js_eq a b instance PToJSVal IDBTransaction where pToJSVal = unIDBTransaction {-# INLINE pToJSVal #-} instance PFromJSVal IDBTransaction where pFromJSVal = IDBTransaction {-# INLINE pFromJSVal #-} instance ToJSVal IDBTransaction where toJSVal = return . unIDBTransaction {-# INLINE toJSVal #-} instance FromJSVal IDBTransaction where fromJSVal = return . fmap IDBTransaction . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventTarget IDBTransaction instance IsGObject IDBTransaction where typeGType _ = gTypeIDBTransaction {-# INLINE typeGType #-} noIDBTransaction :: Maybe IDBTransaction noIDBTransaction = Nothing {-# INLINE noIDBTransaction #-} foreign import javascript unsafe "window[\"IDBTransaction\"]" gTypeIDBTransaction :: GType -- | Functions for this inteface are in "GHCJS.DOM.IDBVersionChangeEvent". -- Base interface functions are in: -- -- * "GHCJS.DOM.Event" -- -- newtype IDBVersionChangeEvent = IDBVersionChangeEvent { unIDBVersionChangeEvent :: JSVal } instance Eq (IDBVersionChangeEvent) where (IDBVersionChangeEvent a) == (IDBVersionChangeEvent b) = js_eq a b instance PToJSVal IDBVersionChangeEvent where pToJSVal = unIDBVersionChangeEvent {-# INLINE pToJSVal #-} instance PFromJSVal IDBVersionChangeEvent where pFromJSVal = IDBVersionChangeEvent {-# INLINE pFromJSVal #-} instance ToJSVal IDBVersionChangeEvent where toJSVal = return . unIDBVersionChangeEvent {-# INLINE toJSVal #-} instance FromJSVal IDBVersionChangeEvent where fromJSVal = return . fmap IDBVersionChangeEvent . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEvent IDBVersionChangeEvent instance IsGObject IDBVersionChangeEvent where typeGType _ = gTypeIDBVersionChangeEvent {-# INLINE typeGType #-} noIDBVersionChangeEvent :: Maybe IDBVersionChangeEvent noIDBVersionChangeEvent = Nothing {-# INLINE noIDBVersionChangeEvent #-} foreign import javascript unsafe "window[\"IDBVersionChangeEvent\"]" gTypeIDBVersionChangeEvent :: GType -- | Functions for this inteface are in "GHCJS.DOM.IDBVersionChangeEventInit". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventInit" -- -- newtype IDBVersionChangeEventInit = IDBVersionChangeEventInit { unIDBVersionChangeEventInit :: JSVal } instance Eq (IDBVersionChangeEventInit) where (IDBVersionChangeEventInit a) == (IDBVersionChangeEventInit b) = js_eq a b instance PToJSVal IDBVersionChangeEventInit where pToJSVal = unIDBVersionChangeEventInit {-# INLINE pToJSVal #-} instance PFromJSVal IDBVersionChangeEventInit where pFromJSVal = IDBVersionChangeEventInit {-# INLINE pFromJSVal #-} instance ToJSVal IDBVersionChangeEventInit where toJSVal = return . unIDBVersionChangeEventInit {-# INLINE toJSVal #-} instance FromJSVal IDBVersionChangeEventInit where fromJSVal = return . fmap IDBVersionChangeEventInit . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventInit IDBVersionChangeEventInit instance IsGObject IDBVersionChangeEventInit where typeGType _ = gTypeIDBVersionChangeEventInit {-# INLINE typeGType #-} noIDBVersionChangeEventInit :: Maybe IDBVersionChangeEventInit noIDBVersionChangeEventInit = Nothing {-# INLINE noIDBVersionChangeEventInit #-} foreign import javascript unsafe "window[\"IDBVersionChangeEventInit\"]" gTypeIDBVersionChangeEventInit :: GType -- | Functions for this inteface are in "GHCJS.DOM.ImageData". -- -- newtype ImageData = ImageData { unImageData :: JSVal } instance Eq (ImageData) where (ImageData a) == (ImageData b) = js_eq a b instance PToJSVal ImageData where pToJSVal = unImageData {-# INLINE pToJSVal #-} instance PFromJSVal ImageData where pFromJSVal = ImageData {-# INLINE pFromJSVal #-} instance ToJSVal ImageData where toJSVal = return . unImageData {-# INLINE toJSVal #-} instance FromJSVal ImageData where fromJSVal = return . fmap ImageData . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject ImageData where typeGType _ = gTypeImageData {-# INLINE typeGType #-} noImageData :: Maybe ImageData noImageData = Nothing {-# INLINE noImageData #-} foreign import javascript unsafe "window[\"ImageData\"]" gTypeImageData :: GType -- | Functions for this inteface are in "GHCJS.DOM.InputEvent". -- Base interface functions are in: -- -- * "GHCJS.DOM.UIEvent" -- * "GHCJS.DOM.Event" -- -- newtype InputEvent = InputEvent { unInputEvent :: JSVal } instance Eq (InputEvent) where (InputEvent a) == (InputEvent b) = js_eq a b instance PToJSVal InputEvent where pToJSVal = unInputEvent {-# INLINE pToJSVal #-} instance PFromJSVal InputEvent where pFromJSVal = InputEvent {-# INLINE pFromJSVal #-} instance ToJSVal InputEvent where toJSVal = return . unInputEvent {-# INLINE toJSVal #-} instance FromJSVal InputEvent where fromJSVal = return . fmap InputEvent . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsUIEvent InputEvent instance IsEvent InputEvent instance IsGObject InputEvent where typeGType _ = gTypeInputEvent {-# INLINE typeGType #-} noInputEvent :: Maybe InputEvent noInputEvent = Nothing {-# INLINE noInputEvent #-} foreign import javascript unsafe "window[\"InputEvent\"]" gTypeInputEvent :: GType -- | Functions for this inteface are in "GHCJS.DOM.InputEventInit". -- Base interface functions are in: -- -- * "GHCJS.DOM.UIEventInit" -- * "GHCJS.DOM.EventInit" -- -- newtype InputEventInit = InputEventInit { unInputEventInit :: JSVal } instance Eq (InputEventInit) where (InputEventInit a) == (InputEventInit b) = js_eq a b instance PToJSVal InputEventInit where pToJSVal = unInputEventInit {-# INLINE pToJSVal #-} instance PFromJSVal InputEventInit where pFromJSVal = InputEventInit {-# INLINE pFromJSVal #-} instance ToJSVal InputEventInit where toJSVal = return . unInputEventInit {-# INLINE toJSVal #-} instance FromJSVal InputEventInit where fromJSVal = return . fmap InputEventInit . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsUIEventInit InputEventInit instance IsEventInit InputEventInit instance IsGObject InputEventInit where typeGType _ = gTypeInputEventInit {-# INLINE typeGType #-} noInputEventInit :: Maybe InputEventInit noInputEventInit = Nothing {-# INLINE noInputEventInit #-} foreign import javascript unsafe "window[\"InputEventInit\"]" gTypeInputEventInit :: GType -- | Functions for this inteface are in "GHCJS.DOM.InspectorFrontendHost". -- -- newtype InspectorFrontendHost = InspectorFrontendHost { unInspectorFrontendHost :: JSVal } instance Eq (InspectorFrontendHost) where (InspectorFrontendHost a) == (InspectorFrontendHost b) = js_eq a b instance PToJSVal InspectorFrontendHost where pToJSVal = unInspectorFrontendHost {-# INLINE pToJSVal #-} instance PFromJSVal InspectorFrontendHost where pFromJSVal = InspectorFrontendHost {-# INLINE pFromJSVal #-} instance ToJSVal InspectorFrontendHost where toJSVal = return . unInspectorFrontendHost {-# INLINE toJSVal #-} instance FromJSVal InspectorFrontendHost where fromJSVal = return . fmap InspectorFrontendHost . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject InspectorFrontendHost where typeGType _ = gTypeInspectorFrontendHost {-# INLINE typeGType #-} noInspectorFrontendHost :: Maybe InspectorFrontendHost noInspectorFrontendHost = Nothing {-# INLINE noInspectorFrontendHost #-} foreign import javascript unsafe "window[\"InspectorFrontendHost\"]" gTypeInspectorFrontendHost :: GType -- | Functions for this inteface are in "GHCJS.DOM.IntersectionObserver". -- -- newtype IntersectionObserver = IntersectionObserver { unIntersectionObserver :: JSVal } instance Eq (IntersectionObserver) where (IntersectionObserver a) == (IntersectionObserver b) = js_eq a b instance PToJSVal IntersectionObserver where pToJSVal = unIntersectionObserver {-# INLINE pToJSVal #-} instance PFromJSVal IntersectionObserver where pFromJSVal = IntersectionObserver {-# INLINE pFromJSVal #-} instance ToJSVal IntersectionObserver where toJSVal = return . unIntersectionObserver {-# INLINE toJSVal #-} instance FromJSVal IntersectionObserver where fromJSVal = return . fmap IntersectionObserver . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject IntersectionObserver where typeGType _ = gTypeIntersectionObserver {-# INLINE typeGType #-} noIntersectionObserver :: Maybe IntersectionObserver noIntersectionObserver = Nothing {-# INLINE noIntersectionObserver #-} foreign import javascript unsafe "window[\"IntersectionObserver\"]" gTypeIntersectionObserver :: GType -- | Functions for this inteface are in "GHCJS.DOM.IntersectionObserverEntry". -- -- newtype IntersectionObserverEntry = IntersectionObserverEntry { unIntersectionObserverEntry :: JSVal } instance Eq (IntersectionObserverEntry) where (IntersectionObserverEntry a) == (IntersectionObserverEntry b) = js_eq a b instance PToJSVal IntersectionObserverEntry where pToJSVal = unIntersectionObserverEntry {-# INLINE pToJSVal #-} instance PFromJSVal IntersectionObserverEntry where pFromJSVal = IntersectionObserverEntry {-# INLINE pFromJSVal #-} instance ToJSVal IntersectionObserverEntry where toJSVal = return . unIntersectionObserverEntry {-# INLINE toJSVal #-} instance FromJSVal IntersectionObserverEntry where fromJSVal = return . fmap IntersectionObserverEntry . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject IntersectionObserverEntry where typeGType _ = gTypeIntersectionObserverEntry {-# INLINE typeGType #-} noIntersectionObserverEntry :: Maybe IntersectionObserverEntry noIntersectionObserverEntry = Nothing {-# INLINE noIntersectionObserverEntry #-} foreign import javascript unsafe "window[\"IntersectionObserverEntry\"]" gTypeIntersectionObserverEntry :: GType -- | Functions for this inteface are in "GHCJS.DOM.IntersectionObserverEntryInit". -- -- newtype IntersectionObserverEntryInit = IntersectionObserverEntryInit { unIntersectionObserverEntryInit :: JSVal } instance Eq (IntersectionObserverEntryInit) where (IntersectionObserverEntryInit a) == (IntersectionObserverEntryInit b) = js_eq a b instance PToJSVal IntersectionObserverEntryInit where pToJSVal = unIntersectionObserverEntryInit {-# INLINE pToJSVal #-} instance PFromJSVal IntersectionObserverEntryInit where pFromJSVal = IntersectionObserverEntryInit {-# INLINE pFromJSVal #-} instance ToJSVal IntersectionObserverEntryInit where toJSVal = return . unIntersectionObserverEntryInit {-# INLINE toJSVal #-} instance FromJSVal IntersectionObserverEntryInit where fromJSVal = return . fmap IntersectionObserverEntryInit . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject IntersectionObserverEntryInit where typeGType _ = gTypeIntersectionObserverEntryInit {-# INLINE typeGType #-} noIntersectionObserverEntryInit :: Maybe IntersectionObserverEntryInit noIntersectionObserverEntryInit = Nothing {-# INLINE noIntersectionObserverEntryInit #-} foreign import javascript unsafe "window[\"IntersectionObserverEntryInit\"]" gTypeIntersectionObserverEntryInit :: GType -- | Functions for this inteface are in "GHCJS.DOM.IntersectionObserverInit". -- -- newtype IntersectionObserverInit = IntersectionObserverInit { unIntersectionObserverInit :: JSVal } instance Eq (IntersectionObserverInit) where (IntersectionObserverInit a) == (IntersectionObserverInit b) = js_eq a b instance PToJSVal IntersectionObserverInit where pToJSVal = unIntersectionObserverInit {-# INLINE pToJSVal #-} instance PFromJSVal IntersectionObserverInit where pFromJSVal = IntersectionObserverInit {-# INLINE pFromJSVal #-} instance ToJSVal IntersectionObserverInit where toJSVal = return . unIntersectionObserverInit {-# INLINE toJSVal #-} instance FromJSVal IntersectionObserverInit where fromJSVal = return . fmap IntersectionObserverInit . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject IntersectionObserverInit where typeGType _ = gTypeIntersectionObserverInit {-# INLINE typeGType #-} noIntersectionObserverInit :: Maybe IntersectionObserverInit noIntersectionObserverInit = Nothing {-# INLINE noIntersectionObserverInit #-} foreign import javascript unsafe "window[\"IntersectionObserverInit\"]" gTypeIntersectionObserverInit :: GType -- | Functions for this inteface are in "GHCJS.DOM.JsonWebKey". -- -- newtype JsonWebKey = JsonWebKey { unJsonWebKey :: JSVal } instance Eq (JsonWebKey) where (JsonWebKey a) == (JsonWebKey b) = js_eq a b instance PToJSVal JsonWebKey where pToJSVal = unJsonWebKey {-# INLINE pToJSVal #-} instance PFromJSVal JsonWebKey where pFromJSVal = JsonWebKey {-# INLINE pFromJSVal #-} instance ToJSVal JsonWebKey where toJSVal = return . unJsonWebKey {-# INLINE toJSVal #-} instance FromJSVal JsonWebKey where fromJSVal = return . fmap JsonWebKey . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject JsonWebKey where typeGType _ = gTypeJsonWebKey {-# INLINE typeGType #-} noJsonWebKey :: Maybe JsonWebKey noJsonWebKey = Nothing {-# INLINE noJsonWebKey #-} foreign import javascript unsafe "window[\"JsonWebKey\"]" gTypeJsonWebKey :: GType -- | Functions for this inteface are in "GHCJS.DOM.KeyboardEvent". -- Base interface functions are in: -- -- * "GHCJS.DOM.UIEvent" -- * "GHCJS.DOM.Event" -- -- newtype KeyboardEvent = KeyboardEvent { unKeyboardEvent :: JSVal } instance Eq (KeyboardEvent) where (KeyboardEvent a) == (KeyboardEvent b) = js_eq a b instance PToJSVal KeyboardEvent where pToJSVal = unKeyboardEvent {-# INLINE pToJSVal #-} instance PFromJSVal KeyboardEvent where pFromJSVal = KeyboardEvent {-# INLINE pFromJSVal #-} instance ToJSVal KeyboardEvent where toJSVal = return . unKeyboardEvent {-# INLINE toJSVal #-} instance FromJSVal KeyboardEvent where fromJSVal = return . fmap KeyboardEvent . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsUIEvent KeyboardEvent instance IsEvent KeyboardEvent instance IsGObject KeyboardEvent where typeGType _ = gTypeKeyboardEvent {-# INLINE typeGType #-} noKeyboardEvent :: Maybe KeyboardEvent noKeyboardEvent = Nothing {-# INLINE noKeyboardEvent #-} foreign import javascript unsafe "window[\"KeyboardEvent\"]" gTypeKeyboardEvent :: GType -- | Functions for this inteface are in "GHCJS.DOM.KeyboardEventInit". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventModifierInit" -- * "GHCJS.DOM.UIEventInit" -- * "GHCJS.DOM.EventInit" -- -- newtype KeyboardEventInit = KeyboardEventInit { unKeyboardEventInit :: JSVal } instance Eq (KeyboardEventInit) where (KeyboardEventInit a) == (KeyboardEventInit b) = js_eq a b instance PToJSVal KeyboardEventInit where pToJSVal = unKeyboardEventInit {-# INLINE pToJSVal #-} instance PFromJSVal KeyboardEventInit where pFromJSVal = KeyboardEventInit {-# INLINE pFromJSVal #-} instance ToJSVal KeyboardEventInit where toJSVal = return . unKeyboardEventInit {-# INLINE toJSVal #-} instance FromJSVal KeyboardEventInit where fromJSVal = return . fmap KeyboardEventInit . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventModifierInit KeyboardEventInit instance IsUIEventInit KeyboardEventInit instance IsEventInit KeyboardEventInit instance IsGObject KeyboardEventInit where typeGType _ = gTypeKeyboardEventInit {-# INLINE typeGType #-} noKeyboardEventInit :: Maybe KeyboardEventInit noKeyboardEventInit = Nothing {-# INLINE noKeyboardEventInit #-} foreign import javascript unsafe "window[\"KeyboardEventInit\"]" gTypeKeyboardEventInit :: GType -- | Functions for this inteface are in "GHCJS.DOM.KeyframeEffect". -- Base interface functions are in: -- -- * "GHCJS.DOM.AnimationEffect" -- -- newtype KeyframeEffect = KeyframeEffect { unKeyframeEffect :: JSVal } instance Eq (KeyframeEffect) where (KeyframeEffect a) == (KeyframeEffect b) = js_eq a b instance PToJSVal KeyframeEffect where pToJSVal = unKeyframeEffect {-# INLINE pToJSVal #-} instance PFromJSVal KeyframeEffect where pFromJSVal = KeyframeEffect {-# INLINE pFromJSVal #-} instance ToJSVal KeyframeEffect where toJSVal = return . unKeyframeEffect {-# INLINE toJSVal #-} instance FromJSVal KeyframeEffect where fromJSVal = return . fmap KeyframeEffect . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsAnimationEffect KeyframeEffect instance IsGObject KeyframeEffect where typeGType _ = gTypeKeyframeEffect {-# INLINE typeGType #-} noKeyframeEffect :: Maybe KeyframeEffect noKeyframeEffect = Nothing {-# INLINE noKeyframeEffect #-} foreign import javascript unsafe "window[\"KeyframeEffect\"]" gTypeKeyframeEffect :: GType -- | Functions for this inteface are in "GHCJS.DOM.Location". -- -- newtype Location = Location { unLocation :: JSVal } instance Eq (Location) where (Location a) == (Location b) = js_eq a b instance PToJSVal Location where pToJSVal = unLocation {-# INLINE pToJSVal #-} instance PFromJSVal Location where pFromJSVal = Location {-# INLINE pFromJSVal #-} instance ToJSVal Location where toJSVal = return . unLocation {-# INLINE toJSVal #-} instance FromJSVal Location where fromJSVal = return . fmap Location . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject Location where typeGType _ = gTypeLocation {-# INLINE typeGType #-} noLocation :: Maybe Location noLocation = Nothing {-# INLINE noLocation #-} foreign import javascript unsafe "window[\"Location\"]" gTypeLocation :: GType -- | Functions for this inteface are in "GHCJS.DOM.LongRange". -- -- newtype LongRange = LongRange { unLongRange :: JSVal } instance Eq (LongRange) where (LongRange a) == (LongRange b) = js_eq a b instance PToJSVal LongRange where pToJSVal = unLongRange {-# INLINE pToJSVal #-} instance PFromJSVal LongRange where pFromJSVal = LongRange {-# INLINE pFromJSVal #-} instance ToJSVal LongRange where toJSVal = return . unLongRange {-# INLINE toJSVal #-} instance FromJSVal LongRange where fromJSVal = return . fmap LongRange . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsGObject o) => IsLongRange o toLongRange :: IsLongRange o => o -> LongRange toLongRange = LongRange . coerce instance IsLongRange LongRange instance IsGObject LongRange where typeGType _ = gTypeLongRange {-# INLINE typeGType #-} noLongRange :: Maybe LongRange noLongRange = Nothing {-# INLINE noLongRange #-} foreign import javascript unsafe "window[\"LongRange\"]" gTypeLongRange :: GType -- | Functions for this inteface are in "GHCJS.DOM.MediaController". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventTarget" -- -- newtype MediaController = MediaController { unMediaController :: JSVal } instance Eq (MediaController) where (MediaController a) == (MediaController b) = js_eq a b instance PToJSVal MediaController where pToJSVal = unMediaController {-# INLINE pToJSVal #-} instance PFromJSVal MediaController where pFromJSVal = MediaController {-# INLINE pFromJSVal #-} instance ToJSVal MediaController where toJSVal = return . unMediaController {-# INLINE toJSVal #-} instance FromJSVal MediaController where fromJSVal = return . fmap MediaController . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventTarget MediaController instance IsGObject MediaController where typeGType _ = gTypeMediaController {-# INLINE typeGType #-} noMediaController :: Maybe MediaController noMediaController = Nothing {-# INLINE noMediaController #-} foreign import javascript unsafe "window[\"MediaController\"]" gTypeMediaController :: GType -- | Functions for this inteface are in "GHCJS.DOM.MediaControlsHost". -- -- newtype MediaControlsHost = MediaControlsHost { unMediaControlsHost :: JSVal } instance Eq (MediaControlsHost) where (MediaControlsHost a) == (MediaControlsHost b) = js_eq a b instance PToJSVal MediaControlsHost where pToJSVal = unMediaControlsHost {-# INLINE pToJSVal #-} instance PFromJSVal MediaControlsHost where pFromJSVal = MediaControlsHost {-# INLINE pFromJSVal #-} instance ToJSVal MediaControlsHost where toJSVal = return . unMediaControlsHost {-# INLINE toJSVal #-} instance FromJSVal MediaControlsHost where fromJSVal = return . fmap MediaControlsHost . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject MediaControlsHost where typeGType _ = gTypeMediaControlsHost {-# INLINE typeGType #-} noMediaControlsHost :: Maybe MediaControlsHost noMediaControlsHost = Nothing {-# INLINE noMediaControlsHost #-} foreign import javascript unsafe "window[\"MediaControlsHost\"]" gTypeMediaControlsHost :: GType -- | Functions for this inteface are in "GHCJS.DOM.MediaDeviceInfo". -- -- newtype MediaDeviceInfo = MediaDeviceInfo { unMediaDeviceInfo :: JSVal } instance Eq (MediaDeviceInfo) where (MediaDeviceInfo a) == (MediaDeviceInfo b) = js_eq a b instance PToJSVal MediaDeviceInfo where pToJSVal = unMediaDeviceInfo {-# INLINE pToJSVal #-} instance PFromJSVal MediaDeviceInfo where pFromJSVal = MediaDeviceInfo {-# INLINE pFromJSVal #-} instance ToJSVal MediaDeviceInfo where toJSVal = return . unMediaDeviceInfo {-# INLINE toJSVal #-} instance FromJSVal MediaDeviceInfo where fromJSVal = return . fmap MediaDeviceInfo . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject MediaDeviceInfo where typeGType _ = gTypeMediaDeviceInfo {-# INLINE typeGType #-} noMediaDeviceInfo :: Maybe MediaDeviceInfo noMediaDeviceInfo = Nothing {-# INLINE noMediaDeviceInfo #-} foreign import javascript unsafe "window[\"MediaDeviceInfo\"]" gTypeMediaDeviceInfo :: GType -- | Functions for this inteface are in "GHCJS.DOM.MediaDevices". -- -- newtype MediaDevices = MediaDevices { unMediaDevices :: JSVal } instance Eq (MediaDevices) where (MediaDevices a) == (MediaDevices b) = js_eq a b instance PToJSVal MediaDevices where pToJSVal = unMediaDevices {-# INLINE pToJSVal #-} instance PFromJSVal MediaDevices where pFromJSVal = MediaDevices {-# INLINE pFromJSVal #-} instance ToJSVal MediaDevices where toJSVal = return . unMediaDevices {-# INLINE toJSVal #-} instance FromJSVal MediaDevices where fromJSVal = return . fmap MediaDevices . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject MediaDevices where typeGType _ = gTypeMediaDevices {-# INLINE typeGType #-} noMediaDevices :: Maybe MediaDevices noMediaDevices = Nothing {-# INLINE noMediaDevices #-} foreign import javascript unsafe "window[\"MediaDevices\"]" gTypeMediaDevices :: GType -- | Functions for this inteface are in "GHCJS.DOM.MediaElementAudioSourceNode". -- Base interface functions are in: -- -- * "GHCJS.DOM.AudioNode" -- * "GHCJS.DOM.EventTarget" -- -- newtype MediaElementAudioSourceNode = MediaElementAudioSourceNode { unMediaElementAudioSourceNode :: JSVal } instance Eq (MediaElementAudioSourceNode) where (MediaElementAudioSourceNode a) == (MediaElementAudioSourceNode b) = js_eq a b instance PToJSVal MediaElementAudioSourceNode where pToJSVal = unMediaElementAudioSourceNode {-# INLINE pToJSVal #-} instance PFromJSVal MediaElementAudioSourceNode where pFromJSVal = MediaElementAudioSourceNode {-# INLINE pFromJSVal #-} instance ToJSVal MediaElementAudioSourceNode where toJSVal = return . unMediaElementAudioSourceNode {-# INLINE toJSVal #-} instance FromJSVal MediaElementAudioSourceNode where fromJSVal = return . fmap MediaElementAudioSourceNode . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsAudioNode MediaElementAudioSourceNode instance IsEventTarget MediaElementAudioSourceNode instance IsGObject MediaElementAudioSourceNode where typeGType _ = gTypeMediaElementAudioSourceNode {-# INLINE typeGType #-} noMediaElementAudioSourceNode :: Maybe MediaElementAudioSourceNode noMediaElementAudioSourceNode = Nothing {-# INLINE noMediaElementAudioSourceNode #-} foreign import javascript unsafe "window[\"MediaElementAudioSourceNode\"]" gTypeMediaElementAudioSourceNode :: GType -- | Functions for this inteface are in "GHCJS.DOM.MediaEncryptedEvent". -- Base interface functions are in: -- -- * "GHCJS.DOM.Event" -- -- newtype MediaEncryptedEvent = MediaEncryptedEvent { unMediaEncryptedEvent :: JSVal } instance Eq (MediaEncryptedEvent) where (MediaEncryptedEvent a) == (MediaEncryptedEvent b) = js_eq a b instance PToJSVal MediaEncryptedEvent where pToJSVal = unMediaEncryptedEvent {-# INLINE pToJSVal #-} instance PFromJSVal MediaEncryptedEvent where pFromJSVal = MediaEncryptedEvent {-# INLINE pFromJSVal #-} instance ToJSVal MediaEncryptedEvent where toJSVal = return . unMediaEncryptedEvent {-# INLINE toJSVal #-} instance FromJSVal MediaEncryptedEvent where fromJSVal = return . fmap MediaEncryptedEvent . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEvent MediaEncryptedEvent instance IsGObject MediaEncryptedEvent where typeGType _ = gTypeMediaEncryptedEvent {-# INLINE typeGType #-} noMediaEncryptedEvent :: Maybe MediaEncryptedEvent noMediaEncryptedEvent = Nothing {-# INLINE noMediaEncryptedEvent #-} foreign import javascript unsafe "window[\"MediaEncryptedEvent\"]" gTypeMediaEncryptedEvent :: GType -- | Functions for this inteface are in "GHCJS.DOM.MediaEncryptedEventInit". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventInit" -- -- newtype MediaEncryptedEventInit = MediaEncryptedEventInit { unMediaEncryptedEventInit :: JSVal } instance Eq (MediaEncryptedEventInit) where (MediaEncryptedEventInit a) == (MediaEncryptedEventInit b) = js_eq a b instance PToJSVal MediaEncryptedEventInit where pToJSVal = unMediaEncryptedEventInit {-# INLINE pToJSVal #-} instance PFromJSVal MediaEncryptedEventInit where pFromJSVal = MediaEncryptedEventInit {-# INLINE pFromJSVal #-} instance ToJSVal MediaEncryptedEventInit where toJSVal = return . unMediaEncryptedEventInit {-# INLINE toJSVal #-} instance FromJSVal MediaEncryptedEventInit where fromJSVal = return . fmap MediaEncryptedEventInit . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventInit MediaEncryptedEventInit instance IsGObject MediaEncryptedEventInit where typeGType _ = gTypeMediaEncryptedEventInit {-# INLINE typeGType #-} noMediaEncryptedEventInit :: Maybe MediaEncryptedEventInit noMediaEncryptedEventInit = Nothing {-# INLINE noMediaEncryptedEventInit #-} foreign import javascript unsafe "window[\"MediaEncryptedEventInit\"]" gTypeMediaEncryptedEventInit :: GType -- | Functions for this inteface are in "GHCJS.DOM.MediaError". -- -- newtype MediaError = MediaError { unMediaError :: JSVal } instance Eq (MediaError) where (MediaError a) == (MediaError b) = js_eq a b instance PToJSVal MediaError where pToJSVal = unMediaError {-# INLINE pToJSVal #-} instance PFromJSVal MediaError where pFromJSVal = MediaError {-# INLINE pFromJSVal #-} instance ToJSVal MediaError where toJSVal = return . unMediaError {-# INLINE toJSVal #-} instance FromJSVal MediaError where fromJSVal = return . fmap MediaError . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject MediaError where typeGType _ = gTypeMediaError {-# INLINE typeGType #-} noMediaError :: Maybe MediaError noMediaError = Nothing {-# INLINE noMediaError #-} foreign import javascript unsafe "window[\"MediaError\"]" gTypeMediaError :: GType -- | Functions for this inteface are in "GHCJS.DOM.MediaKeyMessageEvent". -- Base interface functions are in: -- -- * "GHCJS.DOM.Event" -- -- newtype MediaKeyMessageEvent = MediaKeyMessageEvent { unMediaKeyMessageEvent :: JSVal } instance Eq (MediaKeyMessageEvent) where (MediaKeyMessageEvent a) == (MediaKeyMessageEvent b) = js_eq a b instance PToJSVal MediaKeyMessageEvent where pToJSVal = unMediaKeyMessageEvent {-# INLINE pToJSVal #-} instance PFromJSVal MediaKeyMessageEvent where pFromJSVal = MediaKeyMessageEvent {-# INLINE pFromJSVal #-} instance ToJSVal MediaKeyMessageEvent where toJSVal = return . unMediaKeyMessageEvent {-# INLINE toJSVal #-} instance FromJSVal MediaKeyMessageEvent where fromJSVal = return . fmap MediaKeyMessageEvent . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEvent MediaKeyMessageEvent instance IsGObject MediaKeyMessageEvent where typeGType _ = gTypeMediaKeyMessageEvent {-# INLINE typeGType #-} noMediaKeyMessageEvent :: Maybe MediaKeyMessageEvent noMediaKeyMessageEvent = Nothing {-# INLINE noMediaKeyMessageEvent #-} foreign import javascript unsafe "window[\"WebKitMediaKeyMessageEvent\"]" gTypeMediaKeyMessageEvent :: GType -- | Functions for this inteface are in "GHCJS.DOM.MediaKeyMessageEventInit". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventInit" -- -- newtype MediaKeyMessageEventInit = MediaKeyMessageEventInit { unMediaKeyMessageEventInit :: JSVal } instance Eq (MediaKeyMessageEventInit) where (MediaKeyMessageEventInit a) == (MediaKeyMessageEventInit b) = js_eq a b instance PToJSVal MediaKeyMessageEventInit where pToJSVal = unMediaKeyMessageEventInit {-# INLINE pToJSVal #-} instance PFromJSVal MediaKeyMessageEventInit where pFromJSVal = MediaKeyMessageEventInit {-# INLINE pFromJSVal #-} instance ToJSVal MediaKeyMessageEventInit where toJSVal = return . unMediaKeyMessageEventInit {-# INLINE toJSVal #-} instance FromJSVal MediaKeyMessageEventInit where fromJSVal = return . fmap MediaKeyMessageEventInit . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventInit MediaKeyMessageEventInit instance IsGObject MediaKeyMessageEventInit where typeGType _ = gTypeMediaKeyMessageEventInit {-# INLINE typeGType #-} noMediaKeyMessageEventInit :: Maybe MediaKeyMessageEventInit noMediaKeyMessageEventInit = Nothing {-# INLINE noMediaKeyMessageEventInit #-} foreign import javascript unsafe "window[\"MediaKeyMessageEventInit\"]" gTypeMediaKeyMessageEventInit :: GType -- | Functions for this inteface are in "GHCJS.DOM.MediaKeySession". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventTarget" -- -- newtype MediaKeySession = MediaKeySession { unMediaKeySession :: JSVal } instance Eq (MediaKeySession) where (MediaKeySession a) == (MediaKeySession b) = js_eq a b instance PToJSVal MediaKeySession where pToJSVal = unMediaKeySession {-# INLINE pToJSVal #-} instance PFromJSVal MediaKeySession where pFromJSVal = MediaKeySession {-# INLINE pFromJSVal #-} instance ToJSVal MediaKeySession where toJSVal = return . unMediaKeySession {-# INLINE toJSVal #-} instance FromJSVal MediaKeySession where fromJSVal = return . fmap MediaKeySession . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventTarget MediaKeySession instance IsGObject MediaKeySession where typeGType _ = gTypeMediaKeySession {-# INLINE typeGType #-} noMediaKeySession :: Maybe MediaKeySession noMediaKeySession = Nothing {-# INLINE noMediaKeySession #-} foreign import javascript unsafe "window[\"WebKitMediaKeySession\"]" gTypeMediaKeySession :: GType -- | Functions for this inteface are in "GHCJS.DOM.MediaKeyStatusMap". -- -- newtype MediaKeyStatusMap = MediaKeyStatusMap { unMediaKeyStatusMap :: JSVal } instance Eq (MediaKeyStatusMap) where (MediaKeyStatusMap a) == (MediaKeyStatusMap b) = js_eq a b instance PToJSVal MediaKeyStatusMap where pToJSVal = unMediaKeyStatusMap {-# INLINE pToJSVal #-} instance PFromJSVal MediaKeyStatusMap where pFromJSVal = MediaKeyStatusMap {-# INLINE pFromJSVal #-} instance ToJSVal MediaKeyStatusMap where toJSVal = return . unMediaKeyStatusMap {-# INLINE toJSVal #-} instance FromJSVal MediaKeyStatusMap where fromJSVal = return . fmap MediaKeyStatusMap . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject MediaKeyStatusMap where typeGType _ = gTypeMediaKeyStatusMap {-# INLINE typeGType #-} noMediaKeyStatusMap :: Maybe MediaKeyStatusMap noMediaKeyStatusMap = Nothing {-# INLINE noMediaKeyStatusMap #-} foreign import javascript unsafe "window[\"MediaKeyStatusMap\"]" gTypeMediaKeyStatusMap :: GType -- | Functions for this inteface are in "GHCJS.DOM.MediaKeySystemAccess". -- -- newtype MediaKeySystemAccess = MediaKeySystemAccess { unMediaKeySystemAccess :: JSVal } instance Eq (MediaKeySystemAccess) where (MediaKeySystemAccess a) == (MediaKeySystemAccess b) = js_eq a b instance PToJSVal MediaKeySystemAccess where pToJSVal = unMediaKeySystemAccess {-# INLINE pToJSVal #-} instance PFromJSVal MediaKeySystemAccess where pFromJSVal = MediaKeySystemAccess {-# INLINE pFromJSVal #-} instance ToJSVal MediaKeySystemAccess where toJSVal = return . unMediaKeySystemAccess {-# INLINE toJSVal #-} instance FromJSVal MediaKeySystemAccess where fromJSVal = return . fmap MediaKeySystemAccess . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject MediaKeySystemAccess where typeGType _ = gTypeMediaKeySystemAccess {-# INLINE typeGType #-} noMediaKeySystemAccess :: Maybe MediaKeySystemAccess noMediaKeySystemAccess = Nothing {-# INLINE noMediaKeySystemAccess #-} foreign import javascript unsafe "window[\"MediaKeySystemAccess\"]" gTypeMediaKeySystemAccess :: GType -- | Functions for this inteface are in "GHCJS.DOM.MediaKeySystemConfiguration". -- -- newtype MediaKeySystemConfiguration = MediaKeySystemConfiguration { unMediaKeySystemConfiguration :: JSVal } instance Eq (MediaKeySystemConfiguration) where (MediaKeySystemConfiguration a) == (MediaKeySystemConfiguration b) = js_eq a b instance PToJSVal MediaKeySystemConfiguration where pToJSVal = unMediaKeySystemConfiguration {-# INLINE pToJSVal #-} instance PFromJSVal MediaKeySystemConfiguration where pFromJSVal = MediaKeySystemConfiguration {-# INLINE pFromJSVal #-} instance ToJSVal MediaKeySystemConfiguration where toJSVal = return . unMediaKeySystemConfiguration {-# INLINE toJSVal #-} instance FromJSVal MediaKeySystemConfiguration where fromJSVal = return . fmap MediaKeySystemConfiguration . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject MediaKeySystemConfiguration where typeGType _ = gTypeMediaKeySystemConfiguration {-# INLINE typeGType #-} noMediaKeySystemConfiguration :: Maybe MediaKeySystemConfiguration noMediaKeySystemConfiguration = Nothing {-# INLINE noMediaKeySystemConfiguration #-} foreign import javascript unsafe "window[\"MediaKeySystemConfiguration\"]" gTypeMediaKeySystemConfiguration :: GType -- | Functions for this inteface are in "GHCJS.DOM.MediaKeySystemMediaCapability". -- -- newtype MediaKeySystemMediaCapability = MediaKeySystemMediaCapability { unMediaKeySystemMediaCapability :: JSVal } instance Eq (MediaKeySystemMediaCapability) where (MediaKeySystemMediaCapability a) == (MediaKeySystemMediaCapability b) = js_eq a b instance PToJSVal MediaKeySystemMediaCapability where pToJSVal = unMediaKeySystemMediaCapability {-# INLINE pToJSVal #-} instance PFromJSVal MediaKeySystemMediaCapability where pFromJSVal = MediaKeySystemMediaCapability {-# INLINE pFromJSVal #-} instance ToJSVal MediaKeySystemMediaCapability where toJSVal = return . unMediaKeySystemMediaCapability {-# INLINE toJSVal #-} instance FromJSVal MediaKeySystemMediaCapability where fromJSVal = return . fmap MediaKeySystemMediaCapability . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject MediaKeySystemMediaCapability where typeGType _ = gTypeMediaKeySystemMediaCapability {-# INLINE typeGType #-} noMediaKeySystemMediaCapability :: Maybe MediaKeySystemMediaCapability noMediaKeySystemMediaCapability = Nothing {-# INLINE noMediaKeySystemMediaCapability #-} foreign import javascript unsafe "window[\"MediaKeySystemMediaCapability\"]" gTypeMediaKeySystemMediaCapability :: GType -- | Functions for this inteface are in "GHCJS.DOM.MediaKeys". -- -- newtype MediaKeys = MediaKeys { unMediaKeys :: JSVal } instance Eq (MediaKeys) where (MediaKeys a) == (MediaKeys b) = js_eq a b instance PToJSVal MediaKeys where pToJSVal = unMediaKeys {-# INLINE pToJSVal #-} instance PFromJSVal MediaKeys where pFromJSVal = MediaKeys {-# INLINE pFromJSVal #-} instance ToJSVal MediaKeys where toJSVal = return . unMediaKeys {-# INLINE toJSVal #-} instance FromJSVal MediaKeys where fromJSVal = return . fmap MediaKeys . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject MediaKeys where typeGType _ = gTypeMediaKeys {-# INLINE typeGType #-} noMediaKeys :: Maybe MediaKeys noMediaKeys = Nothing {-# INLINE noMediaKeys #-} foreign import javascript unsafe "window[\"WebKitMediaKeys\"]" gTypeMediaKeys :: GType -- | Functions for this inteface are in "GHCJS.DOM.MediaList". -- -- newtype MediaList = MediaList { unMediaList :: JSVal } instance Eq (MediaList) where (MediaList a) == (MediaList b) = js_eq a b instance PToJSVal MediaList where pToJSVal = unMediaList {-# INLINE pToJSVal #-} instance PFromJSVal MediaList where pFromJSVal = MediaList {-# INLINE pFromJSVal #-} instance ToJSVal MediaList where toJSVal = return . unMediaList {-# INLINE toJSVal #-} instance FromJSVal MediaList where fromJSVal = return . fmap MediaList . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject MediaList where typeGType _ = gTypeMediaList {-# INLINE typeGType #-} noMediaList :: Maybe MediaList noMediaList = Nothing {-# INLINE noMediaList #-} foreign import javascript unsafe "window[\"MediaList\"]" gTypeMediaList :: GType -- | Functions for this inteface are in "GHCJS.DOM.MediaMetadata". -- -- newtype MediaMetadata = MediaMetadata { unMediaMetadata :: JSVal } instance Eq (MediaMetadata) where (MediaMetadata a) == (MediaMetadata b) = js_eq a b instance PToJSVal MediaMetadata where pToJSVal = unMediaMetadata {-# INLINE pToJSVal #-} instance PFromJSVal MediaMetadata where pFromJSVal = MediaMetadata {-# INLINE pFromJSVal #-} instance ToJSVal MediaMetadata where toJSVal = return . unMediaMetadata {-# INLINE toJSVal #-} instance FromJSVal MediaMetadata where fromJSVal = return . fmap MediaMetadata . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject MediaMetadata where typeGType _ = gTypeMediaMetadata {-# INLINE typeGType #-} noMediaMetadata :: Maybe MediaMetadata noMediaMetadata = Nothing {-# INLINE noMediaMetadata #-} foreign import javascript unsafe "window[\"MediaMetadata\"]" gTypeMediaMetadata :: GType -- | Functions for this inteface are in "GHCJS.DOM.MediaQueryList". -- -- newtype MediaQueryList = MediaQueryList { unMediaQueryList :: JSVal } instance Eq (MediaQueryList) where (MediaQueryList a) == (MediaQueryList b) = js_eq a b instance PToJSVal MediaQueryList where pToJSVal = unMediaQueryList {-# INLINE pToJSVal #-} instance PFromJSVal MediaQueryList where pFromJSVal = MediaQueryList {-# INLINE pFromJSVal #-} instance ToJSVal MediaQueryList where toJSVal = return . unMediaQueryList {-# INLINE toJSVal #-} instance FromJSVal MediaQueryList where fromJSVal = return . fmap MediaQueryList . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject MediaQueryList where typeGType _ = gTypeMediaQueryList {-# INLINE typeGType #-} noMediaQueryList :: Maybe MediaQueryList noMediaQueryList = Nothing {-# INLINE noMediaQueryList #-} foreign import javascript unsafe "window[\"MediaQueryList\"]" gTypeMediaQueryList :: GType -- | Functions for this inteface are in "GHCJS.DOM.MediaRemoteControls". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventTarget" -- -- newtype MediaRemoteControls = MediaRemoteControls { unMediaRemoteControls :: JSVal } instance Eq (MediaRemoteControls) where (MediaRemoteControls a) == (MediaRemoteControls b) = js_eq a b instance PToJSVal MediaRemoteControls where pToJSVal = unMediaRemoteControls {-# INLINE pToJSVal #-} instance PFromJSVal MediaRemoteControls where pFromJSVal = MediaRemoteControls {-# INLINE pFromJSVal #-} instance ToJSVal MediaRemoteControls where toJSVal = return . unMediaRemoteControls {-# INLINE toJSVal #-} instance FromJSVal MediaRemoteControls where fromJSVal = return . fmap MediaRemoteControls . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventTarget MediaRemoteControls instance IsGObject MediaRemoteControls where typeGType _ = gTypeMediaRemoteControls {-# INLINE typeGType #-} noMediaRemoteControls :: Maybe MediaRemoteControls noMediaRemoteControls = Nothing {-# INLINE noMediaRemoteControls #-} foreign import javascript unsafe "window[\"MediaRemoteControls\"]" gTypeMediaRemoteControls :: GType -- | Functions for this inteface are in "GHCJS.DOM.MediaSession". -- -- newtype MediaSession = MediaSession { unMediaSession :: JSVal } instance Eq (MediaSession) where (MediaSession a) == (MediaSession b) = js_eq a b instance PToJSVal MediaSession where pToJSVal = unMediaSession {-# INLINE pToJSVal #-} instance PFromJSVal MediaSession where pFromJSVal = MediaSession {-# INLINE pFromJSVal #-} instance ToJSVal MediaSession where toJSVal = return . unMediaSession {-# INLINE toJSVal #-} instance FromJSVal MediaSession where fromJSVal = return . fmap MediaSession . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject MediaSession where typeGType _ = gTypeMediaSession {-# INLINE typeGType #-} noMediaSession :: Maybe MediaSession noMediaSession = Nothing {-# INLINE noMediaSession #-} foreign import javascript unsafe "window[\"MediaSession\"]" gTypeMediaSession :: GType -- | Functions for this inteface are in "GHCJS.DOM.MediaSource". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventTarget" -- -- newtype MediaSource = MediaSource { unMediaSource :: JSVal } instance Eq (MediaSource) where (MediaSource a) == (MediaSource b) = js_eq a b instance PToJSVal MediaSource where pToJSVal = unMediaSource {-# INLINE pToJSVal #-} instance PFromJSVal MediaSource where pFromJSVal = MediaSource {-# INLINE pFromJSVal #-} instance ToJSVal MediaSource where toJSVal = return . unMediaSource {-# INLINE toJSVal #-} instance FromJSVal MediaSource where fromJSVal = return . fmap MediaSource . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventTarget MediaSource instance IsGObject MediaSource where typeGType _ = gTypeMediaSource {-# INLINE typeGType #-} noMediaSource :: Maybe MediaSource noMediaSource = Nothing {-# INLINE noMediaSource #-} foreign import javascript unsafe "window[\"MediaSource\"]" gTypeMediaSource :: GType -- | Functions for this inteface are in "GHCJS.DOM.MediaStream". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventTarget" -- -- newtype MediaStream = MediaStream { unMediaStream :: JSVal } instance Eq (MediaStream) where (MediaStream a) == (MediaStream b) = js_eq a b instance PToJSVal MediaStream where pToJSVal = unMediaStream {-# INLINE pToJSVal #-} instance PFromJSVal MediaStream where pFromJSVal = MediaStream {-# INLINE pFromJSVal #-} instance ToJSVal MediaStream where toJSVal = return . unMediaStream {-# INLINE toJSVal #-} instance FromJSVal MediaStream where fromJSVal = return . fmap MediaStream . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventTarget MediaStream instance IsGObject MediaStream where typeGType _ = gTypeMediaStream {-# INLINE typeGType #-} noMediaStream :: Maybe MediaStream noMediaStream = Nothing {-# INLINE noMediaStream #-} foreign import javascript unsafe "window[\"webkitMediaStream\"]" gTypeMediaStream :: GType -- | Functions for this inteface are in "GHCJS.DOM.MediaStreamAudioDestinationNode". -- Base interface functions are in: -- -- * "GHCJS.DOM.AudioNode" -- * "GHCJS.DOM.EventTarget" -- -- newtype MediaStreamAudioDestinationNode = MediaStreamAudioDestinationNode { unMediaStreamAudioDestinationNode :: JSVal } instance Eq (MediaStreamAudioDestinationNode) where (MediaStreamAudioDestinationNode a) == (MediaStreamAudioDestinationNode b) = js_eq a b instance PToJSVal MediaStreamAudioDestinationNode where pToJSVal = unMediaStreamAudioDestinationNode {-# INLINE pToJSVal #-} instance PFromJSVal MediaStreamAudioDestinationNode where pFromJSVal = MediaStreamAudioDestinationNode {-# INLINE pFromJSVal #-} instance ToJSVal MediaStreamAudioDestinationNode where toJSVal = return . unMediaStreamAudioDestinationNode {-# INLINE toJSVal #-} instance FromJSVal MediaStreamAudioDestinationNode where fromJSVal = return . fmap MediaStreamAudioDestinationNode . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsAudioNode MediaStreamAudioDestinationNode instance IsEventTarget MediaStreamAudioDestinationNode instance IsGObject MediaStreamAudioDestinationNode where typeGType _ = gTypeMediaStreamAudioDestinationNode {-# INLINE typeGType #-} noMediaStreamAudioDestinationNode :: Maybe MediaStreamAudioDestinationNode noMediaStreamAudioDestinationNode = Nothing {-# INLINE noMediaStreamAudioDestinationNode #-} foreign import javascript unsafe "window[\"MediaStreamAudioDestinationNode\"]" gTypeMediaStreamAudioDestinationNode :: GType -- | Functions for this inteface are in "GHCJS.DOM.MediaStreamAudioSourceNode". -- Base interface functions are in: -- -- * "GHCJS.DOM.AudioNode" -- * "GHCJS.DOM.EventTarget" -- -- newtype MediaStreamAudioSourceNode = MediaStreamAudioSourceNode { unMediaStreamAudioSourceNode :: JSVal } instance Eq (MediaStreamAudioSourceNode) where (MediaStreamAudioSourceNode a) == (MediaStreamAudioSourceNode b) = js_eq a b instance PToJSVal MediaStreamAudioSourceNode where pToJSVal = unMediaStreamAudioSourceNode {-# INLINE pToJSVal #-} instance PFromJSVal MediaStreamAudioSourceNode where pFromJSVal = MediaStreamAudioSourceNode {-# INLINE pFromJSVal #-} instance ToJSVal MediaStreamAudioSourceNode where toJSVal = return . unMediaStreamAudioSourceNode {-# INLINE toJSVal #-} instance FromJSVal MediaStreamAudioSourceNode where fromJSVal = return . fmap MediaStreamAudioSourceNode . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsAudioNode MediaStreamAudioSourceNode instance IsEventTarget MediaStreamAudioSourceNode instance IsGObject MediaStreamAudioSourceNode where typeGType _ = gTypeMediaStreamAudioSourceNode {-# INLINE typeGType #-} noMediaStreamAudioSourceNode :: Maybe MediaStreamAudioSourceNode noMediaStreamAudioSourceNode = Nothing {-# INLINE noMediaStreamAudioSourceNode #-} foreign import javascript unsafe "window[\"MediaStreamAudioSourceNode\"]" gTypeMediaStreamAudioSourceNode :: GType -- | Functions for this inteface are in "GHCJS.DOM.MediaStreamConstraints". -- -- newtype MediaStreamConstraints = MediaStreamConstraints { unMediaStreamConstraints :: JSVal } instance Eq (MediaStreamConstraints) where (MediaStreamConstraints a) == (MediaStreamConstraints b) = js_eq a b instance PToJSVal MediaStreamConstraints where pToJSVal = unMediaStreamConstraints {-# INLINE pToJSVal #-} instance PFromJSVal MediaStreamConstraints where pFromJSVal = MediaStreamConstraints {-# INLINE pFromJSVal #-} instance ToJSVal MediaStreamConstraints where toJSVal = return . unMediaStreamConstraints {-# INLINE toJSVal #-} instance FromJSVal MediaStreamConstraints where fromJSVal = return . fmap MediaStreamConstraints . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject MediaStreamConstraints where typeGType _ = gTypeMediaStreamConstraints {-# INLINE typeGType #-} noMediaStreamConstraints :: Maybe MediaStreamConstraints noMediaStreamConstraints = Nothing {-# INLINE noMediaStreamConstraints #-} foreign import javascript unsafe "window[\"MediaStreamConstraints\"]" gTypeMediaStreamConstraints :: GType -- | Functions for this inteface are in "GHCJS.DOM.MediaStreamEvent". -- Base interface functions are in: -- -- * "GHCJS.DOM.Event" -- -- newtype MediaStreamEvent = MediaStreamEvent { unMediaStreamEvent :: JSVal } instance Eq (MediaStreamEvent) where (MediaStreamEvent a) == (MediaStreamEvent b) = js_eq a b instance PToJSVal MediaStreamEvent where pToJSVal = unMediaStreamEvent {-# INLINE pToJSVal #-} instance PFromJSVal MediaStreamEvent where pFromJSVal = MediaStreamEvent {-# INLINE pFromJSVal #-} instance ToJSVal MediaStreamEvent where toJSVal = return . unMediaStreamEvent {-# INLINE toJSVal #-} instance FromJSVal MediaStreamEvent where fromJSVal = return . fmap MediaStreamEvent . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEvent MediaStreamEvent instance IsGObject MediaStreamEvent where typeGType _ = gTypeMediaStreamEvent {-# INLINE typeGType #-} noMediaStreamEvent :: Maybe MediaStreamEvent noMediaStreamEvent = Nothing {-# INLINE noMediaStreamEvent #-} foreign import javascript unsafe "window[\"MediaStreamEvent\"]" gTypeMediaStreamEvent :: GType -- | Functions for this inteface are in "GHCJS.DOM.MediaStreamEventInit". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventInit" -- -- newtype MediaStreamEventInit = MediaStreamEventInit { unMediaStreamEventInit :: JSVal } instance Eq (MediaStreamEventInit) where (MediaStreamEventInit a) == (MediaStreamEventInit b) = js_eq a b instance PToJSVal MediaStreamEventInit where pToJSVal = unMediaStreamEventInit {-# INLINE pToJSVal #-} instance PFromJSVal MediaStreamEventInit where pFromJSVal = MediaStreamEventInit {-# INLINE pFromJSVal #-} instance ToJSVal MediaStreamEventInit where toJSVal = return . unMediaStreamEventInit {-# INLINE toJSVal #-} instance FromJSVal MediaStreamEventInit where fromJSVal = return . fmap MediaStreamEventInit . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventInit MediaStreamEventInit instance IsGObject MediaStreamEventInit where typeGType _ = gTypeMediaStreamEventInit {-# INLINE typeGType #-} noMediaStreamEventInit :: Maybe MediaStreamEventInit noMediaStreamEventInit = Nothing {-# INLINE noMediaStreamEventInit #-} foreign import javascript unsafe "window[\"MediaStreamEventInit\"]" gTypeMediaStreamEventInit :: GType -- | Functions for this inteface are in "GHCJS.DOM.MediaStreamTrack". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventTarget" -- -- newtype MediaStreamTrack = MediaStreamTrack { unMediaStreamTrack :: JSVal } instance Eq (MediaStreamTrack) where (MediaStreamTrack a) == (MediaStreamTrack b) = js_eq a b instance PToJSVal MediaStreamTrack where pToJSVal = unMediaStreamTrack {-# INLINE pToJSVal #-} instance PFromJSVal MediaStreamTrack where pFromJSVal = MediaStreamTrack {-# INLINE pFromJSVal #-} instance ToJSVal MediaStreamTrack where toJSVal = return . unMediaStreamTrack {-# INLINE toJSVal #-} instance FromJSVal MediaStreamTrack where fromJSVal = return . fmap MediaStreamTrack . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsEventTarget o, IsGObject o) => IsMediaStreamTrack o toMediaStreamTrack :: IsMediaStreamTrack o => o -> MediaStreamTrack toMediaStreamTrack = MediaStreamTrack . coerce instance IsMediaStreamTrack MediaStreamTrack instance IsEventTarget MediaStreamTrack instance IsGObject MediaStreamTrack where typeGType _ = gTypeMediaStreamTrack {-# INLINE typeGType #-} noMediaStreamTrack :: Maybe MediaStreamTrack noMediaStreamTrack = Nothing {-# INLINE noMediaStreamTrack #-} foreign import javascript unsafe "window[\"MediaStreamTrack\"]" gTypeMediaStreamTrack :: GType -- | Functions for this inteface are in "GHCJS.DOM.MediaStreamTrackEvent". -- Base interface functions are in: -- -- * "GHCJS.DOM.Event" -- -- newtype MediaStreamTrackEvent = MediaStreamTrackEvent { unMediaStreamTrackEvent :: JSVal } instance Eq (MediaStreamTrackEvent) where (MediaStreamTrackEvent a) == (MediaStreamTrackEvent b) = js_eq a b instance PToJSVal MediaStreamTrackEvent where pToJSVal = unMediaStreamTrackEvent {-# INLINE pToJSVal #-} instance PFromJSVal MediaStreamTrackEvent where pFromJSVal = MediaStreamTrackEvent {-# INLINE pFromJSVal #-} instance ToJSVal MediaStreamTrackEvent where toJSVal = return . unMediaStreamTrackEvent {-# INLINE toJSVal #-} instance FromJSVal MediaStreamTrackEvent where fromJSVal = return . fmap MediaStreamTrackEvent . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEvent MediaStreamTrackEvent instance IsGObject MediaStreamTrackEvent where typeGType _ = gTypeMediaStreamTrackEvent {-# INLINE typeGType #-} noMediaStreamTrackEvent :: Maybe MediaStreamTrackEvent noMediaStreamTrackEvent = Nothing {-# INLINE noMediaStreamTrackEvent #-} foreign import javascript unsafe "window[\"MediaStreamTrackEvent\"]" gTypeMediaStreamTrackEvent :: GType -- | Functions for this inteface are in "GHCJS.DOM.MediaStreamTrackEventInit". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventInit" -- -- newtype MediaStreamTrackEventInit = MediaStreamTrackEventInit { unMediaStreamTrackEventInit :: JSVal } instance Eq (MediaStreamTrackEventInit) where (MediaStreamTrackEventInit a) == (MediaStreamTrackEventInit b) = js_eq a b instance PToJSVal MediaStreamTrackEventInit where pToJSVal = unMediaStreamTrackEventInit {-# INLINE pToJSVal #-} instance PFromJSVal MediaStreamTrackEventInit where pFromJSVal = MediaStreamTrackEventInit {-# INLINE pFromJSVal #-} instance ToJSVal MediaStreamTrackEventInit where toJSVal = return . unMediaStreamTrackEventInit {-# INLINE toJSVal #-} instance FromJSVal MediaStreamTrackEventInit where fromJSVal = return . fmap MediaStreamTrackEventInit . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventInit MediaStreamTrackEventInit instance IsGObject MediaStreamTrackEventInit where typeGType _ = gTypeMediaStreamTrackEventInit {-# INLINE typeGType #-} noMediaStreamTrackEventInit :: Maybe MediaStreamTrackEventInit noMediaStreamTrackEventInit = Nothing {-# INLINE noMediaStreamTrackEventInit #-} foreign import javascript unsafe "window[\"MediaStreamTrackEventInit\"]" gTypeMediaStreamTrackEventInit :: GType -- | Functions for this inteface are in "GHCJS.DOM.MediaTrackCapabilities". -- -- newtype MediaTrackCapabilities = MediaTrackCapabilities { unMediaTrackCapabilities :: JSVal } instance Eq (MediaTrackCapabilities) where (MediaTrackCapabilities a) == (MediaTrackCapabilities b) = js_eq a b instance PToJSVal MediaTrackCapabilities where pToJSVal = unMediaTrackCapabilities {-# INLINE pToJSVal #-} instance PFromJSVal MediaTrackCapabilities where pFromJSVal = MediaTrackCapabilities {-# INLINE pFromJSVal #-} instance ToJSVal MediaTrackCapabilities where toJSVal = return . unMediaTrackCapabilities {-# INLINE toJSVal #-} instance FromJSVal MediaTrackCapabilities where fromJSVal = return . fmap MediaTrackCapabilities . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject MediaTrackCapabilities where typeGType _ = gTypeMediaTrackCapabilities {-# INLINE typeGType #-} noMediaTrackCapabilities :: Maybe MediaTrackCapabilities noMediaTrackCapabilities = Nothing {-# INLINE noMediaTrackCapabilities #-} foreign import javascript unsafe "window[\"MediaTrackCapabilities\"]" gTypeMediaTrackCapabilities :: GType -- | Functions for this inteface are in "GHCJS.DOM.MediaTrackConstraintSet". -- -- newtype MediaTrackConstraintSet = MediaTrackConstraintSet { unMediaTrackConstraintSet :: JSVal } instance Eq (MediaTrackConstraintSet) where (MediaTrackConstraintSet a) == (MediaTrackConstraintSet b) = js_eq a b instance PToJSVal MediaTrackConstraintSet where pToJSVal = unMediaTrackConstraintSet {-# INLINE pToJSVal #-} instance PFromJSVal MediaTrackConstraintSet where pFromJSVal = MediaTrackConstraintSet {-# INLINE pFromJSVal #-} instance ToJSVal MediaTrackConstraintSet where toJSVal = return . unMediaTrackConstraintSet {-# INLINE toJSVal #-} instance FromJSVal MediaTrackConstraintSet where fromJSVal = return . fmap MediaTrackConstraintSet . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsGObject o) => IsMediaTrackConstraintSet o toMediaTrackConstraintSet :: IsMediaTrackConstraintSet o => o -> MediaTrackConstraintSet toMediaTrackConstraintSet = MediaTrackConstraintSet . coerce instance IsMediaTrackConstraintSet MediaTrackConstraintSet instance IsGObject MediaTrackConstraintSet where typeGType _ = gTypeMediaTrackConstraintSet {-# INLINE typeGType #-} noMediaTrackConstraintSet :: Maybe MediaTrackConstraintSet noMediaTrackConstraintSet = Nothing {-# INLINE noMediaTrackConstraintSet #-} foreign import javascript unsafe "window[\"MediaTrackConstraintSet\"]" gTypeMediaTrackConstraintSet :: GType -- | Functions for this inteface are in "GHCJS.DOM.MediaTrackConstraints". -- Base interface functions are in: -- -- * "GHCJS.DOM.MediaTrackConstraintSet" -- -- newtype MediaTrackConstraints = MediaTrackConstraints { unMediaTrackConstraints :: JSVal } instance Eq (MediaTrackConstraints) where (MediaTrackConstraints a) == (MediaTrackConstraints b) = js_eq a b instance PToJSVal MediaTrackConstraints where pToJSVal = unMediaTrackConstraints {-# INLINE pToJSVal #-} instance PFromJSVal MediaTrackConstraints where pFromJSVal = MediaTrackConstraints {-# INLINE pFromJSVal #-} instance ToJSVal MediaTrackConstraints where toJSVal = return . unMediaTrackConstraints {-# INLINE toJSVal #-} instance FromJSVal MediaTrackConstraints where fromJSVal = return . fmap MediaTrackConstraints . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsMediaTrackConstraintSet MediaTrackConstraints instance IsGObject MediaTrackConstraints where typeGType _ = gTypeMediaTrackConstraints {-# INLINE typeGType #-} noMediaTrackConstraints :: Maybe MediaTrackConstraints noMediaTrackConstraints = Nothing {-# INLINE noMediaTrackConstraints #-} foreign import javascript unsafe "window[\"MediaTrackConstraints\"]" gTypeMediaTrackConstraints :: GType -- | Functions for this inteface are in "GHCJS.DOM.MediaTrackSettings". -- -- newtype MediaTrackSettings = MediaTrackSettings { unMediaTrackSettings :: JSVal } instance Eq (MediaTrackSettings) where (MediaTrackSettings a) == (MediaTrackSettings b) = js_eq a b instance PToJSVal MediaTrackSettings where pToJSVal = unMediaTrackSettings {-# INLINE pToJSVal #-} instance PFromJSVal MediaTrackSettings where pFromJSVal = MediaTrackSettings {-# INLINE pFromJSVal #-} instance ToJSVal MediaTrackSettings where toJSVal = return . unMediaTrackSettings {-# INLINE toJSVal #-} instance FromJSVal MediaTrackSettings where fromJSVal = return . fmap MediaTrackSettings . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject MediaTrackSettings where typeGType _ = gTypeMediaTrackSettings {-# INLINE typeGType #-} noMediaTrackSettings :: Maybe MediaTrackSettings noMediaTrackSettings = Nothing {-# INLINE noMediaTrackSettings #-} foreign import javascript unsafe "window[\"MediaTrackSettings\"]" gTypeMediaTrackSettings :: GType -- | Functions for this inteface are in "GHCJS.DOM.MediaTrackSupportedConstraints". -- -- newtype MediaTrackSupportedConstraints = MediaTrackSupportedConstraints { unMediaTrackSupportedConstraints :: JSVal } instance Eq (MediaTrackSupportedConstraints) where (MediaTrackSupportedConstraints a) == (MediaTrackSupportedConstraints b) = js_eq a b instance PToJSVal MediaTrackSupportedConstraints where pToJSVal = unMediaTrackSupportedConstraints {-# INLINE pToJSVal #-} instance PFromJSVal MediaTrackSupportedConstraints where pFromJSVal = MediaTrackSupportedConstraints {-# INLINE pFromJSVal #-} instance ToJSVal MediaTrackSupportedConstraints where toJSVal = return . unMediaTrackSupportedConstraints {-# INLINE toJSVal #-} instance FromJSVal MediaTrackSupportedConstraints where fromJSVal = return . fmap MediaTrackSupportedConstraints . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject MediaTrackSupportedConstraints where typeGType _ = gTypeMediaTrackSupportedConstraints {-# INLINE typeGType #-} noMediaTrackSupportedConstraints :: Maybe MediaTrackSupportedConstraints noMediaTrackSupportedConstraints = Nothing {-# INLINE noMediaTrackSupportedConstraints #-} foreign import javascript unsafe "window[\"MediaTrackSupportedConstraints\"]" gTypeMediaTrackSupportedConstraints :: GType -- | Functions for this inteface are in "GHCJS.DOM.MessageChannel". -- -- newtype MessageChannel = MessageChannel { unMessageChannel :: JSVal } instance Eq (MessageChannel) where (MessageChannel a) == (MessageChannel b) = js_eq a b instance PToJSVal MessageChannel where pToJSVal = unMessageChannel {-# INLINE pToJSVal #-} instance PFromJSVal MessageChannel where pFromJSVal = MessageChannel {-# INLINE pFromJSVal #-} instance ToJSVal MessageChannel where toJSVal = return . unMessageChannel {-# INLINE toJSVal #-} instance FromJSVal MessageChannel where fromJSVal = return . fmap MessageChannel . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject MessageChannel where typeGType _ = gTypeMessageChannel {-# INLINE typeGType #-} noMessageChannel :: Maybe MessageChannel noMessageChannel = Nothing {-# INLINE noMessageChannel #-} foreign import javascript unsafe "window[\"MessageChannel\"]" gTypeMessageChannel :: GType -- | Functions for this inteface are in "GHCJS.DOM.MessageEvent". -- Base interface functions are in: -- -- * "GHCJS.DOM.Event" -- -- newtype MessageEvent = MessageEvent { unMessageEvent :: JSVal } instance Eq (MessageEvent) where (MessageEvent a) == (MessageEvent b) = js_eq a b instance PToJSVal MessageEvent where pToJSVal = unMessageEvent {-# INLINE pToJSVal #-} instance PFromJSVal MessageEvent where pFromJSVal = MessageEvent {-# INLINE pFromJSVal #-} instance ToJSVal MessageEvent where toJSVal = return . unMessageEvent {-# INLINE toJSVal #-} instance FromJSVal MessageEvent where fromJSVal = return . fmap MessageEvent . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEvent MessageEvent instance IsGObject MessageEvent where typeGType _ = gTypeMessageEvent {-# INLINE typeGType #-} noMessageEvent :: Maybe MessageEvent noMessageEvent = Nothing {-# INLINE noMessageEvent #-} foreign import javascript unsafe "window[\"MessageEvent\"]" gTypeMessageEvent :: GType -- | Functions for this inteface are in "GHCJS.DOM.MessageEventInit". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventInit" -- -- newtype MessageEventInit = MessageEventInit { unMessageEventInit :: JSVal } instance Eq (MessageEventInit) where (MessageEventInit a) == (MessageEventInit b) = js_eq a b instance PToJSVal MessageEventInit where pToJSVal = unMessageEventInit {-# INLINE pToJSVal #-} instance PFromJSVal MessageEventInit where pFromJSVal = MessageEventInit {-# INLINE pFromJSVal #-} instance ToJSVal MessageEventInit where toJSVal = return . unMessageEventInit {-# INLINE toJSVal #-} instance FromJSVal MessageEventInit where fromJSVal = return . fmap MessageEventInit . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventInit MessageEventInit instance IsGObject MessageEventInit where typeGType _ = gTypeMessageEventInit {-# INLINE typeGType #-} noMessageEventInit :: Maybe MessageEventInit noMessageEventInit = Nothing {-# INLINE noMessageEventInit #-} foreign import javascript unsafe "window[\"MessageEventInit\"]" gTypeMessageEventInit :: GType -- | Functions for this inteface are in "GHCJS.DOM.MessagePort". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventTarget" -- -- newtype MessagePort = MessagePort { unMessagePort :: JSVal } instance Eq (MessagePort) where (MessagePort a) == (MessagePort b) = js_eq a b instance PToJSVal MessagePort where pToJSVal = unMessagePort {-# INLINE pToJSVal #-} instance PFromJSVal MessagePort where pFromJSVal = MessagePort {-# INLINE pFromJSVal #-} instance ToJSVal MessagePort where toJSVal = return . unMessagePort {-# INLINE toJSVal #-} instance FromJSVal MessagePort where fromJSVal = return . fmap MessagePort . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventTarget MessagePort instance IsGObject MessagePort where typeGType _ = gTypeMessagePort {-# INLINE typeGType #-} noMessagePort :: Maybe MessagePort noMessagePort = Nothing {-# INLINE noMessagePort #-} foreign import javascript unsafe "window[\"MessagePort\"]" gTypeMessagePort :: GType -- | Functions for this inteface are in "GHCJS.DOM.MimeType". -- -- newtype MimeType = MimeType { unMimeType :: JSVal } instance Eq (MimeType) where (MimeType a) == (MimeType b) = js_eq a b instance PToJSVal MimeType where pToJSVal = unMimeType {-# INLINE pToJSVal #-} instance PFromJSVal MimeType where pFromJSVal = MimeType {-# INLINE pFromJSVal #-} instance ToJSVal MimeType where toJSVal = return . unMimeType {-# INLINE toJSVal #-} instance FromJSVal MimeType where fromJSVal = return . fmap MimeType . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject MimeType where typeGType _ = gTypeMimeType {-# INLINE typeGType #-} noMimeType :: Maybe MimeType noMimeType = Nothing {-# INLINE noMimeType #-} foreign import javascript unsafe "window[\"MimeType\"]" gTypeMimeType :: GType -- | Functions for this inteface are in "GHCJS.DOM.MimeTypeArray". -- -- newtype MimeTypeArray = MimeTypeArray { unMimeTypeArray :: JSVal } instance Eq (MimeTypeArray) where (MimeTypeArray a) == (MimeTypeArray b) = js_eq a b instance PToJSVal MimeTypeArray where pToJSVal = unMimeTypeArray {-# INLINE pToJSVal #-} instance PFromJSVal MimeTypeArray where pFromJSVal = MimeTypeArray {-# INLINE pFromJSVal #-} instance ToJSVal MimeTypeArray where toJSVal = return . unMimeTypeArray {-# INLINE toJSVal #-} instance FromJSVal MimeTypeArray where fromJSVal = return . fmap MimeTypeArray . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject MimeTypeArray where typeGType _ = gTypeMimeTypeArray {-# INLINE typeGType #-} noMimeTypeArray :: Maybe MimeTypeArray noMimeTypeArray = Nothing {-# INLINE noMimeTypeArray #-} foreign import javascript unsafe "window[\"MimeTypeArray\"]" gTypeMimeTypeArray :: GType -- | Functions for this inteface are in "GHCJS.DOM.MouseEvent". -- Base interface functions are in: -- -- * "GHCJS.DOM.UIEvent" -- * "GHCJS.DOM.Event" -- -- newtype MouseEvent = MouseEvent { unMouseEvent :: JSVal } instance Eq (MouseEvent) where (MouseEvent a) == (MouseEvent b) = js_eq a b instance PToJSVal MouseEvent where pToJSVal = unMouseEvent {-# INLINE pToJSVal #-} instance PFromJSVal MouseEvent where pFromJSVal = MouseEvent {-# INLINE pFromJSVal #-} instance ToJSVal MouseEvent where toJSVal = return . unMouseEvent {-# INLINE toJSVal #-} instance FromJSVal MouseEvent where fromJSVal = return . fmap MouseEvent . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsUIEvent o, IsEvent o, IsGObject o) => IsMouseEvent o toMouseEvent :: IsMouseEvent o => o -> MouseEvent toMouseEvent = MouseEvent . coerce instance IsMouseEvent MouseEvent instance IsUIEvent MouseEvent instance IsEvent MouseEvent instance IsGObject MouseEvent where typeGType _ = gTypeMouseEvent {-# INLINE typeGType #-} noMouseEvent :: Maybe MouseEvent noMouseEvent = Nothing {-# INLINE noMouseEvent #-} foreign import javascript unsafe "window[\"MouseEvent\"]" gTypeMouseEvent :: GType -- | Functions for this inteface are in "GHCJS.DOM.MouseEventInit". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventModifierInit" -- * "GHCJS.DOM.UIEventInit" -- * "GHCJS.DOM.EventInit" -- -- newtype MouseEventInit = MouseEventInit { unMouseEventInit :: JSVal } instance Eq (MouseEventInit) where (MouseEventInit a) == (MouseEventInit b) = js_eq a b instance PToJSVal MouseEventInit where pToJSVal = unMouseEventInit {-# INLINE pToJSVal #-} instance PFromJSVal MouseEventInit where pFromJSVal = MouseEventInit {-# INLINE pFromJSVal #-} instance ToJSVal MouseEventInit where toJSVal = return . unMouseEventInit {-# INLINE toJSVal #-} instance FromJSVal MouseEventInit where fromJSVal = return . fmap MouseEventInit . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsEventModifierInit o, IsUIEventInit o, IsEventInit o, IsGObject o) => IsMouseEventInit o toMouseEventInit :: IsMouseEventInit o => o -> MouseEventInit toMouseEventInit = MouseEventInit . coerce instance IsMouseEventInit MouseEventInit instance IsEventModifierInit MouseEventInit instance IsUIEventInit MouseEventInit instance IsEventInit MouseEventInit instance IsGObject MouseEventInit where typeGType _ = gTypeMouseEventInit {-# INLINE typeGType #-} noMouseEventInit :: Maybe MouseEventInit noMouseEventInit = Nothing {-# INLINE noMouseEventInit #-} foreign import javascript unsafe "window[\"MouseEventInit\"]" gTypeMouseEventInit :: GType -- | Functions for this inteface are in "GHCJS.DOM.MutationEvent". -- Base interface functions are in: -- -- * "GHCJS.DOM.Event" -- -- newtype MutationEvent = MutationEvent { unMutationEvent :: JSVal } instance Eq (MutationEvent) where (MutationEvent a) == (MutationEvent b) = js_eq a b instance PToJSVal MutationEvent where pToJSVal = unMutationEvent {-# INLINE pToJSVal #-} instance PFromJSVal MutationEvent where pFromJSVal = MutationEvent {-# INLINE pFromJSVal #-} instance ToJSVal MutationEvent where toJSVal = return . unMutationEvent {-# INLINE toJSVal #-} instance FromJSVal MutationEvent where fromJSVal = return . fmap MutationEvent . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEvent MutationEvent instance IsGObject MutationEvent where typeGType _ = gTypeMutationEvent {-# INLINE typeGType #-} noMutationEvent :: Maybe MutationEvent noMutationEvent = Nothing {-# INLINE noMutationEvent #-} foreign import javascript unsafe "window[\"MutationEvent\"]" gTypeMutationEvent :: GType -- | Functions for this inteface are in "GHCJS.DOM.MutationObserver". -- -- newtype MutationObserver = MutationObserver { unMutationObserver :: JSVal } instance Eq (MutationObserver) where (MutationObserver a) == (MutationObserver b) = js_eq a b instance PToJSVal MutationObserver where pToJSVal = unMutationObserver {-# INLINE pToJSVal #-} instance PFromJSVal MutationObserver where pFromJSVal = MutationObserver {-# INLINE pFromJSVal #-} instance ToJSVal MutationObserver where toJSVal = return . unMutationObserver {-# INLINE toJSVal #-} instance FromJSVal MutationObserver where fromJSVal = return . fmap MutationObserver . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject MutationObserver where typeGType _ = gTypeMutationObserver {-# INLINE typeGType #-} noMutationObserver :: Maybe MutationObserver noMutationObserver = Nothing {-# INLINE noMutationObserver #-} foreign import javascript unsafe "window[\"MutationObserver\"]" gTypeMutationObserver :: GType -- | Functions for this inteface are in "GHCJS.DOM.MutationObserverInit". -- -- newtype MutationObserverInit = MutationObserverInit { unMutationObserverInit :: JSVal } instance Eq (MutationObserverInit) where (MutationObserverInit a) == (MutationObserverInit b) = js_eq a b instance PToJSVal MutationObserverInit where pToJSVal = unMutationObserverInit {-# INLINE pToJSVal #-} instance PFromJSVal MutationObserverInit where pFromJSVal = MutationObserverInit {-# INLINE pFromJSVal #-} instance ToJSVal MutationObserverInit where toJSVal = return . unMutationObserverInit {-# INLINE toJSVal #-} instance FromJSVal MutationObserverInit where fromJSVal = return . fmap MutationObserverInit . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject MutationObserverInit where typeGType _ = gTypeMutationObserverInit {-# INLINE typeGType #-} noMutationObserverInit :: Maybe MutationObserverInit noMutationObserverInit = Nothing {-# INLINE noMutationObserverInit #-} foreign import javascript unsafe "window[\"MutationObserverInit\"]" gTypeMutationObserverInit :: GType -- | Functions for this inteface are in "GHCJS.DOM.MutationRecord". -- -- newtype MutationRecord = MutationRecord { unMutationRecord :: JSVal } instance Eq (MutationRecord) where (MutationRecord a) == (MutationRecord b) = js_eq a b instance PToJSVal MutationRecord where pToJSVal = unMutationRecord {-# INLINE pToJSVal #-} instance PFromJSVal MutationRecord where pFromJSVal = MutationRecord {-# INLINE pFromJSVal #-} instance ToJSVal MutationRecord where toJSVal = return . unMutationRecord {-# INLINE toJSVal #-} instance FromJSVal MutationRecord where fromJSVal = return . fmap MutationRecord . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject MutationRecord where typeGType _ = gTypeMutationRecord {-# INLINE typeGType #-} noMutationRecord :: Maybe MutationRecord noMutationRecord = Nothing {-# INLINE noMutationRecord #-} foreign import javascript unsafe "window[\"MutationRecord\"]" gTypeMutationRecord :: GType -- | Functions for this inteface are in "GHCJS.DOM.NamedNodeMap". -- -- newtype NamedNodeMap = NamedNodeMap { unNamedNodeMap :: JSVal } instance Eq (NamedNodeMap) where (NamedNodeMap a) == (NamedNodeMap b) = js_eq a b instance PToJSVal NamedNodeMap where pToJSVal = unNamedNodeMap {-# INLINE pToJSVal #-} instance PFromJSVal NamedNodeMap where pFromJSVal = NamedNodeMap {-# INLINE pFromJSVal #-} instance ToJSVal NamedNodeMap where toJSVal = return . unNamedNodeMap {-# INLINE toJSVal #-} instance FromJSVal NamedNodeMap where fromJSVal = return . fmap NamedNodeMap . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject NamedNodeMap where typeGType _ = gTypeNamedNodeMap {-# INLINE typeGType #-} noNamedNodeMap :: Maybe NamedNodeMap noNamedNodeMap = Nothing {-# INLINE noNamedNodeMap #-} foreign import javascript unsafe "window[\"NamedNodeMap\"]" gTypeNamedNodeMap :: GType -- | Functions for this inteface are in "GHCJS.DOM.Navigator". -- Base interface functions are in: -- -- * "GHCJS.DOM.NavigatorOnLine" -- * "GHCJS.DOM.NavigatorLanguage" -- * "GHCJS.DOM.NavigatorID" -- * "GHCJS.DOM.NavigatorConcurrentHardware" -- -- newtype Navigator = Navigator { unNavigator :: JSVal } instance Eq (Navigator) where (Navigator a) == (Navigator b) = js_eq a b instance PToJSVal Navigator where pToJSVal = unNavigator {-# INLINE pToJSVal #-} instance PFromJSVal Navigator where pFromJSVal = Navigator {-# INLINE pFromJSVal #-} instance ToJSVal Navigator where toJSVal = return . unNavigator {-# INLINE toJSVal #-} instance FromJSVal Navigator where fromJSVal = return . fmap Navigator . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsNavigatorOnLine Navigator instance IsNavigatorLanguage Navigator instance IsNavigatorID Navigator instance IsNavigatorConcurrentHardware Navigator instance IsGObject Navigator where typeGType _ = gTypeNavigator {-# INLINE typeGType #-} noNavigator :: Maybe Navigator noNavigator = Nothing {-# INLINE noNavigator #-} foreign import javascript unsafe "window[\"Navigator\"]" gTypeNavigator :: GType -- | Functions for this inteface are in "GHCJS.DOM.NavigatorConcurrentHardware". -- -- newtype NavigatorConcurrentHardware = NavigatorConcurrentHardware { unNavigatorConcurrentHardware :: JSVal } instance Eq (NavigatorConcurrentHardware) where (NavigatorConcurrentHardware a) == (NavigatorConcurrentHardware b) = js_eq a b instance PToJSVal NavigatorConcurrentHardware where pToJSVal = unNavigatorConcurrentHardware {-# INLINE pToJSVal #-} instance PFromJSVal NavigatorConcurrentHardware where pFromJSVal = NavigatorConcurrentHardware {-# INLINE pFromJSVal #-} instance ToJSVal NavigatorConcurrentHardware where toJSVal = return . unNavigatorConcurrentHardware {-# INLINE toJSVal #-} instance FromJSVal NavigatorConcurrentHardware where fromJSVal = return . fmap NavigatorConcurrentHardware . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsGObject o) => IsNavigatorConcurrentHardware o toNavigatorConcurrentHardware :: IsNavigatorConcurrentHardware o => o -> NavigatorConcurrentHardware toNavigatorConcurrentHardware = NavigatorConcurrentHardware . coerce instance IsNavigatorConcurrentHardware NavigatorConcurrentHardware instance IsGObject NavigatorConcurrentHardware where typeGType _ = gTypeNavigatorConcurrentHardware {-# INLINE typeGType #-} noNavigatorConcurrentHardware :: Maybe NavigatorConcurrentHardware noNavigatorConcurrentHardware = Nothing {-# INLINE noNavigatorConcurrentHardware #-} foreign import javascript unsafe "window[\"NavigatorConcurrentHardware\"]" gTypeNavigatorConcurrentHardware :: GType -- | Functions for this inteface are in "GHCJS.DOM.NavigatorID". -- -- newtype NavigatorID = NavigatorID { unNavigatorID :: JSVal } instance Eq (NavigatorID) where (NavigatorID a) == (NavigatorID b) = js_eq a b instance PToJSVal NavigatorID where pToJSVal = unNavigatorID {-# INLINE pToJSVal #-} instance PFromJSVal NavigatorID where pFromJSVal = NavigatorID {-# INLINE pFromJSVal #-} instance ToJSVal NavigatorID where toJSVal = return . unNavigatorID {-# INLINE toJSVal #-} instance FromJSVal NavigatorID where fromJSVal = return . fmap NavigatorID . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsGObject o) => IsNavigatorID o toNavigatorID :: IsNavigatorID o => o -> NavigatorID toNavigatorID = NavigatorID . coerce instance IsNavigatorID NavigatorID instance IsGObject NavigatorID where typeGType _ = gTypeNavigatorID {-# INLINE typeGType #-} noNavigatorID :: Maybe NavigatorID noNavigatorID = Nothing {-# INLINE noNavigatorID #-} foreign import javascript unsafe "window[\"NavigatorID\"]" gTypeNavigatorID :: GType -- | Functions for this inteface are in "GHCJS.DOM.NavigatorLanguage". -- -- newtype NavigatorLanguage = NavigatorLanguage { unNavigatorLanguage :: JSVal } instance Eq (NavigatorLanguage) where (NavigatorLanguage a) == (NavigatorLanguage b) = js_eq a b instance PToJSVal NavigatorLanguage where pToJSVal = unNavigatorLanguage {-# INLINE pToJSVal #-} instance PFromJSVal NavigatorLanguage where pFromJSVal = NavigatorLanguage {-# INLINE pFromJSVal #-} instance ToJSVal NavigatorLanguage where toJSVal = return . unNavigatorLanguage {-# INLINE toJSVal #-} instance FromJSVal NavigatorLanguage where fromJSVal = return . fmap NavigatorLanguage . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsGObject o) => IsNavigatorLanguage o toNavigatorLanguage :: IsNavigatorLanguage o => o -> NavigatorLanguage toNavigatorLanguage = NavigatorLanguage . coerce instance IsNavigatorLanguage NavigatorLanguage instance IsGObject NavigatorLanguage where typeGType _ = gTypeNavigatorLanguage {-# INLINE typeGType #-} noNavigatorLanguage :: Maybe NavigatorLanguage noNavigatorLanguage = Nothing {-# INLINE noNavigatorLanguage #-} foreign import javascript unsafe "window[\"NavigatorLanguage\"]" gTypeNavigatorLanguage :: GType -- | Functions for this inteface are in "GHCJS.DOM.NavigatorOnLine". -- -- newtype NavigatorOnLine = NavigatorOnLine { unNavigatorOnLine :: JSVal } instance Eq (NavigatorOnLine) where (NavigatorOnLine a) == (NavigatorOnLine b) = js_eq a b instance PToJSVal NavigatorOnLine where pToJSVal = unNavigatorOnLine {-# INLINE pToJSVal #-} instance PFromJSVal NavigatorOnLine where pFromJSVal = NavigatorOnLine {-# INLINE pFromJSVal #-} instance ToJSVal NavigatorOnLine where toJSVal = return . unNavigatorOnLine {-# INLINE toJSVal #-} instance FromJSVal NavigatorOnLine where fromJSVal = return . fmap NavigatorOnLine . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsGObject o) => IsNavigatorOnLine o toNavigatorOnLine :: IsNavigatorOnLine o => o -> NavigatorOnLine toNavigatorOnLine = NavigatorOnLine . coerce instance IsNavigatorOnLine NavigatorOnLine instance IsGObject NavigatorOnLine where typeGType _ = gTypeNavigatorOnLine {-# INLINE typeGType #-} noNavigatorOnLine :: Maybe NavigatorOnLine noNavigatorOnLine = Nothing {-# INLINE noNavigatorOnLine #-} foreign import javascript unsafe "window[\"NavigatorOnLine\"]" gTypeNavigatorOnLine :: GType -- | Functions for this inteface are in "GHCJS.DOM.NavigatorUserMediaError". -- Base interface functions are in: -- -- * "GHCJS.DOM.DOMError" -- -- newtype NavigatorUserMediaError = NavigatorUserMediaError { unNavigatorUserMediaError :: JSVal } instance Eq (NavigatorUserMediaError) where (NavigatorUserMediaError a) == (NavigatorUserMediaError b) = js_eq a b instance PToJSVal NavigatorUserMediaError where pToJSVal = unNavigatorUserMediaError {-# INLINE pToJSVal #-} instance PFromJSVal NavigatorUserMediaError where pFromJSVal = NavigatorUserMediaError {-# INLINE pFromJSVal #-} instance ToJSVal NavigatorUserMediaError where toJSVal = return . unNavigatorUserMediaError {-# INLINE toJSVal #-} instance FromJSVal NavigatorUserMediaError where fromJSVal = return . fmap NavigatorUserMediaError . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsDOMError NavigatorUserMediaError instance IsGObject NavigatorUserMediaError where typeGType _ = gTypeNavigatorUserMediaError {-# INLINE typeGType #-} noNavigatorUserMediaError :: Maybe NavigatorUserMediaError noNavigatorUserMediaError = Nothing {-# INLINE noNavigatorUserMediaError #-} foreign import javascript unsafe "window[\"NavigatorUserMediaError\"]" gTypeNavigatorUserMediaError :: GType -- | Functions for this inteface are in "GHCJS.DOM.Node". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventTarget" -- -- newtype Node = Node { unNode :: JSVal } instance Eq (Node) where (Node a) == (Node b) = js_eq a b instance PToJSVal Node where pToJSVal = unNode {-# INLINE pToJSVal #-} instance PFromJSVal Node where pFromJSVal = Node {-# INLINE pFromJSVal #-} instance ToJSVal Node where toJSVal = return . unNode {-# INLINE toJSVal #-} instance FromJSVal Node where fromJSVal = return . fmap Node . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsEventTarget o, IsGObject o) => IsNode o toNode :: IsNode o => o -> Node toNode = Node . coerce instance IsNode Node instance IsEventTarget Node instance IsGObject Node where typeGType _ = gTypeNode {-# INLINE typeGType #-} noNode :: Maybe Node noNode = Nothing {-# INLINE noNode #-} foreign import javascript unsafe "window[\"Node\"]" gTypeNode :: GType -- | Functions for this inteface are in "GHCJS.DOM.NodeIterator". -- -- newtype NodeIterator = NodeIterator { unNodeIterator :: JSVal } instance Eq (NodeIterator) where (NodeIterator a) == (NodeIterator b) = js_eq a b instance PToJSVal NodeIterator where pToJSVal = unNodeIterator {-# INLINE pToJSVal #-} instance PFromJSVal NodeIterator where pFromJSVal = NodeIterator {-# INLINE pFromJSVal #-} instance ToJSVal NodeIterator where toJSVal = return . unNodeIterator {-# INLINE toJSVal #-} instance FromJSVal NodeIterator where fromJSVal = return . fmap NodeIterator . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject NodeIterator where typeGType _ = gTypeNodeIterator {-# INLINE typeGType #-} noNodeIterator :: Maybe NodeIterator noNodeIterator = Nothing {-# INLINE noNodeIterator #-} foreign import javascript unsafe "window[\"NodeIterator\"]" gTypeNodeIterator :: GType -- | Functions for this inteface are in "GHCJS.DOM.NodeList". -- -- newtype NodeList = NodeList { unNodeList :: JSVal } instance Eq (NodeList) where (NodeList a) == (NodeList b) = js_eq a b instance PToJSVal NodeList where pToJSVal = unNodeList {-# INLINE pToJSVal #-} instance PFromJSVal NodeList where pFromJSVal = NodeList {-# INLINE pFromJSVal #-} instance ToJSVal NodeList where toJSVal = return . unNodeList {-# INLINE toJSVal #-} instance FromJSVal NodeList where fromJSVal = return . fmap NodeList . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsGObject o) => IsNodeList o toNodeList :: IsNodeList o => o -> NodeList toNodeList = NodeList . coerce instance IsNodeList NodeList instance IsGObject NodeList where typeGType _ = gTypeNodeList {-# INLINE typeGType #-} noNodeList :: Maybe NodeList noNodeList = Nothing {-# INLINE noNodeList #-} foreign import javascript unsafe "window[\"NodeList\"]" gTypeNodeList :: GType -- | Functions for this inteface are in "GHCJS.DOM.NonDocumentTypeChildNode". -- -- newtype NonDocumentTypeChildNode = NonDocumentTypeChildNode { unNonDocumentTypeChildNode :: JSVal } instance Eq (NonDocumentTypeChildNode) where (NonDocumentTypeChildNode a) == (NonDocumentTypeChildNode b) = js_eq a b instance PToJSVal NonDocumentTypeChildNode where pToJSVal = unNonDocumentTypeChildNode {-# INLINE pToJSVal #-} instance PFromJSVal NonDocumentTypeChildNode where pFromJSVal = NonDocumentTypeChildNode {-# INLINE pFromJSVal #-} instance ToJSVal NonDocumentTypeChildNode where toJSVal = return . unNonDocumentTypeChildNode {-# INLINE toJSVal #-} instance FromJSVal NonDocumentTypeChildNode where fromJSVal = return . fmap NonDocumentTypeChildNode . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsGObject o) => IsNonDocumentTypeChildNode o toNonDocumentTypeChildNode :: IsNonDocumentTypeChildNode o => o -> NonDocumentTypeChildNode toNonDocumentTypeChildNode = NonDocumentTypeChildNode . coerce instance IsNonDocumentTypeChildNode NonDocumentTypeChildNode instance IsGObject NonDocumentTypeChildNode where typeGType _ = gTypeNonDocumentTypeChildNode {-# INLINE typeGType #-} noNonDocumentTypeChildNode :: Maybe NonDocumentTypeChildNode noNonDocumentTypeChildNode = Nothing {-# INLINE noNonDocumentTypeChildNode #-} foreign import javascript unsafe "window[\"NonDocumentTypeChildNode\"]" gTypeNonDocumentTypeChildNode :: GType -- | Functions for this inteface are in "GHCJS.DOM.NonElementParentNode". -- -- newtype NonElementParentNode = NonElementParentNode { unNonElementParentNode :: JSVal } instance Eq (NonElementParentNode) where (NonElementParentNode a) == (NonElementParentNode b) = js_eq a b instance PToJSVal NonElementParentNode where pToJSVal = unNonElementParentNode {-# INLINE pToJSVal #-} instance PFromJSVal NonElementParentNode where pFromJSVal = NonElementParentNode {-# INLINE pFromJSVal #-} instance ToJSVal NonElementParentNode where toJSVal = return . unNonElementParentNode {-# INLINE toJSVal #-} instance FromJSVal NonElementParentNode where fromJSVal = return . fmap NonElementParentNode . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsGObject o) => IsNonElementParentNode o toNonElementParentNode :: IsNonElementParentNode o => o -> NonElementParentNode toNonElementParentNode = NonElementParentNode . coerce instance IsNonElementParentNode NonElementParentNode instance IsGObject NonElementParentNode where typeGType _ = gTypeNonElementParentNode {-# INLINE typeGType #-} noNonElementParentNode :: Maybe NonElementParentNode noNonElementParentNode = Nothing {-# INLINE noNonElementParentNode #-} foreign import javascript unsafe "window[\"NonElementParentNode\"]" gTypeNonElementParentNode :: GType -- | Functions for this inteface are in "GHCJS.DOM.Notification". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventTarget" -- -- newtype Notification = Notification { unNotification :: JSVal } instance Eq (Notification) where (Notification a) == (Notification b) = js_eq a b instance PToJSVal Notification where pToJSVal = unNotification {-# INLINE pToJSVal #-} instance PFromJSVal Notification where pFromJSVal = Notification {-# INLINE pFromJSVal #-} instance ToJSVal Notification where toJSVal = return . unNotification {-# INLINE toJSVal #-} instance FromJSVal Notification where fromJSVal = return . fmap Notification . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventTarget Notification instance IsGObject Notification where typeGType _ = gTypeNotification {-# INLINE typeGType #-} noNotification :: Maybe Notification noNotification = Nothing {-# INLINE noNotification #-} foreign import javascript unsafe "window[\"Notification\"]" gTypeNotification :: GType -- | Functions for this inteface are in "GHCJS.DOM.NotificationOptions". -- -- newtype NotificationOptions = NotificationOptions { unNotificationOptions :: JSVal } instance Eq (NotificationOptions) where (NotificationOptions a) == (NotificationOptions b) = js_eq a b instance PToJSVal NotificationOptions where pToJSVal = unNotificationOptions {-# INLINE pToJSVal #-} instance PFromJSVal NotificationOptions where pFromJSVal = NotificationOptions {-# INLINE pFromJSVal #-} instance ToJSVal NotificationOptions where toJSVal = return . unNotificationOptions {-# INLINE toJSVal #-} instance FromJSVal NotificationOptions where fromJSVal = return . fmap NotificationOptions . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject NotificationOptions where typeGType _ = gTypeNotificationOptions {-# INLINE typeGType #-} noNotificationOptions :: Maybe NotificationOptions noNotificationOptions = Nothing {-# INLINE noNotificationOptions #-} foreign import javascript unsafe "window[\"NotificationOptions\"]" gTypeNotificationOptions :: GType -- | Functions for this inteface are in "GHCJS.DOM.OESElementIndexUint". -- -- newtype OESElementIndexUint = OESElementIndexUint { unOESElementIndexUint :: JSVal } instance Eq (OESElementIndexUint) where (OESElementIndexUint a) == (OESElementIndexUint b) = js_eq a b instance PToJSVal OESElementIndexUint where pToJSVal = unOESElementIndexUint {-# INLINE pToJSVal #-} instance PFromJSVal OESElementIndexUint where pFromJSVal = OESElementIndexUint {-# INLINE pFromJSVal #-} instance ToJSVal OESElementIndexUint where toJSVal = return . unOESElementIndexUint {-# INLINE toJSVal #-} instance FromJSVal OESElementIndexUint where fromJSVal = return . fmap OESElementIndexUint . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject OESElementIndexUint where typeGType _ = gTypeOESElementIndexUint {-# INLINE typeGType #-} noOESElementIndexUint :: Maybe OESElementIndexUint noOESElementIndexUint = Nothing {-# INLINE noOESElementIndexUint #-} foreign import javascript unsafe "window[\"OESElementIndexUint\"]" gTypeOESElementIndexUint :: GType -- | Functions for this inteface are in "GHCJS.DOM.OESStandardDerivatives". -- -- newtype OESStandardDerivatives = OESStandardDerivatives { unOESStandardDerivatives :: JSVal } instance Eq (OESStandardDerivatives) where (OESStandardDerivatives a) == (OESStandardDerivatives b) = js_eq a b instance PToJSVal OESStandardDerivatives where pToJSVal = unOESStandardDerivatives {-# INLINE pToJSVal #-} instance PFromJSVal OESStandardDerivatives where pFromJSVal = OESStandardDerivatives {-# INLINE pFromJSVal #-} instance ToJSVal OESStandardDerivatives where toJSVal = return . unOESStandardDerivatives {-# INLINE toJSVal #-} instance FromJSVal OESStandardDerivatives where fromJSVal = return . fmap OESStandardDerivatives . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject OESStandardDerivatives where typeGType _ = gTypeOESStandardDerivatives {-# INLINE typeGType #-} noOESStandardDerivatives :: Maybe OESStandardDerivatives noOESStandardDerivatives = Nothing {-# INLINE noOESStandardDerivatives #-} foreign import javascript unsafe "window[\"OESStandardDerivatives\"]" gTypeOESStandardDerivatives :: GType -- | Functions for this inteface are in "GHCJS.DOM.OESTextureFloat". -- -- newtype OESTextureFloat = OESTextureFloat { unOESTextureFloat :: JSVal } instance Eq (OESTextureFloat) where (OESTextureFloat a) == (OESTextureFloat b) = js_eq a b instance PToJSVal OESTextureFloat where pToJSVal = unOESTextureFloat {-# INLINE pToJSVal #-} instance PFromJSVal OESTextureFloat where pFromJSVal = OESTextureFloat {-# INLINE pFromJSVal #-} instance ToJSVal OESTextureFloat where toJSVal = return . unOESTextureFloat {-# INLINE toJSVal #-} instance FromJSVal OESTextureFloat where fromJSVal = return . fmap OESTextureFloat . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject OESTextureFloat where typeGType _ = gTypeOESTextureFloat {-# INLINE typeGType #-} noOESTextureFloat :: Maybe OESTextureFloat noOESTextureFloat = Nothing {-# INLINE noOESTextureFloat #-} foreign import javascript unsafe "window[\"OESTextureFloat\"]" gTypeOESTextureFloat :: GType -- | Functions for this inteface are in "GHCJS.DOM.OESTextureFloatLinear". -- -- newtype OESTextureFloatLinear = OESTextureFloatLinear { unOESTextureFloatLinear :: JSVal } instance Eq (OESTextureFloatLinear) where (OESTextureFloatLinear a) == (OESTextureFloatLinear b) = js_eq a b instance PToJSVal OESTextureFloatLinear where pToJSVal = unOESTextureFloatLinear {-# INLINE pToJSVal #-} instance PFromJSVal OESTextureFloatLinear where pFromJSVal = OESTextureFloatLinear {-# INLINE pFromJSVal #-} instance ToJSVal OESTextureFloatLinear where toJSVal = return . unOESTextureFloatLinear {-# INLINE toJSVal #-} instance FromJSVal OESTextureFloatLinear where fromJSVal = return . fmap OESTextureFloatLinear . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject OESTextureFloatLinear where typeGType _ = gTypeOESTextureFloatLinear {-# INLINE typeGType #-} noOESTextureFloatLinear :: Maybe OESTextureFloatLinear noOESTextureFloatLinear = Nothing {-# INLINE noOESTextureFloatLinear #-} foreign import javascript unsafe "window[\"OESTextureFloatLinear\"]" gTypeOESTextureFloatLinear :: GType -- | Functions for this inteface are in "GHCJS.DOM.OESTextureHalfFloat". -- -- newtype OESTextureHalfFloat = OESTextureHalfFloat { unOESTextureHalfFloat :: JSVal } instance Eq (OESTextureHalfFloat) where (OESTextureHalfFloat a) == (OESTextureHalfFloat b) = js_eq a b instance PToJSVal OESTextureHalfFloat where pToJSVal = unOESTextureHalfFloat {-# INLINE pToJSVal #-} instance PFromJSVal OESTextureHalfFloat where pFromJSVal = OESTextureHalfFloat {-# INLINE pFromJSVal #-} instance ToJSVal OESTextureHalfFloat where toJSVal = return . unOESTextureHalfFloat {-# INLINE toJSVal #-} instance FromJSVal OESTextureHalfFloat where fromJSVal = return . fmap OESTextureHalfFloat . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject OESTextureHalfFloat where typeGType _ = gTypeOESTextureHalfFloat {-# INLINE typeGType #-} noOESTextureHalfFloat :: Maybe OESTextureHalfFloat noOESTextureHalfFloat = Nothing {-# INLINE noOESTextureHalfFloat #-} foreign import javascript unsafe "window[\"OESTextureHalfFloat\"]" gTypeOESTextureHalfFloat :: GType -- | Functions for this inteface are in "GHCJS.DOM.OESTextureHalfFloatLinear". -- -- newtype OESTextureHalfFloatLinear = OESTextureHalfFloatLinear { unOESTextureHalfFloatLinear :: JSVal } instance Eq (OESTextureHalfFloatLinear) where (OESTextureHalfFloatLinear a) == (OESTextureHalfFloatLinear b) = js_eq a b instance PToJSVal OESTextureHalfFloatLinear where pToJSVal = unOESTextureHalfFloatLinear {-# INLINE pToJSVal #-} instance PFromJSVal OESTextureHalfFloatLinear where pFromJSVal = OESTextureHalfFloatLinear {-# INLINE pFromJSVal #-} instance ToJSVal OESTextureHalfFloatLinear where toJSVal = return . unOESTextureHalfFloatLinear {-# INLINE toJSVal #-} instance FromJSVal OESTextureHalfFloatLinear where fromJSVal = return . fmap OESTextureHalfFloatLinear . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject OESTextureHalfFloatLinear where typeGType _ = gTypeOESTextureHalfFloatLinear {-# INLINE typeGType #-} noOESTextureHalfFloatLinear :: Maybe OESTextureHalfFloatLinear noOESTextureHalfFloatLinear = Nothing {-# INLINE noOESTextureHalfFloatLinear #-} foreign import javascript unsafe "window[\"OESTextureHalfFloatLinear\"]" gTypeOESTextureHalfFloatLinear :: GType -- | Functions for this inteface are in "GHCJS.DOM.OESVertexArrayObject". -- -- newtype OESVertexArrayObject = OESVertexArrayObject { unOESVertexArrayObject :: JSVal } instance Eq (OESVertexArrayObject) where (OESVertexArrayObject a) == (OESVertexArrayObject b) = js_eq a b instance PToJSVal OESVertexArrayObject where pToJSVal = unOESVertexArrayObject {-# INLINE pToJSVal #-} instance PFromJSVal OESVertexArrayObject where pFromJSVal = OESVertexArrayObject {-# INLINE pFromJSVal #-} instance ToJSVal OESVertexArrayObject where toJSVal = return . unOESVertexArrayObject {-# INLINE toJSVal #-} instance FromJSVal OESVertexArrayObject where fromJSVal = return . fmap OESVertexArrayObject . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject OESVertexArrayObject where typeGType _ = gTypeOESVertexArrayObject {-# INLINE typeGType #-} noOESVertexArrayObject :: Maybe OESVertexArrayObject noOESVertexArrayObject = Nothing {-# INLINE noOESVertexArrayObject #-} foreign import javascript unsafe "window[\"OESVertexArrayObject\"]" gTypeOESVertexArrayObject :: GType -- | Functions for this inteface are in "GHCJS.DOM.OfflineAudioCompletionEvent". -- Base interface functions are in: -- -- * "GHCJS.DOM.Event" -- -- newtype OfflineAudioCompletionEvent = OfflineAudioCompletionEvent { unOfflineAudioCompletionEvent :: JSVal } instance Eq (OfflineAudioCompletionEvent) where (OfflineAudioCompletionEvent a) == (OfflineAudioCompletionEvent b) = js_eq a b instance PToJSVal OfflineAudioCompletionEvent where pToJSVal = unOfflineAudioCompletionEvent {-# INLINE pToJSVal #-} instance PFromJSVal OfflineAudioCompletionEvent where pFromJSVal = OfflineAudioCompletionEvent {-# INLINE pFromJSVal #-} instance ToJSVal OfflineAudioCompletionEvent where toJSVal = return . unOfflineAudioCompletionEvent {-# INLINE toJSVal #-} instance FromJSVal OfflineAudioCompletionEvent where fromJSVal = return . fmap OfflineAudioCompletionEvent . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEvent OfflineAudioCompletionEvent instance IsGObject OfflineAudioCompletionEvent where typeGType _ = gTypeOfflineAudioCompletionEvent {-# INLINE typeGType #-} noOfflineAudioCompletionEvent :: Maybe OfflineAudioCompletionEvent noOfflineAudioCompletionEvent = Nothing {-# INLINE noOfflineAudioCompletionEvent #-} foreign import javascript unsafe "window[\"OfflineAudioCompletionEvent\"]" gTypeOfflineAudioCompletionEvent :: GType -- | Functions for this inteface are in "GHCJS.DOM.OfflineAudioContext". -- Base interface functions are in: -- -- * "GHCJS.DOM.AudioContext" -- * "GHCJS.DOM.EventTarget" -- -- newtype OfflineAudioContext = OfflineAudioContext { unOfflineAudioContext :: JSVal } instance Eq (OfflineAudioContext) where (OfflineAudioContext a) == (OfflineAudioContext b) = js_eq a b instance PToJSVal OfflineAudioContext where pToJSVal = unOfflineAudioContext {-# INLINE pToJSVal #-} instance PFromJSVal OfflineAudioContext where pFromJSVal = OfflineAudioContext {-# INLINE pFromJSVal #-} instance ToJSVal OfflineAudioContext where toJSVal = return . unOfflineAudioContext {-# INLINE toJSVal #-} instance FromJSVal OfflineAudioContext where fromJSVal = return . fmap OfflineAudioContext . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsAudioContext OfflineAudioContext instance IsEventTarget OfflineAudioContext instance IsGObject OfflineAudioContext where typeGType _ = gTypeOfflineAudioContext {-# INLINE typeGType #-} noOfflineAudioContext :: Maybe OfflineAudioContext noOfflineAudioContext = Nothing {-# INLINE noOfflineAudioContext #-} foreign import javascript unsafe "window[\"OfflineAudioContext\"]" gTypeOfflineAudioContext :: GType -- | Functions for this inteface are in "GHCJS.DOM.OscillatorNode". -- Base interface functions are in: -- -- * "GHCJS.DOM.AudioNode" -- * "GHCJS.DOM.EventTarget" -- -- newtype OscillatorNode = OscillatorNode { unOscillatorNode :: JSVal } instance Eq (OscillatorNode) where (OscillatorNode a) == (OscillatorNode b) = js_eq a b instance PToJSVal OscillatorNode where pToJSVal = unOscillatorNode {-# INLINE pToJSVal #-} instance PFromJSVal OscillatorNode where pFromJSVal = OscillatorNode {-# INLINE pFromJSVal #-} instance ToJSVal OscillatorNode where toJSVal = return . unOscillatorNode {-# INLINE toJSVal #-} instance FromJSVal OscillatorNode where fromJSVal = return . fmap OscillatorNode . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsAudioNode OscillatorNode instance IsEventTarget OscillatorNode instance IsGObject OscillatorNode where typeGType _ = gTypeOscillatorNode {-# INLINE typeGType #-} noOscillatorNode :: Maybe OscillatorNode noOscillatorNode = Nothing {-# INLINE noOscillatorNode #-} foreign import javascript unsafe "window[\"OscillatorNode\"]" gTypeOscillatorNode :: GType -- | Functions for this inteface are in "GHCJS.DOM.OverconstrainedError". -- -- newtype OverconstrainedError = OverconstrainedError { unOverconstrainedError :: JSVal } instance Eq (OverconstrainedError) where (OverconstrainedError a) == (OverconstrainedError b) = js_eq a b instance PToJSVal OverconstrainedError where pToJSVal = unOverconstrainedError {-# INLINE pToJSVal #-} instance PFromJSVal OverconstrainedError where pFromJSVal = OverconstrainedError {-# INLINE pFromJSVal #-} instance ToJSVal OverconstrainedError where toJSVal = return . unOverconstrainedError {-# INLINE toJSVal #-} instance FromJSVal OverconstrainedError where fromJSVal = return . fmap OverconstrainedError . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject OverconstrainedError where typeGType _ = gTypeOverconstrainedError {-# INLINE typeGType #-} noOverconstrainedError :: Maybe OverconstrainedError noOverconstrainedError = Nothing {-# INLINE noOverconstrainedError #-} foreign import javascript unsafe "window[\"OverconstrainedError\"]" gTypeOverconstrainedError :: GType -- | Functions for this inteface are in "GHCJS.DOM.OverconstrainedErrorEvent". -- Base interface functions are in: -- -- * "GHCJS.DOM.Event" -- -- newtype OverconstrainedErrorEvent = OverconstrainedErrorEvent { unOverconstrainedErrorEvent :: JSVal } instance Eq (OverconstrainedErrorEvent) where (OverconstrainedErrorEvent a) == (OverconstrainedErrorEvent b) = js_eq a b instance PToJSVal OverconstrainedErrorEvent where pToJSVal = unOverconstrainedErrorEvent {-# INLINE pToJSVal #-} instance PFromJSVal OverconstrainedErrorEvent where pFromJSVal = OverconstrainedErrorEvent {-# INLINE pFromJSVal #-} instance ToJSVal OverconstrainedErrorEvent where toJSVal = return . unOverconstrainedErrorEvent {-# INLINE toJSVal #-} instance FromJSVal OverconstrainedErrorEvent where fromJSVal = return . fmap OverconstrainedErrorEvent . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEvent OverconstrainedErrorEvent instance IsGObject OverconstrainedErrorEvent where typeGType _ = gTypeOverconstrainedErrorEvent {-# INLINE typeGType #-} noOverconstrainedErrorEvent :: Maybe OverconstrainedErrorEvent noOverconstrainedErrorEvent = Nothing {-# INLINE noOverconstrainedErrorEvent #-} foreign import javascript unsafe "window[\"OverconstrainedErrorEvent\"]" gTypeOverconstrainedErrorEvent :: GType -- | Functions for this inteface are in "GHCJS.DOM.OverconstrainedErrorEventInit". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventInit" -- -- newtype OverconstrainedErrorEventInit = OverconstrainedErrorEventInit { unOverconstrainedErrorEventInit :: JSVal } instance Eq (OverconstrainedErrorEventInit) where (OverconstrainedErrorEventInit a) == (OverconstrainedErrorEventInit b) = js_eq a b instance PToJSVal OverconstrainedErrorEventInit where pToJSVal = unOverconstrainedErrorEventInit {-# INLINE pToJSVal #-} instance PFromJSVal OverconstrainedErrorEventInit where pFromJSVal = OverconstrainedErrorEventInit {-# INLINE pFromJSVal #-} instance ToJSVal OverconstrainedErrorEventInit where toJSVal = return . unOverconstrainedErrorEventInit {-# INLINE toJSVal #-} instance FromJSVal OverconstrainedErrorEventInit where fromJSVal = return . fmap OverconstrainedErrorEventInit . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventInit OverconstrainedErrorEventInit instance IsGObject OverconstrainedErrorEventInit where typeGType _ = gTypeOverconstrainedErrorEventInit {-# INLINE typeGType #-} noOverconstrainedErrorEventInit :: Maybe OverconstrainedErrorEventInit noOverconstrainedErrorEventInit = Nothing {-# INLINE noOverconstrainedErrorEventInit #-} foreign import javascript unsafe "window[\"OverconstrainedErrorEventInit\"]" gTypeOverconstrainedErrorEventInit :: GType -- | Functions for this inteface are in "GHCJS.DOM.OverflowEvent". -- Base interface functions are in: -- -- * "GHCJS.DOM.Event" -- -- newtype OverflowEvent = OverflowEvent { unOverflowEvent :: JSVal } instance Eq (OverflowEvent) where (OverflowEvent a) == (OverflowEvent b) = js_eq a b instance PToJSVal OverflowEvent where pToJSVal = unOverflowEvent {-# INLINE pToJSVal #-} instance PFromJSVal OverflowEvent where pFromJSVal = OverflowEvent {-# INLINE pFromJSVal #-} instance ToJSVal OverflowEvent where toJSVal = return . unOverflowEvent {-# INLINE toJSVal #-} instance FromJSVal OverflowEvent where fromJSVal = return . fmap OverflowEvent . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEvent OverflowEvent instance IsGObject OverflowEvent where typeGType _ = gTypeOverflowEvent {-# INLINE typeGType #-} noOverflowEvent :: Maybe OverflowEvent noOverflowEvent = Nothing {-# INLINE noOverflowEvent #-} foreign import javascript unsafe "window[\"OverflowEvent\"]" gTypeOverflowEvent :: GType -- | Functions for this inteface are in "GHCJS.DOM.OverflowEventInit". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventInit" -- -- newtype OverflowEventInit = OverflowEventInit { unOverflowEventInit :: JSVal } instance Eq (OverflowEventInit) where (OverflowEventInit a) == (OverflowEventInit b) = js_eq a b instance PToJSVal OverflowEventInit where pToJSVal = unOverflowEventInit {-# INLINE pToJSVal #-} instance PFromJSVal OverflowEventInit where pFromJSVal = OverflowEventInit {-# INLINE pFromJSVal #-} instance ToJSVal OverflowEventInit where toJSVal = return . unOverflowEventInit {-# INLINE toJSVal #-} instance FromJSVal OverflowEventInit where fromJSVal = return . fmap OverflowEventInit . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventInit OverflowEventInit instance IsGObject OverflowEventInit where typeGType _ = gTypeOverflowEventInit {-# INLINE typeGType #-} noOverflowEventInit :: Maybe OverflowEventInit noOverflowEventInit = Nothing {-# INLINE noOverflowEventInit #-} foreign import javascript unsafe "window[\"OverflowEventInit\"]" gTypeOverflowEventInit :: GType -- | Functions for this inteface are in "GHCJS.DOM.PageTransitionEvent". -- Base interface functions are in: -- -- * "GHCJS.DOM.Event" -- -- newtype PageTransitionEvent = PageTransitionEvent { unPageTransitionEvent :: JSVal } instance Eq (PageTransitionEvent) where (PageTransitionEvent a) == (PageTransitionEvent b) = js_eq a b instance PToJSVal PageTransitionEvent where pToJSVal = unPageTransitionEvent {-# INLINE pToJSVal #-} instance PFromJSVal PageTransitionEvent where pFromJSVal = PageTransitionEvent {-# INLINE pFromJSVal #-} instance ToJSVal PageTransitionEvent where toJSVal = return . unPageTransitionEvent {-# INLINE toJSVal #-} instance FromJSVal PageTransitionEvent where fromJSVal = return . fmap PageTransitionEvent . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEvent PageTransitionEvent instance IsGObject PageTransitionEvent where typeGType _ = gTypePageTransitionEvent {-# INLINE typeGType #-} noPageTransitionEvent :: Maybe PageTransitionEvent noPageTransitionEvent = Nothing {-# INLINE noPageTransitionEvent #-} foreign import javascript unsafe "window[\"PageTransitionEvent\"]" gTypePageTransitionEvent :: GType -- | Functions for this inteface are in "GHCJS.DOM.PageTransitionEventInit". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventInit" -- -- newtype PageTransitionEventInit = PageTransitionEventInit { unPageTransitionEventInit :: JSVal } instance Eq (PageTransitionEventInit) where (PageTransitionEventInit a) == (PageTransitionEventInit b) = js_eq a b instance PToJSVal PageTransitionEventInit where pToJSVal = unPageTransitionEventInit {-# INLINE pToJSVal #-} instance PFromJSVal PageTransitionEventInit where pFromJSVal = PageTransitionEventInit {-# INLINE pFromJSVal #-} instance ToJSVal PageTransitionEventInit where toJSVal = return . unPageTransitionEventInit {-# INLINE toJSVal #-} instance FromJSVal PageTransitionEventInit where fromJSVal = return . fmap PageTransitionEventInit . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventInit PageTransitionEventInit instance IsGObject PageTransitionEventInit where typeGType _ = gTypePageTransitionEventInit {-# INLINE typeGType #-} noPageTransitionEventInit :: Maybe PageTransitionEventInit noPageTransitionEventInit = Nothing {-# INLINE noPageTransitionEventInit #-} foreign import javascript unsafe "window[\"PageTransitionEventInit\"]" gTypePageTransitionEventInit :: GType -- | Functions for this inteface are in "GHCJS.DOM.PannerNode". -- Base interface functions are in: -- -- * "GHCJS.DOM.AudioNode" -- * "GHCJS.DOM.EventTarget" -- -- newtype PannerNode = PannerNode { unPannerNode :: JSVal } instance Eq (PannerNode) where (PannerNode a) == (PannerNode b) = js_eq a b instance PToJSVal PannerNode where pToJSVal = unPannerNode {-# INLINE pToJSVal #-} instance PFromJSVal PannerNode where pFromJSVal = PannerNode {-# INLINE pFromJSVal #-} instance ToJSVal PannerNode where toJSVal = return . unPannerNode {-# INLINE toJSVal #-} instance FromJSVal PannerNode where fromJSVal = return . fmap PannerNode . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsAudioNode PannerNode instance IsEventTarget PannerNode instance IsGObject PannerNode where typeGType _ = gTypePannerNode {-# INLINE typeGType #-} noPannerNode :: Maybe PannerNode noPannerNode = Nothing {-# INLINE noPannerNode #-} foreign import javascript unsafe "window[\"webkitAudioPannerNode\"]" gTypePannerNode :: GType -- | Functions for this inteface are in "GHCJS.DOM.ParentNode". -- -- newtype ParentNode = ParentNode { unParentNode :: JSVal } instance Eq (ParentNode) where (ParentNode a) == (ParentNode b) = js_eq a b instance PToJSVal ParentNode where pToJSVal = unParentNode {-# INLINE pToJSVal #-} instance PFromJSVal ParentNode where pFromJSVal = ParentNode {-# INLINE pFromJSVal #-} instance ToJSVal ParentNode where toJSVal = return . unParentNode {-# INLINE toJSVal #-} instance FromJSVal ParentNode where fromJSVal = return . fmap ParentNode . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsGObject o) => IsParentNode o toParentNode :: IsParentNode o => o -> ParentNode toParentNode = ParentNode . coerce instance IsParentNode ParentNode instance IsGObject ParentNode where typeGType _ = gTypeParentNode {-# INLINE typeGType #-} noParentNode :: Maybe ParentNode noParentNode = Nothing {-# INLINE noParentNode #-} foreign import javascript unsafe "window[\"ParentNode\"]" gTypeParentNode :: GType -- | Functions for this inteface are in "GHCJS.DOM.PasswordCredential". -- Base interface functions are in: -- -- * "GHCJS.DOM.SiteBoundCredential" -- * "GHCJS.DOM.BasicCredential" -- -- newtype PasswordCredential = PasswordCredential { unPasswordCredential :: JSVal } instance Eq (PasswordCredential) where (PasswordCredential a) == (PasswordCredential b) = js_eq a b instance PToJSVal PasswordCredential where pToJSVal = unPasswordCredential {-# INLINE pToJSVal #-} instance PFromJSVal PasswordCredential where pFromJSVal = PasswordCredential {-# INLINE pFromJSVal #-} instance ToJSVal PasswordCredential where toJSVal = return . unPasswordCredential {-# INLINE toJSVal #-} instance FromJSVal PasswordCredential where fromJSVal = return . fmap PasswordCredential . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSiteBoundCredential PasswordCredential instance IsBasicCredential PasswordCredential instance IsGObject PasswordCredential where typeGType _ = gTypePasswordCredential {-# INLINE typeGType #-} noPasswordCredential :: Maybe PasswordCredential noPasswordCredential = Nothing {-# INLINE noPasswordCredential #-} foreign import javascript unsafe "window[\"PasswordCredential\"]" gTypePasswordCredential :: GType -- | Functions for this inteface are in "GHCJS.DOM.PasswordCredentialData". -- Base interface functions are in: -- -- * "GHCJS.DOM.SiteBoundCredentialData" -- * "GHCJS.DOM.CredentialData" -- -- newtype PasswordCredentialData = PasswordCredentialData { unPasswordCredentialData :: JSVal } instance Eq (PasswordCredentialData) where (PasswordCredentialData a) == (PasswordCredentialData b) = js_eq a b instance PToJSVal PasswordCredentialData where pToJSVal = unPasswordCredentialData {-# INLINE pToJSVal #-} instance PFromJSVal PasswordCredentialData where pFromJSVal = PasswordCredentialData {-# INLINE pFromJSVal #-} instance ToJSVal PasswordCredentialData where toJSVal = return . unPasswordCredentialData {-# INLINE toJSVal #-} instance FromJSVal PasswordCredentialData where fromJSVal = return . fmap PasswordCredentialData . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSiteBoundCredentialData PasswordCredentialData instance IsCredentialData PasswordCredentialData instance IsGObject PasswordCredentialData where typeGType _ = gTypePasswordCredentialData {-# INLINE typeGType #-} noPasswordCredentialData :: Maybe PasswordCredentialData noPasswordCredentialData = Nothing {-# INLINE noPasswordCredentialData #-} foreign import javascript unsafe "window[\"PasswordCredentialData\"]" gTypePasswordCredentialData :: GType -- | Functions for this inteface are in "GHCJS.DOM.Path2D". -- Base interface functions are in: -- -- * "GHCJS.DOM.CanvasPath" -- -- newtype Path2D = Path2D { unPath2D :: JSVal } instance Eq (Path2D) where (Path2D a) == (Path2D b) = js_eq a b instance PToJSVal Path2D where pToJSVal = unPath2D {-# INLINE pToJSVal #-} instance PFromJSVal Path2D where pFromJSVal = Path2D {-# INLINE pFromJSVal #-} instance ToJSVal Path2D where toJSVal = return . unPath2D {-# INLINE toJSVal #-} instance FromJSVal Path2D where fromJSVal = return . fmap Path2D . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsCanvasPath Path2D instance IsGObject Path2D where typeGType _ = gTypePath2D {-# INLINE typeGType #-} noPath2D :: Maybe Path2D noPath2D = Nothing {-# INLINE noPath2D #-} foreign import javascript unsafe "window[\"Path2D\"]" gTypePath2D :: GType -- | Functions for this inteface are in "GHCJS.DOM.Pbkdf2Params". -- Base interface functions are in: -- -- * "GHCJS.DOM.CryptoAlgorithmParameters" -- -- newtype Pbkdf2Params = Pbkdf2Params { unPbkdf2Params :: JSVal } instance Eq (Pbkdf2Params) where (Pbkdf2Params a) == (Pbkdf2Params b) = js_eq a b instance PToJSVal Pbkdf2Params where pToJSVal = unPbkdf2Params {-# INLINE pToJSVal #-} instance PFromJSVal Pbkdf2Params where pFromJSVal = Pbkdf2Params {-# INLINE pFromJSVal #-} instance ToJSVal Pbkdf2Params where toJSVal = return . unPbkdf2Params {-# INLINE toJSVal #-} instance FromJSVal Pbkdf2Params where fromJSVal = return . fmap Pbkdf2Params . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsCryptoAlgorithmParameters Pbkdf2Params instance IsGObject Pbkdf2Params where typeGType _ = gTypePbkdf2Params {-# INLINE typeGType #-} noPbkdf2Params :: Maybe Pbkdf2Params noPbkdf2Params = Nothing {-# INLINE noPbkdf2Params #-} foreign import javascript unsafe "window[\"Pbkdf2Params\"]" gTypePbkdf2Params :: GType -- | Functions for this inteface are in "GHCJS.DOM.Performance". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventTarget" -- -- newtype Performance = Performance { unPerformance :: JSVal } instance Eq (Performance) where (Performance a) == (Performance b) = js_eq a b instance PToJSVal Performance where pToJSVal = unPerformance {-# INLINE pToJSVal #-} instance PFromJSVal Performance where pFromJSVal = Performance {-# INLINE pFromJSVal #-} instance ToJSVal Performance where toJSVal = return . unPerformance {-# INLINE toJSVal #-} instance FromJSVal Performance where fromJSVal = return . fmap Performance . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventTarget Performance instance IsGObject Performance where typeGType _ = gTypePerformance {-# INLINE typeGType #-} noPerformance :: Maybe Performance noPerformance = Nothing {-# INLINE noPerformance #-} foreign import javascript unsafe "window[\"Performance\"]" gTypePerformance :: GType -- | Functions for this inteface are in "GHCJS.DOM.PerformanceEntry". -- -- newtype PerformanceEntry = PerformanceEntry { unPerformanceEntry :: JSVal } instance Eq (PerformanceEntry) where (PerformanceEntry a) == (PerformanceEntry b) = js_eq a b instance PToJSVal PerformanceEntry where pToJSVal = unPerformanceEntry {-# INLINE pToJSVal #-} instance PFromJSVal PerformanceEntry where pFromJSVal = PerformanceEntry {-# INLINE pFromJSVal #-} instance ToJSVal PerformanceEntry where toJSVal = return . unPerformanceEntry {-# INLINE toJSVal #-} instance FromJSVal PerformanceEntry where fromJSVal = return . fmap PerformanceEntry . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsGObject o) => IsPerformanceEntry o toPerformanceEntry :: IsPerformanceEntry o => o -> PerformanceEntry toPerformanceEntry = PerformanceEntry . coerce instance IsPerformanceEntry PerformanceEntry instance IsGObject PerformanceEntry where typeGType _ = gTypePerformanceEntry {-# INLINE typeGType #-} noPerformanceEntry :: Maybe PerformanceEntry noPerformanceEntry = Nothing {-# INLINE noPerformanceEntry #-} foreign import javascript unsafe "window[\"PerformanceEntry\"]" gTypePerformanceEntry :: GType -- | Functions for this inteface are in "GHCJS.DOM.PerformanceMark". -- Base interface functions are in: -- -- * "GHCJS.DOM.PerformanceEntry" -- -- newtype PerformanceMark = PerformanceMark { unPerformanceMark :: JSVal } instance Eq (PerformanceMark) where (PerformanceMark a) == (PerformanceMark b) = js_eq a b instance PToJSVal PerformanceMark where pToJSVal = unPerformanceMark {-# INLINE pToJSVal #-} instance PFromJSVal PerformanceMark where pFromJSVal = PerformanceMark {-# INLINE pFromJSVal #-} instance ToJSVal PerformanceMark where toJSVal = return . unPerformanceMark {-# INLINE toJSVal #-} instance FromJSVal PerformanceMark where fromJSVal = return . fmap PerformanceMark . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsPerformanceEntry PerformanceMark instance IsGObject PerformanceMark where typeGType _ = gTypePerformanceMark {-# INLINE typeGType #-} noPerformanceMark :: Maybe PerformanceMark noPerformanceMark = Nothing {-# INLINE noPerformanceMark #-} foreign import javascript unsafe "window[\"PerformanceMark\"]" gTypePerformanceMark :: GType -- | Functions for this inteface are in "GHCJS.DOM.PerformanceMeasure". -- Base interface functions are in: -- -- * "GHCJS.DOM.PerformanceEntry" -- -- newtype PerformanceMeasure = PerformanceMeasure { unPerformanceMeasure :: JSVal } instance Eq (PerformanceMeasure) where (PerformanceMeasure a) == (PerformanceMeasure b) = js_eq a b instance PToJSVal PerformanceMeasure where pToJSVal = unPerformanceMeasure {-# INLINE pToJSVal #-} instance PFromJSVal PerformanceMeasure where pFromJSVal = PerformanceMeasure {-# INLINE pFromJSVal #-} instance ToJSVal PerformanceMeasure where toJSVal = return . unPerformanceMeasure {-# INLINE toJSVal #-} instance FromJSVal PerformanceMeasure where fromJSVal = return . fmap PerformanceMeasure . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsPerformanceEntry PerformanceMeasure instance IsGObject PerformanceMeasure where typeGType _ = gTypePerformanceMeasure {-# INLINE typeGType #-} noPerformanceMeasure :: Maybe PerformanceMeasure noPerformanceMeasure = Nothing {-# INLINE noPerformanceMeasure #-} foreign import javascript unsafe "window[\"PerformanceMeasure\"]" gTypePerformanceMeasure :: GType -- | Functions for this inteface are in "GHCJS.DOM.PerformanceNavigation". -- -- newtype PerformanceNavigation = PerformanceNavigation { unPerformanceNavigation :: JSVal } instance Eq (PerformanceNavigation) where (PerformanceNavigation a) == (PerformanceNavigation b) = js_eq a b instance PToJSVal PerformanceNavigation where pToJSVal = unPerformanceNavigation {-# INLINE pToJSVal #-} instance PFromJSVal PerformanceNavigation where pFromJSVal = PerformanceNavigation {-# INLINE pFromJSVal #-} instance ToJSVal PerformanceNavigation where toJSVal = return . unPerformanceNavigation {-# INLINE toJSVal #-} instance FromJSVal PerformanceNavigation where fromJSVal = return . fmap PerformanceNavigation . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject PerformanceNavigation where typeGType _ = gTypePerformanceNavigation {-# INLINE typeGType #-} noPerformanceNavigation :: Maybe PerformanceNavigation noPerformanceNavigation = Nothing {-# INLINE noPerformanceNavigation #-} foreign import javascript unsafe "window[\"PerformanceNavigation\"]" gTypePerformanceNavigation :: GType -- | Functions for this inteface are in "GHCJS.DOM.PerformanceObserver". -- -- newtype PerformanceObserver = PerformanceObserver { unPerformanceObserver :: JSVal } instance Eq (PerformanceObserver) where (PerformanceObserver a) == (PerformanceObserver b) = js_eq a b instance PToJSVal PerformanceObserver where pToJSVal = unPerformanceObserver {-# INLINE pToJSVal #-} instance PFromJSVal PerformanceObserver where pFromJSVal = PerformanceObserver {-# INLINE pFromJSVal #-} instance ToJSVal PerformanceObserver where toJSVal = return . unPerformanceObserver {-# INLINE toJSVal #-} instance FromJSVal PerformanceObserver where fromJSVal = return . fmap PerformanceObserver . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject PerformanceObserver where typeGType _ = gTypePerformanceObserver {-# INLINE typeGType #-} noPerformanceObserver :: Maybe PerformanceObserver noPerformanceObserver = Nothing {-# INLINE noPerformanceObserver #-} foreign import javascript unsafe "window[\"PerformanceObserver\"]" gTypePerformanceObserver :: GType -- | Functions for this inteface are in "GHCJS.DOM.PerformanceObserverEntryList". -- -- newtype PerformanceObserverEntryList = PerformanceObserverEntryList { unPerformanceObserverEntryList :: JSVal } instance Eq (PerformanceObserverEntryList) where (PerformanceObserverEntryList a) == (PerformanceObserverEntryList b) = js_eq a b instance PToJSVal PerformanceObserverEntryList where pToJSVal = unPerformanceObserverEntryList {-# INLINE pToJSVal #-} instance PFromJSVal PerformanceObserverEntryList where pFromJSVal = PerformanceObserverEntryList {-# INLINE pFromJSVal #-} instance ToJSVal PerformanceObserverEntryList where toJSVal = return . unPerformanceObserverEntryList {-# INLINE toJSVal #-} instance FromJSVal PerformanceObserverEntryList where fromJSVal = return . fmap PerformanceObserverEntryList . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject PerformanceObserverEntryList where typeGType _ = gTypePerformanceObserverEntryList {-# INLINE typeGType #-} noPerformanceObserverEntryList :: Maybe PerformanceObserverEntryList noPerformanceObserverEntryList = Nothing {-# INLINE noPerformanceObserverEntryList #-} foreign import javascript unsafe "window[\"PerformanceObserverEntryList\"]" gTypePerformanceObserverEntryList :: GType -- | Functions for this inteface are in "GHCJS.DOM.PerformanceObserverInit". -- -- newtype PerformanceObserverInit = PerformanceObserverInit { unPerformanceObserverInit :: JSVal } instance Eq (PerformanceObserverInit) where (PerformanceObserverInit a) == (PerformanceObserverInit b) = js_eq a b instance PToJSVal PerformanceObserverInit where pToJSVal = unPerformanceObserverInit {-# INLINE pToJSVal #-} instance PFromJSVal PerformanceObserverInit where pFromJSVal = PerformanceObserverInit {-# INLINE pFromJSVal #-} instance ToJSVal PerformanceObserverInit where toJSVal = return . unPerformanceObserverInit {-# INLINE toJSVal #-} instance FromJSVal PerformanceObserverInit where fromJSVal = return . fmap PerformanceObserverInit . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject PerformanceObserverInit where typeGType _ = gTypePerformanceObserverInit {-# INLINE typeGType #-} noPerformanceObserverInit :: Maybe PerformanceObserverInit noPerformanceObserverInit = Nothing {-# INLINE noPerformanceObserverInit #-} foreign import javascript unsafe "window[\"PerformanceObserverInit\"]" gTypePerformanceObserverInit :: GType -- | Functions for this inteface are in "GHCJS.DOM.PerformanceResourceTiming". -- Base interface functions are in: -- -- * "GHCJS.DOM.PerformanceEntry" -- -- newtype PerformanceResourceTiming = PerformanceResourceTiming { unPerformanceResourceTiming :: JSVal } instance Eq (PerformanceResourceTiming) where (PerformanceResourceTiming a) == (PerformanceResourceTiming b) = js_eq a b instance PToJSVal PerformanceResourceTiming where pToJSVal = unPerformanceResourceTiming {-# INLINE pToJSVal #-} instance PFromJSVal PerformanceResourceTiming where pFromJSVal = PerformanceResourceTiming {-# INLINE pFromJSVal #-} instance ToJSVal PerformanceResourceTiming where toJSVal = return . unPerformanceResourceTiming {-# INLINE toJSVal #-} instance FromJSVal PerformanceResourceTiming where fromJSVal = return . fmap PerformanceResourceTiming . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsPerformanceEntry PerformanceResourceTiming instance IsGObject PerformanceResourceTiming where typeGType _ = gTypePerformanceResourceTiming {-# INLINE typeGType #-} noPerformanceResourceTiming :: Maybe PerformanceResourceTiming noPerformanceResourceTiming = Nothing {-# INLINE noPerformanceResourceTiming #-} foreign import javascript unsafe "window[\"PerformanceResourceTiming\"]" gTypePerformanceResourceTiming :: GType -- | Functions for this inteface are in "GHCJS.DOM.PerformanceTiming". -- -- newtype PerformanceTiming = PerformanceTiming { unPerformanceTiming :: JSVal } instance Eq (PerformanceTiming) where (PerformanceTiming a) == (PerformanceTiming b) = js_eq a b instance PToJSVal PerformanceTiming where pToJSVal = unPerformanceTiming {-# INLINE pToJSVal #-} instance PFromJSVal PerformanceTiming where pFromJSVal = PerformanceTiming {-# INLINE pFromJSVal #-} instance ToJSVal PerformanceTiming where toJSVal = return . unPerformanceTiming {-# INLINE toJSVal #-} instance FromJSVal PerformanceTiming where fromJSVal = return . fmap PerformanceTiming . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject PerformanceTiming where typeGType _ = gTypePerformanceTiming {-# INLINE typeGType #-} noPerformanceTiming :: Maybe PerformanceTiming noPerformanceTiming = Nothing {-# INLINE noPerformanceTiming #-} foreign import javascript unsafe "window[\"PerformanceTiming\"]" gTypePerformanceTiming :: GType -- | Functions for this inteface are in "GHCJS.DOM.PeriodicWave". -- -- newtype PeriodicWave = PeriodicWave { unPeriodicWave :: JSVal } instance Eq (PeriodicWave) where (PeriodicWave a) == (PeriodicWave b) = js_eq a b instance PToJSVal PeriodicWave where pToJSVal = unPeriodicWave {-# INLINE pToJSVal #-} instance PFromJSVal PeriodicWave where pFromJSVal = PeriodicWave {-# INLINE pFromJSVal #-} instance ToJSVal PeriodicWave where toJSVal = return . unPeriodicWave {-# INLINE toJSVal #-} instance FromJSVal PeriodicWave where fromJSVal = return . fmap PeriodicWave . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject PeriodicWave where typeGType _ = gTypePeriodicWave {-# INLINE typeGType #-} noPeriodicWave :: Maybe PeriodicWave noPeriodicWave = Nothing {-# INLINE noPeriodicWave #-} foreign import javascript unsafe "window[\"PeriodicWave\"]" gTypePeriodicWave :: GType -- | Functions for this inteface are in "GHCJS.DOM.Plugin". -- -- newtype Plugin = Plugin { unPlugin :: JSVal } instance Eq (Plugin) where (Plugin a) == (Plugin b) = js_eq a b instance PToJSVal Plugin where pToJSVal = unPlugin {-# INLINE pToJSVal #-} instance PFromJSVal Plugin where pFromJSVal = Plugin {-# INLINE pFromJSVal #-} instance ToJSVal Plugin where toJSVal = return . unPlugin {-# INLINE toJSVal #-} instance FromJSVal Plugin where fromJSVal = return . fmap Plugin . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject Plugin where typeGType _ = gTypePlugin {-# INLINE typeGType #-} noPlugin :: Maybe Plugin noPlugin = Nothing {-# INLINE noPlugin #-} foreign import javascript unsafe "window[\"Plugin\"]" gTypePlugin :: GType -- | Functions for this inteface are in "GHCJS.DOM.PluginArray". -- -- newtype PluginArray = PluginArray { unPluginArray :: JSVal } instance Eq (PluginArray) where (PluginArray a) == (PluginArray b) = js_eq a b instance PToJSVal PluginArray where pToJSVal = unPluginArray {-# INLINE pToJSVal #-} instance PFromJSVal PluginArray where pFromJSVal = PluginArray {-# INLINE pFromJSVal #-} instance ToJSVal PluginArray where toJSVal = return . unPluginArray {-# INLINE toJSVal #-} instance FromJSVal PluginArray where fromJSVal = return . fmap PluginArray . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject PluginArray where typeGType _ = gTypePluginArray {-# INLINE typeGType #-} noPluginArray :: Maybe PluginArray noPluginArray = Nothing {-# INLINE noPluginArray #-} foreign import javascript unsafe "window[\"PluginArray\"]" gTypePluginArray :: GType -- | Functions for this inteface are in "GHCJS.DOM.PopStateEvent". -- Base interface functions are in: -- -- * "GHCJS.DOM.Event" -- -- newtype PopStateEvent = PopStateEvent { unPopStateEvent :: JSVal } instance Eq (PopStateEvent) where (PopStateEvent a) == (PopStateEvent b) = js_eq a b instance PToJSVal PopStateEvent where pToJSVal = unPopStateEvent {-# INLINE pToJSVal #-} instance PFromJSVal PopStateEvent where pFromJSVal = PopStateEvent {-# INLINE pFromJSVal #-} instance ToJSVal PopStateEvent where toJSVal = return . unPopStateEvent {-# INLINE toJSVal #-} instance FromJSVal PopStateEvent where fromJSVal = return . fmap PopStateEvent . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEvent PopStateEvent instance IsGObject PopStateEvent where typeGType _ = gTypePopStateEvent {-# INLINE typeGType #-} noPopStateEvent :: Maybe PopStateEvent noPopStateEvent = Nothing {-# INLINE noPopStateEvent #-} foreign import javascript unsafe "window[\"PopStateEvent\"]" gTypePopStateEvent :: GType -- | Functions for this inteface are in "GHCJS.DOM.PopStateEventInit". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventInit" -- -- newtype PopStateEventInit = PopStateEventInit { unPopStateEventInit :: JSVal } instance Eq (PopStateEventInit) where (PopStateEventInit a) == (PopStateEventInit b) = js_eq a b instance PToJSVal PopStateEventInit where pToJSVal = unPopStateEventInit {-# INLINE pToJSVal #-} instance PFromJSVal PopStateEventInit where pFromJSVal = PopStateEventInit {-# INLINE pFromJSVal #-} instance ToJSVal PopStateEventInit where toJSVal = return . unPopStateEventInit {-# INLINE toJSVal #-} instance FromJSVal PopStateEventInit where fromJSVal = return . fmap PopStateEventInit . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventInit PopStateEventInit instance IsGObject PopStateEventInit where typeGType _ = gTypePopStateEventInit {-# INLINE typeGType #-} noPopStateEventInit :: Maybe PopStateEventInit noPopStateEventInit = Nothing {-# INLINE noPopStateEventInit #-} foreign import javascript unsafe "window[\"PopStateEventInit\"]" gTypePopStateEventInit :: GType -- | Functions for this inteface are in "GHCJS.DOM.PositionError". -- -- newtype PositionError = PositionError { unPositionError :: JSVal } instance Eq (PositionError) where (PositionError a) == (PositionError b) = js_eq a b instance PToJSVal PositionError where pToJSVal = unPositionError {-# INLINE pToJSVal #-} instance PFromJSVal PositionError where pFromJSVal = PositionError {-# INLINE pFromJSVal #-} instance ToJSVal PositionError where toJSVal = return . unPositionError {-# INLINE toJSVal #-} instance FromJSVal PositionError where fromJSVal = return . fmap PositionError . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject PositionError where typeGType _ = gTypePositionError {-# INLINE typeGType #-} noPositionError :: Maybe PositionError noPositionError = Nothing {-# INLINE noPositionError #-} foreign import javascript unsafe "window[\"PositionError\"]" gTypePositionError :: GType -- | Functions for this inteface are in "GHCJS.DOM.PositionOptions". -- -- newtype PositionOptions = PositionOptions { unPositionOptions :: JSVal } instance Eq (PositionOptions) where (PositionOptions a) == (PositionOptions b) = js_eq a b instance PToJSVal PositionOptions where pToJSVal = unPositionOptions {-# INLINE pToJSVal #-} instance PFromJSVal PositionOptions where pFromJSVal = PositionOptions {-# INLINE pFromJSVal #-} instance ToJSVal PositionOptions where toJSVal = return . unPositionOptions {-# INLINE toJSVal #-} instance FromJSVal PositionOptions where fromJSVal = return . fmap PositionOptions . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject PositionOptions where typeGType _ = gTypePositionOptions {-# INLINE typeGType #-} noPositionOptions :: Maybe PositionOptions noPositionOptions = Nothing {-# INLINE noPositionOptions #-} foreign import javascript unsafe "window[\"PositionOptions\"]" gTypePositionOptions :: GType -- | Functions for this inteface are in "GHCJS.DOM.ProcessingInstruction". -- Base interface functions are in: -- -- * "GHCJS.DOM.CharacterData" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.ChildNode" -- -- newtype ProcessingInstruction = ProcessingInstruction { unProcessingInstruction :: JSVal } instance Eq (ProcessingInstruction) where (ProcessingInstruction a) == (ProcessingInstruction b) = js_eq a b instance PToJSVal ProcessingInstruction where pToJSVal = unProcessingInstruction {-# INLINE pToJSVal #-} instance PFromJSVal ProcessingInstruction where pFromJSVal = ProcessingInstruction {-# INLINE pFromJSVal #-} instance ToJSVal ProcessingInstruction where toJSVal = return . unProcessingInstruction {-# INLINE toJSVal #-} instance FromJSVal ProcessingInstruction where fromJSVal = return . fmap ProcessingInstruction . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsCharacterData ProcessingInstruction instance IsNode ProcessingInstruction instance IsEventTarget ProcessingInstruction instance IsNonDocumentTypeChildNode ProcessingInstruction instance IsChildNode ProcessingInstruction instance IsGObject ProcessingInstruction where typeGType _ = gTypeProcessingInstruction {-# INLINE typeGType #-} noProcessingInstruction :: Maybe ProcessingInstruction noProcessingInstruction = Nothing {-# INLINE noProcessingInstruction #-} foreign import javascript unsafe "window[\"ProcessingInstruction\"]" gTypeProcessingInstruction :: GType -- | Functions for this inteface are in "GHCJS.DOM.ProgressEvent". -- Base interface functions are in: -- -- * "GHCJS.DOM.Event" -- -- newtype ProgressEvent = ProgressEvent { unProgressEvent :: JSVal } instance Eq (ProgressEvent) where (ProgressEvent a) == (ProgressEvent b) = js_eq a b instance PToJSVal ProgressEvent where pToJSVal = unProgressEvent {-# INLINE pToJSVal #-} instance PFromJSVal ProgressEvent where pFromJSVal = ProgressEvent {-# INLINE pFromJSVal #-} instance ToJSVal ProgressEvent where toJSVal = return . unProgressEvent {-# INLINE toJSVal #-} instance FromJSVal ProgressEvent where fromJSVal = return . fmap ProgressEvent . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsEvent o, IsGObject o) => IsProgressEvent o toProgressEvent :: IsProgressEvent o => o -> ProgressEvent toProgressEvent = ProgressEvent . coerce instance IsProgressEvent ProgressEvent instance IsEvent ProgressEvent instance IsGObject ProgressEvent where typeGType _ = gTypeProgressEvent {-# INLINE typeGType #-} noProgressEvent :: Maybe ProgressEvent noProgressEvent = Nothing {-# INLINE noProgressEvent #-} foreign import javascript unsafe "window[\"ProgressEvent\"]" gTypeProgressEvent :: GType -- | Functions for this inteface are in "GHCJS.DOM.ProgressEventInit". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventInit" -- -- newtype ProgressEventInit = ProgressEventInit { unProgressEventInit :: JSVal } instance Eq (ProgressEventInit) where (ProgressEventInit a) == (ProgressEventInit b) = js_eq a b instance PToJSVal ProgressEventInit where pToJSVal = unProgressEventInit {-# INLINE pToJSVal #-} instance PFromJSVal ProgressEventInit where pFromJSVal = ProgressEventInit {-# INLINE pFromJSVal #-} instance ToJSVal ProgressEventInit where toJSVal = return . unProgressEventInit {-# INLINE toJSVal #-} instance FromJSVal ProgressEventInit where fromJSVal = return . fmap ProgressEventInit . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventInit ProgressEventInit instance IsGObject ProgressEventInit where typeGType _ = gTypeProgressEventInit {-# INLINE typeGType #-} noProgressEventInit :: Maybe ProgressEventInit noProgressEventInit = Nothing {-# INLINE noProgressEventInit #-} foreign import javascript unsafe "window[\"ProgressEventInit\"]" gTypeProgressEventInit :: GType -- | Functions for this inteface are in "GHCJS.DOM.PromiseRejectionEvent". -- Base interface functions are in: -- -- * "GHCJS.DOM.Event" -- -- newtype PromiseRejectionEvent = PromiseRejectionEvent { unPromiseRejectionEvent :: JSVal } instance Eq (PromiseRejectionEvent) where (PromiseRejectionEvent a) == (PromiseRejectionEvent b) = js_eq a b instance PToJSVal PromiseRejectionEvent where pToJSVal = unPromiseRejectionEvent {-# INLINE pToJSVal #-} instance PFromJSVal PromiseRejectionEvent where pFromJSVal = PromiseRejectionEvent {-# INLINE pFromJSVal #-} instance ToJSVal PromiseRejectionEvent where toJSVal = return . unPromiseRejectionEvent {-# INLINE toJSVal #-} instance FromJSVal PromiseRejectionEvent where fromJSVal = return . fmap PromiseRejectionEvent . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEvent PromiseRejectionEvent instance IsGObject PromiseRejectionEvent where typeGType _ = gTypePromiseRejectionEvent {-# INLINE typeGType #-} noPromiseRejectionEvent :: Maybe PromiseRejectionEvent noPromiseRejectionEvent = Nothing {-# INLINE noPromiseRejectionEvent #-} foreign import javascript unsafe "window[\"PromiseRejectionEvent\"]" gTypePromiseRejectionEvent :: GType -- | Functions for this inteface are in "GHCJS.DOM.PromiseRejectionEventInit". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventInit" -- -- newtype PromiseRejectionEventInit = PromiseRejectionEventInit { unPromiseRejectionEventInit :: JSVal } instance Eq (PromiseRejectionEventInit) where (PromiseRejectionEventInit a) == (PromiseRejectionEventInit b) = js_eq a b instance PToJSVal PromiseRejectionEventInit where pToJSVal = unPromiseRejectionEventInit {-# INLINE pToJSVal #-} instance PFromJSVal PromiseRejectionEventInit where pFromJSVal = PromiseRejectionEventInit {-# INLINE pFromJSVal #-} instance ToJSVal PromiseRejectionEventInit where toJSVal = return . unPromiseRejectionEventInit {-# INLINE toJSVal #-} instance FromJSVal PromiseRejectionEventInit where fromJSVal = return . fmap PromiseRejectionEventInit . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventInit PromiseRejectionEventInit instance IsGObject PromiseRejectionEventInit where typeGType _ = gTypePromiseRejectionEventInit {-# INLINE typeGType #-} noPromiseRejectionEventInit :: Maybe PromiseRejectionEventInit noPromiseRejectionEventInit = Nothing {-# INLINE noPromiseRejectionEventInit #-} foreign import javascript unsafe "window[\"PromiseRejectionEventInit\"]" gTypePromiseRejectionEventInit :: GType -- | Functions for this inteface are in "GHCJS.DOM.QuickTimePluginReplacement". -- -- newtype QuickTimePluginReplacement = QuickTimePluginReplacement { unQuickTimePluginReplacement :: JSVal } instance Eq (QuickTimePluginReplacement) where (QuickTimePluginReplacement a) == (QuickTimePluginReplacement b) = js_eq a b instance PToJSVal QuickTimePluginReplacement where pToJSVal = unQuickTimePluginReplacement {-# INLINE pToJSVal #-} instance PFromJSVal QuickTimePluginReplacement where pFromJSVal = QuickTimePluginReplacement {-# INLINE pFromJSVal #-} instance ToJSVal QuickTimePluginReplacement where toJSVal = return . unQuickTimePluginReplacement {-# INLINE toJSVal #-} instance FromJSVal QuickTimePluginReplacement where fromJSVal = return . fmap QuickTimePluginReplacement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject QuickTimePluginReplacement where typeGType _ = gTypeQuickTimePluginReplacement {-# INLINE typeGType #-} noQuickTimePluginReplacement :: Maybe QuickTimePluginReplacement noQuickTimePluginReplacement = Nothing {-# INLINE noQuickTimePluginReplacement #-} foreign import javascript unsafe "window[\"QuickTimePluginReplacement\"]" gTypeQuickTimePluginReplacement :: GType -- | Functions for this inteface are in "GHCJS.DOM.RGBColor". -- -- newtype RGBColor = RGBColor { unRGBColor :: JSVal } instance Eq (RGBColor) where (RGBColor a) == (RGBColor b) = js_eq a b instance PToJSVal RGBColor where pToJSVal = unRGBColor {-# INLINE pToJSVal #-} instance PFromJSVal RGBColor where pFromJSVal = RGBColor {-# INLINE pFromJSVal #-} instance ToJSVal RGBColor where toJSVal = return . unRGBColor {-# INLINE toJSVal #-} instance FromJSVal RGBColor where fromJSVal = return . fmap RGBColor . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject RGBColor where typeGType _ = gTypeRGBColor {-# INLINE typeGType #-} noRGBColor :: Maybe RGBColor noRGBColor = Nothing {-# INLINE noRGBColor #-} foreign import javascript unsafe "window[\"RGBColor\"]" gTypeRGBColor :: GType -- | Functions for this inteface are in "GHCJS.DOM.RTCAnswerOptions". -- Base interface functions are in: -- -- * "GHCJS.DOM.RTCOfferAnswerOptions" -- -- newtype RTCAnswerOptions = RTCAnswerOptions { unRTCAnswerOptions :: JSVal } instance Eq (RTCAnswerOptions) where (RTCAnswerOptions a) == (RTCAnswerOptions b) = js_eq a b instance PToJSVal RTCAnswerOptions where pToJSVal = unRTCAnswerOptions {-# INLINE pToJSVal #-} instance PFromJSVal RTCAnswerOptions where pFromJSVal = RTCAnswerOptions {-# INLINE pFromJSVal #-} instance ToJSVal RTCAnswerOptions where toJSVal = return . unRTCAnswerOptions {-# INLINE toJSVal #-} instance FromJSVal RTCAnswerOptions where fromJSVal = return . fmap RTCAnswerOptions . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsRTCOfferAnswerOptions RTCAnswerOptions instance IsGObject RTCAnswerOptions where typeGType _ = gTypeRTCAnswerOptions {-# INLINE typeGType #-} noRTCAnswerOptions :: Maybe RTCAnswerOptions noRTCAnswerOptions = Nothing {-# INLINE noRTCAnswerOptions #-} foreign import javascript unsafe "window[\"RTCAnswerOptions\"]" gTypeRTCAnswerOptions :: GType -- | Functions for this inteface are in "GHCJS.DOM.RTCConfiguration". -- -- newtype RTCConfiguration = RTCConfiguration { unRTCConfiguration :: JSVal } instance Eq (RTCConfiguration) where (RTCConfiguration a) == (RTCConfiguration b) = js_eq a b instance PToJSVal RTCConfiguration where pToJSVal = unRTCConfiguration {-# INLINE pToJSVal #-} instance PFromJSVal RTCConfiguration where pFromJSVal = RTCConfiguration {-# INLINE pFromJSVal #-} instance ToJSVal RTCConfiguration where toJSVal = return . unRTCConfiguration {-# INLINE toJSVal #-} instance FromJSVal RTCConfiguration where fromJSVal = return . fmap RTCConfiguration . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject RTCConfiguration where typeGType _ = gTypeRTCConfiguration {-# INLINE typeGType #-} noRTCConfiguration :: Maybe RTCConfiguration noRTCConfiguration = Nothing {-# INLINE noRTCConfiguration #-} foreign import javascript unsafe "window[\"RTCConfiguration\"]" gTypeRTCConfiguration :: GType -- | Functions for this inteface are in "GHCJS.DOM.RTCDTMFSender". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventTarget" -- -- newtype RTCDTMFSender = RTCDTMFSender { unRTCDTMFSender :: JSVal } instance Eq (RTCDTMFSender) where (RTCDTMFSender a) == (RTCDTMFSender b) = js_eq a b instance PToJSVal RTCDTMFSender where pToJSVal = unRTCDTMFSender {-# INLINE pToJSVal #-} instance PFromJSVal RTCDTMFSender where pFromJSVal = RTCDTMFSender {-# INLINE pFromJSVal #-} instance ToJSVal RTCDTMFSender where toJSVal = return . unRTCDTMFSender {-# INLINE toJSVal #-} instance FromJSVal RTCDTMFSender where fromJSVal = return . fmap RTCDTMFSender . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventTarget RTCDTMFSender instance IsGObject RTCDTMFSender where typeGType _ = gTypeRTCDTMFSender {-# INLINE typeGType #-} noRTCDTMFSender :: Maybe RTCDTMFSender noRTCDTMFSender = Nothing {-# INLINE noRTCDTMFSender #-} foreign import javascript unsafe "window[\"RTCDTMFSender\"]" gTypeRTCDTMFSender :: GType -- | Functions for this inteface are in "GHCJS.DOM.RTCDTMFToneChangeEvent". -- Base interface functions are in: -- -- * "GHCJS.DOM.Event" -- -- newtype RTCDTMFToneChangeEvent = RTCDTMFToneChangeEvent { unRTCDTMFToneChangeEvent :: JSVal } instance Eq (RTCDTMFToneChangeEvent) where (RTCDTMFToneChangeEvent a) == (RTCDTMFToneChangeEvent b) = js_eq a b instance PToJSVal RTCDTMFToneChangeEvent where pToJSVal = unRTCDTMFToneChangeEvent {-# INLINE pToJSVal #-} instance PFromJSVal RTCDTMFToneChangeEvent where pFromJSVal = RTCDTMFToneChangeEvent {-# INLINE pFromJSVal #-} instance ToJSVal RTCDTMFToneChangeEvent where toJSVal = return . unRTCDTMFToneChangeEvent {-# INLINE toJSVal #-} instance FromJSVal RTCDTMFToneChangeEvent where fromJSVal = return . fmap RTCDTMFToneChangeEvent . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEvent RTCDTMFToneChangeEvent instance IsGObject RTCDTMFToneChangeEvent where typeGType _ = gTypeRTCDTMFToneChangeEvent {-# INLINE typeGType #-} noRTCDTMFToneChangeEvent :: Maybe RTCDTMFToneChangeEvent noRTCDTMFToneChangeEvent = Nothing {-# INLINE noRTCDTMFToneChangeEvent #-} foreign import javascript unsafe "window[\"RTCDTMFToneChangeEvent\"]" gTypeRTCDTMFToneChangeEvent :: GType -- | Functions for this inteface are in "GHCJS.DOM.RTCDTMFToneChangeEventInit". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventInit" -- -- newtype RTCDTMFToneChangeEventInit = RTCDTMFToneChangeEventInit { unRTCDTMFToneChangeEventInit :: JSVal } instance Eq (RTCDTMFToneChangeEventInit) where (RTCDTMFToneChangeEventInit a) == (RTCDTMFToneChangeEventInit b) = js_eq a b instance PToJSVal RTCDTMFToneChangeEventInit where pToJSVal = unRTCDTMFToneChangeEventInit {-# INLINE pToJSVal #-} instance PFromJSVal RTCDTMFToneChangeEventInit where pFromJSVal = RTCDTMFToneChangeEventInit {-# INLINE pFromJSVal #-} instance ToJSVal RTCDTMFToneChangeEventInit where toJSVal = return . unRTCDTMFToneChangeEventInit {-# INLINE toJSVal #-} instance FromJSVal RTCDTMFToneChangeEventInit where fromJSVal = return . fmap RTCDTMFToneChangeEventInit . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventInit RTCDTMFToneChangeEventInit instance IsGObject RTCDTMFToneChangeEventInit where typeGType _ = gTypeRTCDTMFToneChangeEventInit {-# INLINE typeGType #-} noRTCDTMFToneChangeEventInit :: Maybe RTCDTMFToneChangeEventInit noRTCDTMFToneChangeEventInit = Nothing {-# INLINE noRTCDTMFToneChangeEventInit #-} foreign import javascript unsafe "window[\"RTCDTMFToneChangeEventInit\"]" gTypeRTCDTMFToneChangeEventInit :: GType -- | Functions for this inteface are in "GHCJS.DOM.RTCDataChannel". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventTarget" -- -- newtype RTCDataChannel = RTCDataChannel { unRTCDataChannel :: JSVal } instance Eq (RTCDataChannel) where (RTCDataChannel a) == (RTCDataChannel b) = js_eq a b instance PToJSVal RTCDataChannel where pToJSVal = unRTCDataChannel {-# INLINE pToJSVal #-} instance PFromJSVal RTCDataChannel where pFromJSVal = RTCDataChannel {-# INLINE pFromJSVal #-} instance ToJSVal RTCDataChannel where toJSVal = return . unRTCDataChannel {-# INLINE toJSVal #-} instance FromJSVal RTCDataChannel where fromJSVal = return . fmap RTCDataChannel . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventTarget RTCDataChannel instance IsGObject RTCDataChannel where typeGType _ = gTypeRTCDataChannel {-# INLINE typeGType #-} noRTCDataChannel :: Maybe RTCDataChannel noRTCDataChannel = Nothing {-# INLINE noRTCDataChannel #-} foreign import javascript unsafe "window[\"RTCDataChannel\"]" gTypeRTCDataChannel :: GType -- | Functions for this inteface are in "GHCJS.DOM.RTCDataChannelEvent". -- Base interface functions are in: -- -- * "GHCJS.DOM.Event" -- -- newtype RTCDataChannelEvent = RTCDataChannelEvent { unRTCDataChannelEvent :: JSVal } instance Eq (RTCDataChannelEvent) where (RTCDataChannelEvent a) == (RTCDataChannelEvent b) = js_eq a b instance PToJSVal RTCDataChannelEvent where pToJSVal = unRTCDataChannelEvent {-# INLINE pToJSVal #-} instance PFromJSVal RTCDataChannelEvent where pFromJSVal = RTCDataChannelEvent {-# INLINE pFromJSVal #-} instance ToJSVal RTCDataChannelEvent where toJSVal = return . unRTCDataChannelEvent {-# INLINE toJSVal #-} instance FromJSVal RTCDataChannelEvent where fromJSVal = return . fmap RTCDataChannelEvent . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEvent RTCDataChannelEvent instance IsGObject RTCDataChannelEvent where typeGType _ = gTypeRTCDataChannelEvent {-# INLINE typeGType #-} noRTCDataChannelEvent :: Maybe RTCDataChannelEvent noRTCDataChannelEvent = Nothing {-# INLINE noRTCDataChannelEvent #-} foreign import javascript unsafe "window[\"RTCDataChannelEvent\"]" gTypeRTCDataChannelEvent :: GType -- | Functions for this inteface are in "GHCJS.DOM.RTCDataChannelEventInit". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventInit" -- -- newtype RTCDataChannelEventInit = RTCDataChannelEventInit { unRTCDataChannelEventInit :: JSVal } instance Eq (RTCDataChannelEventInit) where (RTCDataChannelEventInit a) == (RTCDataChannelEventInit b) = js_eq a b instance PToJSVal RTCDataChannelEventInit where pToJSVal = unRTCDataChannelEventInit {-# INLINE pToJSVal #-} instance PFromJSVal RTCDataChannelEventInit where pFromJSVal = RTCDataChannelEventInit {-# INLINE pFromJSVal #-} instance ToJSVal RTCDataChannelEventInit where toJSVal = return . unRTCDataChannelEventInit {-# INLINE toJSVal #-} instance FromJSVal RTCDataChannelEventInit where fromJSVal = return . fmap RTCDataChannelEventInit . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventInit RTCDataChannelEventInit instance IsGObject RTCDataChannelEventInit where typeGType _ = gTypeRTCDataChannelEventInit {-# INLINE typeGType #-} noRTCDataChannelEventInit :: Maybe RTCDataChannelEventInit noRTCDataChannelEventInit = Nothing {-# INLINE noRTCDataChannelEventInit #-} foreign import javascript unsafe "window[\"RTCDataChannelEventInit\"]" gTypeRTCDataChannelEventInit :: GType -- | Functions for this inteface are in "GHCJS.DOM.RTCDataChannelInit". -- -- newtype RTCDataChannelInit = RTCDataChannelInit { unRTCDataChannelInit :: JSVal } instance Eq (RTCDataChannelInit) where (RTCDataChannelInit a) == (RTCDataChannelInit b) = js_eq a b instance PToJSVal RTCDataChannelInit where pToJSVal = unRTCDataChannelInit {-# INLINE pToJSVal #-} instance PFromJSVal RTCDataChannelInit where pFromJSVal = RTCDataChannelInit {-# INLINE pFromJSVal #-} instance ToJSVal RTCDataChannelInit where toJSVal = return . unRTCDataChannelInit {-# INLINE toJSVal #-} instance FromJSVal RTCDataChannelInit where fromJSVal = return . fmap RTCDataChannelInit . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject RTCDataChannelInit where typeGType _ = gTypeRTCDataChannelInit {-# INLINE typeGType #-} noRTCDataChannelInit :: Maybe RTCDataChannelInit noRTCDataChannelInit = Nothing {-# INLINE noRTCDataChannelInit #-} foreign import javascript unsafe "window[\"RTCDataChannelInit\"]" gTypeRTCDataChannelInit :: GType -- | Functions for this inteface are in "GHCJS.DOM.RTCDataChannelStats". -- Base interface functions are in: -- -- * "GHCJS.DOM.RTCStats" -- -- newtype RTCDataChannelStats = RTCDataChannelStats { unRTCDataChannelStats :: JSVal } instance Eq (RTCDataChannelStats) where (RTCDataChannelStats a) == (RTCDataChannelStats b) = js_eq a b instance PToJSVal RTCDataChannelStats where pToJSVal = unRTCDataChannelStats {-# INLINE pToJSVal #-} instance PFromJSVal RTCDataChannelStats where pFromJSVal = RTCDataChannelStats {-# INLINE pFromJSVal #-} instance ToJSVal RTCDataChannelStats where toJSVal = return . unRTCDataChannelStats {-# INLINE toJSVal #-} instance FromJSVal RTCDataChannelStats where fromJSVal = return . fmap RTCDataChannelStats . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsRTCStats RTCDataChannelStats instance IsGObject RTCDataChannelStats where typeGType _ = gTypeRTCDataChannelStats {-# INLINE typeGType #-} noRTCDataChannelStats :: Maybe RTCDataChannelStats noRTCDataChannelStats = Nothing {-# INLINE noRTCDataChannelStats #-} foreign import javascript unsafe "window[\"RTCDataChannelStats\"]" gTypeRTCDataChannelStats :: GType -- | Functions for this inteface are in "GHCJS.DOM.RTCIceCandidate". -- -- newtype RTCIceCandidate = RTCIceCandidate { unRTCIceCandidate :: JSVal } instance Eq (RTCIceCandidate) where (RTCIceCandidate a) == (RTCIceCandidate b) = js_eq a b instance PToJSVal RTCIceCandidate where pToJSVal = unRTCIceCandidate {-# INLINE pToJSVal #-} instance PFromJSVal RTCIceCandidate where pFromJSVal = RTCIceCandidate {-# INLINE pFromJSVal #-} instance ToJSVal RTCIceCandidate where toJSVal = return . unRTCIceCandidate {-# INLINE toJSVal #-} instance FromJSVal RTCIceCandidate where fromJSVal = return . fmap RTCIceCandidate . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject RTCIceCandidate where typeGType _ = gTypeRTCIceCandidate {-# INLINE typeGType #-} noRTCIceCandidate :: Maybe RTCIceCandidate noRTCIceCandidate = Nothing {-# INLINE noRTCIceCandidate #-} foreign import javascript unsafe "window[\"RTCIceCandidate\"]" gTypeRTCIceCandidate :: GType -- | Functions for this inteface are in "GHCJS.DOM.RTCIceCandidateEvent". -- Base interface functions are in: -- -- * "GHCJS.DOM.Event" -- -- newtype RTCIceCandidateEvent = RTCIceCandidateEvent { unRTCIceCandidateEvent :: JSVal } instance Eq (RTCIceCandidateEvent) where (RTCIceCandidateEvent a) == (RTCIceCandidateEvent b) = js_eq a b instance PToJSVal RTCIceCandidateEvent where pToJSVal = unRTCIceCandidateEvent {-# INLINE pToJSVal #-} instance PFromJSVal RTCIceCandidateEvent where pFromJSVal = RTCIceCandidateEvent {-# INLINE pFromJSVal #-} instance ToJSVal RTCIceCandidateEvent where toJSVal = return . unRTCIceCandidateEvent {-# INLINE toJSVal #-} instance FromJSVal RTCIceCandidateEvent where fromJSVal = return . fmap RTCIceCandidateEvent . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEvent RTCIceCandidateEvent instance IsGObject RTCIceCandidateEvent where typeGType _ = gTypeRTCIceCandidateEvent {-# INLINE typeGType #-} noRTCIceCandidateEvent :: Maybe RTCIceCandidateEvent noRTCIceCandidateEvent = Nothing {-# INLINE noRTCIceCandidateEvent #-} foreign import javascript unsafe "window[\"RTCIceCandidateEvent\"]" gTypeRTCIceCandidateEvent :: GType -- | Functions for this inteface are in "GHCJS.DOM.RTCIceCandidateInit". -- -- newtype RTCIceCandidateInit = RTCIceCandidateInit { unRTCIceCandidateInit :: JSVal } instance Eq (RTCIceCandidateInit) where (RTCIceCandidateInit a) == (RTCIceCandidateInit b) = js_eq a b instance PToJSVal RTCIceCandidateInit where pToJSVal = unRTCIceCandidateInit {-# INLINE pToJSVal #-} instance PFromJSVal RTCIceCandidateInit where pFromJSVal = RTCIceCandidateInit {-# INLINE pFromJSVal #-} instance ToJSVal RTCIceCandidateInit where toJSVal = return . unRTCIceCandidateInit {-# INLINE toJSVal #-} instance FromJSVal RTCIceCandidateInit where fromJSVal = return . fmap RTCIceCandidateInit . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject RTCIceCandidateInit where typeGType _ = gTypeRTCIceCandidateInit {-# INLINE typeGType #-} noRTCIceCandidateInit :: Maybe RTCIceCandidateInit noRTCIceCandidateInit = Nothing {-# INLINE noRTCIceCandidateInit #-} foreign import javascript unsafe "window[\"RTCIceCandidateInit\"]" gTypeRTCIceCandidateInit :: GType -- | Functions for this inteface are in "GHCJS.DOM.RTCIceServer". -- -- newtype RTCIceServer = RTCIceServer { unRTCIceServer :: JSVal } instance Eq (RTCIceServer) where (RTCIceServer a) == (RTCIceServer b) = js_eq a b instance PToJSVal RTCIceServer where pToJSVal = unRTCIceServer {-# INLINE pToJSVal #-} instance PFromJSVal RTCIceServer where pFromJSVal = RTCIceServer {-# INLINE pFromJSVal #-} instance ToJSVal RTCIceServer where toJSVal = return . unRTCIceServer {-# INLINE toJSVal #-} instance FromJSVal RTCIceServer where fromJSVal = return . fmap RTCIceServer . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject RTCIceServer where typeGType _ = gTypeRTCIceServer {-# INLINE typeGType #-} noRTCIceServer :: Maybe RTCIceServer noRTCIceServer = Nothing {-# INLINE noRTCIceServer #-} foreign import javascript unsafe "window[\"RTCIceServer\"]" gTypeRTCIceServer :: GType -- | Functions for this inteface are in "GHCJS.DOM.RTCIceTransport". -- -- newtype RTCIceTransport = RTCIceTransport { unRTCIceTransport :: JSVal } instance Eq (RTCIceTransport) where (RTCIceTransport a) == (RTCIceTransport b) = js_eq a b instance PToJSVal RTCIceTransport where pToJSVal = unRTCIceTransport {-# INLINE pToJSVal #-} instance PFromJSVal RTCIceTransport where pFromJSVal = RTCIceTransport {-# INLINE pFromJSVal #-} instance ToJSVal RTCIceTransport where toJSVal = return . unRTCIceTransport {-# INLINE toJSVal #-} instance FromJSVal RTCIceTransport where fromJSVal = return . fmap RTCIceTransport . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject RTCIceTransport where typeGType _ = gTypeRTCIceTransport {-# INLINE typeGType #-} noRTCIceTransport :: Maybe RTCIceTransport noRTCIceTransport = Nothing {-# INLINE noRTCIceTransport #-} foreign import javascript unsafe "window[\"RTCIceTransport\"]" gTypeRTCIceTransport :: GType -- | Functions for this inteface are in "GHCJS.DOM.RTCInboundRTPStreamStats". -- Base interface functions are in: -- -- * "GHCJS.DOM.RTCRTPStreamStats" -- * "GHCJS.DOM.RTCStats" -- -- newtype RTCInboundRTPStreamStats = RTCInboundRTPStreamStats { unRTCInboundRTPStreamStats :: JSVal } instance Eq (RTCInboundRTPStreamStats) where (RTCInboundRTPStreamStats a) == (RTCInboundRTPStreamStats b) = js_eq a b instance PToJSVal RTCInboundRTPStreamStats where pToJSVal = unRTCInboundRTPStreamStats {-# INLINE pToJSVal #-} instance PFromJSVal RTCInboundRTPStreamStats where pFromJSVal = RTCInboundRTPStreamStats {-# INLINE pFromJSVal #-} instance ToJSVal RTCInboundRTPStreamStats where toJSVal = return . unRTCInboundRTPStreamStats {-# INLINE toJSVal #-} instance FromJSVal RTCInboundRTPStreamStats where fromJSVal = return . fmap RTCInboundRTPStreamStats . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsRTCRTPStreamStats RTCInboundRTPStreamStats instance IsRTCStats RTCInboundRTPStreamStats instance IsGObject RTCInboundRTPStreamStats where typeGType _ = gTypeRTCInboundRTPStreamStats {-# INLINE typeGType #-} noRTCInboundRTPStreamStats :: Maybe RTCInboundRTPStreamStats noRTCInboundRTPStreamStats = Nothing {-# INLINE noRTCInboundRTPStreamStats #-} foreign import javascript unsafe "window[\"RTCInboundRTPStreamStats\"]" gTypeRTCInboundRTPStreamStats :: GType -- | Functions for this inteface are in "GHCJS.DOM.RTCMediaStreamTrackStats". -- Base interface functions are in: -- -- * "GHCJS.DOM.RTCStats" -- -- newtype RTCMediaStreamTrackStats = RTCMediaStreamTrackStats { unRTCMediaStreamTrackStats :: JSVal } instance Eq (RTCMediaStreamTrackStats) where (RTCMediaStreamTrackStats a) == (RTCMediaStreamTrackStats b) = js_eq a b instance PToJSVal RTCMediaStreamTrackStats where pToJSVal = unRTCMediaStreamTrackStats {-# INLINE pToJSVal #-} instance PFromJSVal RTCMediaStreamTrackStats where pFromJSVal = RTCMediaStreamTrackStats {-# INLINE pFromJSVal #-} instance ToJSVal RTCMediaStreamTrackStats where toJSVal = return . unRTCMediaStreamTrackStats {-# INLINE toJSVal #-} instance FromJSVal RTCMediaStreamTrackStats where fromJSVal = return . fmap RTCMediaStreamTrackStats . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsRTCStats RTCMediaStreamTrackStats instance IsGObject RTCMediaStreamTrackStats where typeGType _ = gTypeRTCMediaStreamTrackStats {-# INLINE typeGType #-} noRTCMediaStreamTrackStats :: Maybe RTCMediaStreamTrackStats noRTCMediaStreamTrackStats = Nothing {-# INLINE noRTCMediaStreamTrackStats #-} foreign import javascript unsafe "window[\"RTCMediaStreamTrackStats\"]" gTypeRTCMediaStreamTrackStats :: GType -- | Functions for this inteface are in "GHCJS.DOM.RTCOfferAnswerOptions". -- -- newtype RTCOfferAnswerOptions = RTCOfferAnswerOptions { unRTCOfferAnswerOptions :: JSVal } instance Eq (RTCOfferAnswerOptions) where (RTCOfferAnswerOptions a) == (RTCOfferAnswerOptions b) = js_eq a b instance PToJSVal RTCOfferAnswerOptions where pToJSVal = unRTCOfferAnswerOptions {-# INLINE pToJSVal #-} instance PFromJSVal RTCOfferAnswerOptions where pFromJSVal = RTCOfferAnswerOptions {-# INLINE pFromJSVal #-} instance ToJSVal RTCOfferAnswerOptions where toJSVal = return . unRTCOfferAnswerOptions {-# INLINE toJSVal #-} instance FromJSVal RTCOfferAnswerOptions where fromJSVal = return . fmap RTCOfferAnswerOptions . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsGObject o) => IsRTCOfferAnswerOptions o toRTCOfferAnswerOptions :: IsRTCOfferAnswerOptions o => o -> RTCOfferAnswerOptions toRTCOfferAnswerOptions = RTCOfferAnswerOptions . coerce instance IsRTCOfferAnswerOptions RTCOfferAnswerOptions instance IsGObject RTCOfferAnswerOptions where typeGType _ = gTypeRTCOfferAnswerOptions {-# INLINE typeGType #-} noRTCOfferAnswerOptions :: Maybe RTCOfferAnswerOptions noRTCOfferAnswerOptions = Nothing {-# INLINE noRTCOfferAnswerOptions #-} foreign import javascript unsafe "window[\"RTCOfferAnswerOptions\"]" gTypeRTCOfferAnswerOptions :: GType -- | Functions for this inteface are in "GHCJS.DOM.RTCOfferOptions". -- Base interface functions are in: -- -- * "GHCJS.DOM.RTCOfferAnswerOptions" -- -- newtype RTCOfferOptions = RTCOfferOptions { unRTCOfferOptions :: JSVal } instance Eq (RTCOfferOptions) where (RTCOfferOptions a) == (RTCOfferOptions b) = js_eq a b instance PToJSVal RTCOfferOptions where pToJSVal = unRTCOfferOptions {-# INLINE pToJSVal #-} instance PFromJSVal RTCOfferOptions where pFromJSVal = RTCOfferOptions {-# INLINE pFromJSVal #-} instance ToJSVal RTCOfferOptions where toJSVal = return . unRTCOfferOptions {-# INLINE toJSVal #-} instance FromJSVal RTCOfferOptions where fromJSVal = return . fmap RTCOfferOptions . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsRTCOfferAnswerOptions RTCOfferOptions instance IsGObject RTCOfferOptions where typeGType _ = gTypeRTCOfferOptions {-# INLINE typeGType #-} noRTCOfferOptions :: Maybe RTCOfferOptions noRTCOfferOptions = Nothing {-# INLINE noRTCOfferOptions #-} foreign import javascript unsafe "window[\"RTCOfferOptions\"]" gTypeRTCOfferOptions :: GType -- | Functions for this inteface are in "GHCJS.DOM.RTCOutboundRTPStreamStats". -- Base interface functions are in: -- -- * "GHCJS.DOM.RTCRTPStreamStats" -- * "GHCJS.DOM.RTCStats" -- -- newtype RTCOutboundRTPStreamStats = RTCOutboundRTPStreamStats { unRTCOutboundRTPStreamStats :: JSVal } instance Eq (RTCOutboundRTPStreamStats) where (RTCOutboundRTPStreamStats a) == (RTCOutboundRTPStreamStats b) = js_eq a b instance PToJSVal RTCOutboundRTPStreamStats where pToJSVal = unRTCOutboundRTPStreamStats {-# INLINE pToJSVal #-} instance PFromJSVal RTCOutboundRTPStreamStats where pFromJSVal = RTCOutboundRTPStreamStats {-# INLINE pFromJSVal #-} instance ToJSVal RTCOutboundRTPStreamStats where toJSVal = return . unRTCOutboundRTPStreamStats {-# INLINE toJSVal #-} instance FromJSVal RTCOutboundRTPStreamStats where fromJSVal = return . fmap RTCOutboundRTPStreamStats . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsRTCRTPStreamStats RTCOutboundRTPStreamStats instance IsRTCStats RTCOutboundRTPStreamStats instance IsGObject RTCOutboundRTPStreamStats where typeGType _ = gTypeRTCOutboundRTPStreamStats {-# INLINE typeGType #-} noRTCOutboundRTPStreamStats :: Maybe RTCOutboundRTPStreamStats noRTCOutboundRTPStreamStats = Nothing {-# INLINE noRTCOutboundRTPStreamStats #-} foreign import javascript unsafe "window[\"RTCOutboundRTPStreamStats\"]" gTypeRTCOutboundRTPStreamStats :: GType -- | Functions for this inteface are in "GHCJS.DOM.RTCPeerConnection". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventTarget" -- -- newtype RTCPeerConnection = RTCPeerConnection { unRTCPeerConnection :: JSVal } instance Eq (RTCPeerConnection) where (RTCPeerConnection a) == (RTCPeerConnection b) = js_eq a b instance PToJSVal RTCPeerConnection where pToJSVal = unRTCPeerConnection {-# INLINE pToJSVal #-} instance PFromJSVal RTCPeerConnection where pFromJSVal = RTCPeerConnection {-# INLINE pFromJSVal #-} instance ToJSVal RTCPeerConnection where toJSVal = return . unRTCPeerConnection {-# INLINE toJSVal #-} instance FromJSVal RTCPeerConnection where fromJSVal = return . fmap RTCPeerConnection . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventTarget RTCPeerConnection instance IsGObject RTCPeerConnection where typeGType _ = gTypeRTCPeerConnection {-# INLINE typeGType #-} noRTCPeerConnection :: Maybe RTCPeerConnection noRTCPeerConnection = Nothing {-# INLINE noRTCPeerConnection #-} foreign import javascript unsafe "window[\"webkitRTCPeerConnection\"]" gTypeRTCPeerConnection :: GType -- | Functions for this inteface are in "GHCJS.DOM.RTCPeerConnectionIceEvent". -- Base interface functions are in: -- -- * "GHCJS.DOM.Event" -- -- newtype RTCPeerConnectionIceEvent = RTCPeerConnectionIceEvent { unRTCPeerConnectionIceEvent :: JSVal } instance Eq (RTCPeerConnectionIceEvent) where (RTCPeerConnectionIceEvent a) == (RTCPeerConnectionIceEvent b) = js_eq a b instance PToJSVal RTCPeerConnectionIceEvent where pToJSVal = unRTCPeerConnectionIceEvent {-# INLINE pToJSVal #-} instance PFromJSVal RTCPeerConnectionIceEvent where pFromJSVal = RTCPeerConnectionIceEvent {-# INLINE pFromJSVal #-} instance ToJSVal RTCPeerConnectionIceEvent where toJSVal = return . unRTCPeerConnectionIceEvent {-# INLINE toJSVal #-} instance FromJSVal RTCPeerConnectionIceEvent where fromJSVal = return . fmap RTCPeerConnectionIceEvent . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEvent RTCPeerConnectionIceEvent instance IsGObject RTCPeerConnectionIceEvent where typeGType _ = gTypeRTCPeerConnectionIceEvent {-# INLINE typeGType #-} noRTCPeerConnectionIceEvent :: Maybe RTCPeerConnectionIceEvent noRTCPeerConnectionIceEvent = Nothing {-# INLINE noRTCPeerConnectionIceEvent #-} foreign import javascript unsafe "window[\"RTCPeerConnectionIceEvent\"]" gTypeRTCPeerConnectionIceEvent :: GType -- | Functions for this inteface are in "GHCJS.DOM.RTCRTPStreamStats". -- Base interface functions are in: -- -- * "GHCJS.DOM.RTCStats" -- -- newtype RTCRTPStreamStats = RTCRTPStreamStats { unRTCRTPStreamStats :: JSVal } instance Eq (RTCRTPStreamStats) where (RTCRTPStreamStats a) == (RTCRTPStreamStats b) = js_eq a b instance PToJSVal RTCRTPStreamStats where pToJSVal = unRTCRTPStreamStats {-# INLINE pToJSVal #-} instance PFromJSVal RTCRTPStreamStats where pFromJSVal = RTCRTPStreamStats {-# INLINE pFromJSVal #-} instance ToJSVal RTCRTPStreamStats where toJSVal = return . unRTCRTPStreamStats {-# INLINE toJSVal #-} instance FromJSVal RTCRTPStreamStats where fromJSVal = return . fmap RTCRTPStreamStats . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsRTCStats o, IsGObject o) => IsRTCRTPStreamStats o toRTCRTPStreamStats :: IsRTCRTPStreamStats o => o -> RTCRTPStreamStats toRTCRTPStreamStats = RTCRTPStreamStats . coerce instance IsRTCRTPStreamStats RTCRTPStreamStats instance IsRTCStats RTCRTPStreamStats instance IsGObject RTCRTPStreamStats where typeGType _ = gTypeRTCRTPStreamStats {-# INLINE typeGType #-} noRTCRTPStreamStats :: Maybe RTCRTPStreamStats noRTCRTPStreamStats = Nothing {-# INLINE noRTCRTPStreamStats #-} foreign import javascript unsafe "window[\"RTCRTPStreamStats\"]" gTypeRTCRTPStreamStats :: GType -- | Functions for this inteface are in "GHCJS.DOM.RTCRtpCodecParameters". -- -- newtype RTCRtpCodecParameters = RTCRtpCodecParameters { unRTCRtpCodecParameters :: JSVal } instance Eq (RTCRtpCodecParameters) where (RTCRtpCodecParameters a) == (RTCRtpCodecParameters b) = js_eq a b instance PToJSVal RTCRtpCodecParameters where pToJSVal = unRTCRtpCodecParameters {-# INLINE pToJSVal #-} instance PFromJSVal RTCRtpCodecParameters where pFromJSVal = RTCRtpCodecParameters {-# INLINE pFromJSVal #-} instance ToJSVal RTCRtpCodecParameters where toJSVal = return . unRTCRtpCodecParameters {-# INLINE toJSVal #-} instance FromJSVal RTCRtpCodecParameters where fromJSVal = return . fmap RTCRtpCodecParameters . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject RTCRtpCodecParameters where typeGType _ = gTypeRTCRtpCodecParameters {-# INLINE typeGType #-} noRTCRtpCodecParameters :: Maybe RTCRtpCodecParameters noRTCRtpCodecParameters = Nothing {-# INLINE noRTCRtpCodecParameters #-} foreign import javascript unsafe "window[\"RTCRtpCodecParameters\"]" gTypeRTCRtpCodecParameters :: GType -- | Functions for this inteface are in "GHCJS.DOM.RTCRtpEncodingParameters". -- -- newtype RTCRtpEncodingParameters = RTCRtpEncodingParameters { unRTCRtpEncodingParameters :: JSVal } instance Eq (RTCRtpEncodingParameters) where (RTCRtpEncodingParameters a) == (RTCRtpEncodingParameters b) = js_eq a b instance PToJSVal RTCRtpEncodingParameters where pToJSVal = unRTCRtpEncodingParameters {-# INLINE pToJSVal #-} instance PFromJSVal RTCRtpEncodingParameters where pFromJSVal = RTCRtpEncodingParameters {-# INLINE pFromJSVal #-} instance ToJSVal RTCRtpEncodingParameters where toJSVal = return . unRTCRtpEncodingParameters {-# INLINE toJSVal #-} instance FromJSVal RTCRtpEncodingParameters where fromJSVal = return . fmap RTCRtpEncodingParameters . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject RTCRtpEncodingParameters where typeGType _ = gTypeRTCRtpEncodingParameters {-# INLINE typeGType #-} noRTCRtpEncodingParameters :: Maybe RTCRtpEncodingParameters noRTCRtpEncodingParameters = Nothing {-# INLINE noRTCRtpEncodingParameters #-} foreign import javascript unsafe "window[\"RTCRtpEncodingParameters\"]" gTypeRTCRtpEncodingParameters :: GType -- | Functions for this inteface are in "GHCJS.DOM.RTCRtpFecParameters". -- -- newtype RTCRtpFecParameters = RTCRtpFecParameters { unRTCRtpFecParameters :: JSVal } instance Eq (RTCRtpFecParameters) where (RTCRtpFecParameters a) == (RTCRtpFecParameters b) = js_eq a b instance PToJSVal RTCRtpFecParameters where pToJSVal = unRTCRtpFecParameters {-# INLINE pToJSVal #-} instance PFromJSVal RTCRtpFecParameters where pFromJSVal = RTCRtpFecParameters {-# INLINE pFromJSVal #-} instance ToJSVal RTCRtpFecParameters where toJSVal = return . unRTCRtpFecParameters {-# INLINE toJSVal #-} instance FromJSVal RTCRtpFecParameters where fromJSVal = return . fmap RTCRtpFecParameters . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject RTCRtpFecParameters where typeGType _ = gTypeRTCRtpFecParameters {-# INLINE typeGType #-} noRTCRtpFecParameters :: Maybe RTCRtpFecParameters noRTCRtpFecParameters = Nothing {-# INLINE noRTCRtpFecParameters #-} foreign import javascript unsafe "window[\"RTCRtpFecParameters\"]" gTypeRTCRtpFecParameters :: GType -- | Functions for this inteface are in "GHCJS.DOM.RTCRtpHeaderExtensionParameters". -- -- newtype RTCRtpHeaderExtensionParameters = RTCRtpHeaderExtensionParameters { unRTCRtpHeaderExtensionParameters :: JSVal } instance Eq (RTCRtpHeaderExtensionParameters) where (RTCRtpHeaderExtensionParameters a) == (RTCRtpHeaderExtensionParameters b) = js_eq a b instance PToJSVal RTCRtpHeaderExtensionParameters where pToJSVal = unRTCRtpHeaderExtensionParameters {-# INLINE pToJSVal #-} instance PFromJSVal RTCRtpHeaderExtensionParameters where pFromJSVal = RTCRtpHeaderExtensionParameters {-# INLINE pFromJSVal #-} instance ToJSVal RTCRtpHeaderExtensionParameters where toJSVal = return . unRTCRtpHeaderExtensionParameters {-# INLINE toJSVal #-} instance FromJSVal RTCRtpHeaderExtensionParameters where fromJSVal = return . fmap RTCRtpHeaderExtensionParameters . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject RTCRtpHeaderExtensionParameters where typeGType _ = gTypeRTCRtpHeaderExtensionParameters {-# INLINE typeGType #-} noRTCRtpHeaderExtensionParameters :: Maybe RTCRtpHeaderExtensionParameters noRTCRtpHeaderExtensionParameters = Nothing {-# INLINE noRTCRtpHeaderExtensionParameters #-} foreign import javascript unsafe "window[\"RTCRtpHeaderExtensionParameters\"]" gTypeRTCRtpHeaderExtensionParameters :: GType -- | Functions for this inteface are in "GHCJS.DOM.RTCRtpParameters". -- -- newtype RTCRtpParameters = RTCRtpParameters { unRTCRtpParameters :: JSVal } instance Eq (RTCRtpParameters) where (RTCRtpParameters a) == (RTCRtpParameters b) = js_eq a b instance PToJSVal RTCRtpParameters where pToJSVal = unRTCRtpParameters {-# INLINE pToJSVal #-} instance PFromJSVal RTCRtpParameters where pFromJSVal = RTCRtpParameters {-# INLINE pFromJSVal #-} instance ToJSVal RTCRtpParameters where toJSVal = return . unRTCRtpParameters {-# INLINE toJSVal #-} instance FromJSVal RTCRtpParameters where fromJSVal = return . fmap RTCRtpParameters . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject RTCRtpParameters where typeGType _ = gTypeRTCRtpParameters {-# INLINE typeGType #-} noRTCRtpParameters :: Maybe RTCRtpParameters noRTCRtpParameters = Nothing {-# INLINE noRTCRtpParameters #-} foreign import javascript unsafe "window[\"RTCRtpParameters\"]" gTypeRTCRtpParameters :: GType -- | Functions for this inteface are in "GHCJS.DOM.RTCRtpReceiver". -- -- newtype RTCRtpReceiver = RTCRtpReceiver { unRTCRtpReceiver :: JSVal } instance Eq (RTCRtpReceiver) where (RTCRtpReceiver a) == (RTCRtpReceiver b) = js_eq a b instance PToJSVal RTCRtpReceiver where pToJSVal = unRTCRtpReceiver {-# INLINE pToJSVal #-} instance PFromJSVal RTCRtpReceiver where pFromJSVal = RTCRtpReceiver {-# INLINE pFromJSVal #-} instance ToJSVal RTCRtpReceiver where toJSVal = return . unRTCRtpReceiver {-# INLINE toJSVal #-} instance FromJSVal RTCRtpReceiver where fromJSVal = return . fmap RTCRtpReceiver . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject RTCRtpReceiver where typeGType _ = gTypeRTCRtpReceiver {-# INLINE typeGType #-} noRTCRtpReceiver :: Maybe RTCRtpReceiver noRTCRtpReceiver = Nothing {-# INLINE noRTCRtpReceiver #-} foreign import javascript unsafe "window[\"RTCRtpReceiver\"]" gTypeRTCRtpReceiver :: GType -- | Functions for this inteface are in "GHCJS.DOM.RTCRtpRtxParameters". -- -- newtype RTCRtpRtxParameters = RTCRtpRtxParameters { unRTCRtpRtxParameters :: JSVal } instance Eq (RTCRtpRtxParameters) where (RTCRtpRtxParameters a) == (RTCRtpRtxParameters b) = js_eq a b instance PToJSVal RTCRtpRtxParameters where pToJSVal = unRTCRtpRtxParameters {-# INLINE pToJSVal #-} instance PFromJSVal RTCRtpRtxParameters where pFromJSVal = RTCRtpRtxParameters {-# INLINE pFromJSVal #-} instance ToJSVal RTCRtpRtxParameters where toJSVal = return . unRTCRtpRtxParameters {-# INLINE toJSVal #-} instance FromJSVal RTCRtpRtxParameters where fromJSVal = return . fmap RTCRtpRtxParameters . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject RTCRtpRtxParameters where typeGType _ = gTypeRTCRtpRtxParameters {-# INLINE typeGType #-} noRTCRtpRtxParameters :: Maybe RTCRtpRtxParameters noRTCRtpRtxParameters = Nothing {-# INLINE noRTCRtpRtxParameters #-} foreign import javascript unsafe "window[\"RTCRtpRtxParameters\"]" gTypeRTCRtpRtxParameters :: GType -- | Functions for this inteface are in "GHCJS.DOM.RTCRtpSender". -- -- newtype RTCRtpSender = RTCRtpSender { unRTCRtpSender :: JSVal } instance Eq (RTCRtpSender) where (RTCRtpSender a) == (RTCRtpSender b) = js_eq a b instance PToJSVal RTCRtpSender where pToJSVal = unRTCRtpSender {-# INLINE pToJSVal #-} instance PFromJSVal RTCRtpSender where pFromJSVal = RTCRtpSender {-# INLINE pFromJSVal #-} instance ToJSVal RTCRtpSender where toJSVal = return . unRTCRtpSender {-# INLINE toJSVal #-} instance FromJSVal RTCRtpSender where fromJSVal = return . fmap RTCRtpSender . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject RTCRtpSender where typeGType _ = gTypeRTCRtpSender {-# INLINE typeGType #-} noRTCRtpSender :: Maybe RTCRtpSender noRTCRtpSender = Nothing {-# INLINE noRTCRtpSender #-} foreign import javascript unsafe "window[\"RTCRtpSender\"]" gTypeRTCRtpSender :: GType -- | Functions for this inteface are in "GHCJS.DOM.RTCRtpTransceiver". -- -- newtype RTCRtpTransceiver = RTCRtpTransceiver { unRTCRtpTransceiver :: JSVal } instance Eq (RTCRtpTransceiver) where (RTCRtpTransceiver a) == (RTCRtpTransceiver b) = js_eq a b instance PToJSVal RTCRtpTransceiver where pToJSVal = unRTCRtpTransceiver {-# INLINE pToJSVal #-} instance PFromJSVal RTCRtpTransceiver where pFromJSVal = RTCRtpTransceiver {-# INLINE pFromJSVal #-} instance ToJSVal RTCRtpTransceiver where toJSVal = return . unRTCRtpTransceiver {-# INLINE toJSVal #-} instance FromJSVal RTCRtpTransceiver where fromJSVal = return . fmap RTCRtpTransceiver . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject RTCRtpTransceiver where typeGType _ = gTypeRTCRtpTransceiver {-# INLINE typeGType #-} noRTCRtpTransceiver :: Maybe RTCRtpTransceiver noRTCRtpTransceiver = Nothing {-# INLINE noRTCRtpTransceiver #-} foreign import javascript unsafe "window[\"RTCRtpTransceiver\"]" gTypeRTCRtpTransceiver :: GType -- | Functions for this inteface are in "GHCJS.DOM.RTCRtpTransceiverInit". -- -- newtype RTCRtpTransceiverInit = RTCRtpTransceiverInit { unRTCRtpTransceiverInit :: JSVal } instance Eq (RTCRtpTransceiverInit) where (RTCRtpTransceiverInit a) == (RTCRtpTransceiverInit b) = js_eq a b instance PToJSVal RTCRtpTransceiverInit where pToJSVal = unRTCRtpTransceiverInit {-# INLINE pToJSVal #-} instance PFromJSVal RTCRtpTransceiverInit where pFromJSVal = RTCRtpTransceiverInit {-# INLINE pFromJSVal #-} instance ToJSVal RTCRtpTransceiverInit where toJSVal = return . unRTCRtpTransceiverInit {-# INLINE toJSVal #-} instance FromJSVal RTCRtpTransceiverInit where fromJSVal = return . fmap RTCRtpTransceiverInit . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject RTCRtpTransceiverInit where typeGType _ = gTypeRTCRtpTransceiverInit {-# INLINE typeGType #-} noRTCRtpTransceiverInit :: Maybe RTCRtpTransceiverInit noRTCRtpTransceiverInit = Nothing {-# INLINE noRTCRtpTransceiverInit #-} foreign import javascript unsafe "window[\"RTCRtpTransceiverInit\"]" gTypeRTCRtpTransceiverInit :: GType -- | Functions for this inteface are in "GHCJS.DOM.RTCSessionDescription". -- -- newtype RTCSessionDescription = RTCSessionDescription { unRTCSessionDescription :: JSVal } instance Eq (RTCSessionDescription) where (RTCSessionDescription a) == (RTCSessionDescription b) = js_eq a b instance PToJSVal RTCSessionDescription where pToJSVal = unRTCSessionDescription {-# INLINE pToJSVal #-} instance PFromJSVal RTCSessionDescription where pFromJSVal = RTCSessionDescription {-# INLINE pFromJSVal #-} instance ToJSVal RTCSessionDescription where toJSVal = return . unRTCSessionDescription {-# INLINE toJSVal #-} instance FromJSVal RTCSessionDescription where fromJSVal = return . fmap RTCSessionDescription . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject RTCSessionDescription where typeGType _ = gTypeRTCSessionDescription {-# INLINE typeGType #-} noRTCSessionDescription :: Maybe RTCSessionDescription noRTCSessionDescription = Nothing {-# INLINE noRTCSessionDescription #-} foreign import javascript unsafe "window[\"RTCSessionDescription\"]" gTypeRTCSessionDescription :: GType -- | Functions for this inteface are in "GHCJS.DOM.RTCSessionDescriptionInit". -- -- newtype RTCSessionDescriptionInit = RTCSessionDescriptionInit { unRTCSessionDescriptionInit :: JSVal } instance Eq (RTCSessionDescriptionInit) where (RTCSessionDescriptionInit a) == (RTCSessionDescriptionInit b) = js_eq a b instance PToJSVal RTCSessionDescriptionInit where pToJSVal = unRTCSessionDescriptionInit {-# INLINE pToJSVal #-} instance PFromJSVal RTCSessionDescriptionInit where pFromJSVal = RTCSessionDescriptionInit {-# INLINE pFromJSVal #-} instance ToJSVal RTCSessionDescriptionInit where toJSVal = return . unRTCSessionDescriptionInit {-# INLINE toJSVal #-} instance FromJSVal RTCSessionDescriptionInit where fromJSVal = return . fmap RTCSessionDescriptionInit . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject RTCSessionDescriptionInit where typeGType _ = gTypeRTCSessionDescriptionInit {-# INLINE typeGType #-} noRTCSessionDescriptionInit :: Maybe RTCSessionDescriptionInit noRTCSessionDescriptionInit = Nothing {-# INLINE noRTCSessionDescriptionInit #-} foreign import javascript unsafe "window[\"RTCSessionDescriptionInit\"]" gTypeRTCSessionDescriptionInit :: GType -- | Functions for this inteface are in "GHCJS.DOM.RTCStats". -- -- newtype RTCStats = RTCStats { unRTCStats :: JSVal } instance Eq (RTCStats) where (RTCStats a) == (RTCStats b) = js_eq a b instance PToJSVal RTCStats where pToJSVal = unRTCStats {-# INLINE pToJSVal #-} instance PFromJSVal RTCStats where pFromJSVal = RTCStats {-# INLINE pFromJSVal #-} instance ToJSVal RTCStats where toJSVal = return . unRTCStats {-# INLINE toJSVal #-} instance FromJSVal RTCStats where fromJSVal = return . fmap RTCStats . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsGObject o) => IsRTCStats o toRTCStats :: IsRTCStats o => o -> RTCStats toRTCStats = RTCStats . coerce instance IsRTCStats RTCStats instance IsGObject RTCStats where typeGType _ = gTypeRTCStats {-# INLINE typeGType #-} noRTCStats :: Maybe RTCStats noRTCStats = Nothing {-# INLINE noRTCStats #-} foreign import javascript unsafe "window[\"RTCStats\"]" gTypeRTCStats :: GType -- | Functions for this inteface are in "GHCJS.DOM.RTCStatsReport". -- -- newtype RTCStatsReport = RTCStatsReport { unRTCStatsReport :: JSVal } instance Eq (RTCStatsReport) where (RTCStatsReport a) == (RTCStatsReport b) = js_eq a b instance PToJSVal RTCStatsReport where pToJSVal = unRTCStatsReport {-# INLINE pToJSVal #-} instance PFromJSVal RTCStatsReport where pFromJSVal = RTCStatsReport {-# INLINE pFromJSVal #-} instance ToJSVal RTCStatsReport where toJSVal = return . unRTCStatsReport {-# INLINE toJSVal #-} instance FromJSVal RTCStatsReport where fromJSVal = return . fmap RTCStatsReport . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject RTCStatsReport where typeGType _ = gTypeRTCStatsReport {-# INLINE typeGType #-} noRTCStatsReport :: Maybe RTCStatsReport noRTCStatsReport = Nothing {-# INLINE noRTCStatsReport #-} foreign import javascript unsafe "window[\"RTCStatsReport\"]" gTypeRTCStatsReport :: GType -- | Functions for this inteface are in "GHCJS.DOM.RTCTrackEvent". -- Base interface functions are in: -- -- * "GHCJS.DOM.Event" -- -- newtype RTCTrackEvent = RTCTrackEvent { unRTCTrackEvent :: JSVal } instance Eq (RTCTrackEvent) where (RTCTrackEvent a) == (RTCTrackEvent b) = js_eq a b instance PToJSVal RTCTrackEvent where pToJSVal = unRTCTrackEvent {-# INLINE pToJSVal #-} instance PFromJSVal RTCTrackEvent where pFromJSVal = RTCTrackEvent {-# INLINE pFromJSVal #-} instance ToJSVal RTCTrackEvent where toJSVal = return . unRTCTrackEvent {-# INLINE toJSVal #-} instance FromJSVal RTCTrackEvent where fromJSVal = return . fmap RTCTrackEvent . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEvent RTCTrackEvent instance IsGObject RTCTrackEvent where typeGType _ = gTypeRTCTrackEvent {-# INLINE typeGType #-} noRTCTrackEvent :: Maybe RTCTrackEvent noRTCTrackEvent = Nothing {-# INLINE noRTCTrackEvent #-} foreign import javascript unsafe "window[\"RTCTrackEvent\"]" gTypeRTCTrackEvent :: GType -- | Functions for this inteface are in "GHCJS.DOM.RTCTrackEventInit". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventInit" -- -- newtype RTCTrackEventInit = RTCTrackEventInit { unRTCTrackEventInit :: JSVal } instance Eq (RTCTrackEventInit) where (RTCTrackEventInit a) == (RTCTrackEventInit b) = js_eq a b instance PToJSVal RTCTrackEventInit where pToJSVal = unRTCTrackEventInit {-# INLINE pToJSVal #-} instance PFromJSVal RTCTrackEventInit where pFromJSVal = RTCTrackEventInit {-# INLINE pFromJSVal #-} instance ToJSVal RTCTrackEventInit where toJSVal = return . unRTCTrackEventInit {-# INLINE toJSVal #-} instance FromJSVal RTCTrackEventInit where fromJSVal = return . fmap RTCTrackEventInit . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventInit RTCTrackEventInit instance IsGObject RTCTrackEventInit where typeGType _ = gTypeRTCTrackEventInit {-# INLINE typeGType #-} noRTCTrackEventInit :: Maybe RTCTrackEventInit noRTCTrackEventInit = Nothing {-# INLINE noRTCTrackEventInit #-} foreign import javascript unsafe "window[\"RTCTrackEventInit\"]" gTypeRTCTrackEventInit :: GType -- | Functions for this inteface are in "GHCJS.DOM.RadioNodeList". -- Base interface functions are in: -- -- * "GHCJS.DOM.NodeList" -- -- newtype RadioNodeList = RadioNodeList { unRadioNodeList :: JSVal } instance Eq (RadioNodeList) where (RadioNodeList a) == (RadioNodeList b) = js_eq a b instance PToJSVal RadioNodeList where pToJSVal = unRadioNodeList {-# INLINE pToJSVal #-} instance PFromJSVal RadioNodeList where pFromJSVal = RadioNodeList {-# INLINE pFromJSVal #-} instance ToJSVal RadioNodeList where toJSVal = return . unRadioNodeList {-# INLINE toJSVal #-} instance FromJSVal RadioNodeList where fromJSVal = return . fmap RadioNodeList . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsNodeList RadioNodeList instance IsGObject RadioNodeList where typeGType _ = gTypeRadioNodeList {-# INLINE typeGType #-} noRadioNodeList :: Maybe RadioNodeList noRadioNodeList = Nothing {-# INLINE noRadioNodeList #-} foreign import javascript unsafe "window[\"RadioNodeList\"]" gTypeRadioNodeList :: GType -- | Functions for this inteface are in "GHCJS.DOM.Range". -- -- newtype Range = Range { unRange :: JSVal } instance Eq (Range) where (Range a) == (Range b) = js_eq a b instance PToJSVal Range where pToJSVal = unRange {-# INLINE pToJSVal #-} instance PFromJSVal Range where pFromJSVal = Range {-# INLINE pFromJSVal #-} instance ToJSVal Range where toJSVal = return . unRange {-# INLINE toJSVal #-} instance FromJSVal Range where fromJSVal = return . fmap Range . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject Range where typeGType _ = gTypeRange {-# INLINE typeGType #-} noRange :: Maybe Range noRange = Nothing {-# INLINE noRange #-} foreign import javascript unsafe "window[\"Range\"]" gTypeRange :: GType -- | Functions for this inteface are in "GHCJS.DOM.ReadableByteStreamController". -- -- newtype ReadableByteStreamController = ReadableByteStreamController { unReadableByteStreamController :: JSVal } instance Eq (ReadableByteStreamController) where (ReadableByteStreamController a) == (ReadableByteStreamController b) = js_eq a b instance PToJSVal ReadableByteStreamController where pToJSVal = unReadableByteStreamController {-# INLINE pToJSVal #-} instance PFromJSVal ReadableByteStreamController where pFromJSVal = ReadableByteStreamController {-# INLINE pFromJSVal #-} instance ToJSVal ReadableByteStreamController where toJSVal = return . unReadableByteStreamController {-# INLINE toJSVal #-} instance FromJSVal ReadableByteStreamController where fromJSVal = return . fmap ReadableByteStreamController . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject ReadableByteStreamController where typeGType _ = gTypeReadableByteStreamController {-# INLINE typeGType #-} noReadableByteStreamController :: Maybe ReadableByteStreamController noReadableByteStreamController = Nothing {-# INLINE noReadableByteStreamController #-} foreign import javascript unsafe "window[\"ReadableByteStreamController\"]" gTypeReadableByteStreamController :: GType -- | Functions for this inteface are in "GHCJS.DOM.ReadableStream". -- -- newtype ReadableStream = ReadableStream { unReadableStream :: JSVal } instance Eq (ReadableStream) where (ReadableStream a) == (ReadableStream b) = js_eq a b instance PToJSVal ReadableStream where pToJSVal = unReadableStream {-# INLINE pToJSVal #-} instance PFromJSVal ReadableStream where pFromJSVal = ReadableStream {-# INLINE pFromJSVal #-} instance ToJSVal ReadableStream where toJSVal = return . unReadableStream {-# INLINE toJSVal #-} instance FromJSVal ReadableStream where fromJSVal = return . fmap ReadableStream . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject ReadableStream where typeGType _ = gTypeReadableStream {-# INLINE typeGType #-} noReadableStream :: Maybe ReadableStream noReadableStream = Nothing {-# INLINE noReadableStream #-} foreign import javascript unsafe "window[\"ReadableStream\"]" gTypeReadableStream :: GType -- | Functions for this inteface are in "GHCJS.DOM.ReadableStreamBYOBReader". -- -- newtype ReadableStreamBYOBReader = ReadableStreamBYOBReader { unReadableStreamBYOBReader :: JSVal } instance Eq (ReadableStreamBYOBReader) where (ReadableStreamBYOBReader a) == (ReadableStreamBYOBReader b) = js_eq a b instance PToJSVal ReadableStreamBYOBReader where pToJSVal = unReadableStreamBYOBReader {-# INLINE pToJSVal #-} instance PFromJSVal ReadableStreamBYOBReader where pFromJSVal = ReadableStreamBYOBReader {-# INLINE pFromJSVal #-} instance ToJSVal ReadableStreamBYOBReader where toJSVal = return . unReadableStreamBYOBReader {-# INLINE toJSVal #-} instance FromJSVal ReadableStreamBYOBReader where fromJSVal = return . fmap ReadableStreamBYOBReader . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject ReadableStreamBYOBReader where typeGType _ = gTypeReadableStreamBYOBReader {-# INLINE typeGType #-} noReadableStreamBYOBReader :: Maybe ReadableStreamBYOBReader noReadableStreamBYOBReader = Nothing {-# INLINE noReadableStreamBYOBReader #-} foreign import javascript unsafe "window[\"ReadableStreamBYOBReader\"]" gTypeReadableStreamBYOBReader :: GType -- | Functions for this inteface are in "GHCJS.DOM.ReadableStreamBYOBRequest". -- -- newtype ReadableStreamBYOBRequest = ReadableStreamBYOBRequest { unReadableStreamBYOBRequest :: JSVal } instance Eq (ReadableStreamBYOBRequest) where (ReadableStreamBYOBRequest a) == (ReadableStreamBYOBRequest b) = js_eq a b instance PToJSVal ReadableStreamBYOBRequest where pToJSVal = unReadableStreamBYOBRequest {-# INLINE pToJSVal #-} instance PFromJSVal ReadableStreamBYOBRequest where pFromJSVal = ReadableStreamBYOBRequest {-# INLINE pFromJSVal #-} instance ToJSVal ReadableStreamBYOBRequest where toJSVal = return . unReadableStreamBYOBRequest {-# INLINE toJSVal #-} instance FromJSVal ReadableStreamBYOBRequest where fromJSVal = return . fmap ReadableStreamBYOBRequest . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject ReadableStreamBYOBRequest where typeGType _ = gTypeReadableStreamBYOBRequest {-# INLINE typeGType #-} noReadableStreamBYOBRequest :: Maybe ReadableStreamBYOBRequest noReadableStreamBYOBRequest = Nothing {-# INLINE noReadableStreamBYOBRequest #-} foreign import javascript unsafe "window[\"ReadableStreamBYOBRequest\"]" gTypeReadableStreamBYOBRequest :: GType -- | Functions for this inteface are in "GHCJS.DOM.ReadableStreamDefaultController". -- -- newtype ReadableStreamDefaultController = ReadableStreamDefaultController { unReadableStreamDefaultController :: JSVal } instance Eq (ReadableStreamDefaultController) where (ReadableStreamDefaultController a) == (ReadableStreamDefaultController b) = js_eq a b instance PToJSVal ReadableStreamDefaultController where pToJSVal = unReadableStreamDefaultController {-# INLINE pToJSVal #-} instance PFromJSVal ReadableStreamDefaultController where pFromJSVal = ReadableStreamDefaultController {-# INLINE pFromJSVal #-} instance ToJSVal ReadableStreamDefaultController where toJSVal = return . unReadableStreamDefaultController {-# INLINE toJSVal #-} instance FromJSVal ReadableStreamDefaultController where fromJSVal = return . fmap ReadableStreamDefaultController . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject ReadableStreamDefaultController where typeGType _ = gTypeReadableStreamDefaultController {-# INLINE typeGType #-} noReadableStreamDefaultController :: Maybe ReadableStreamDefaultController noReadableStreamDefaultController = Nothing {-# INLINE noReadableStreamDefaultController #-} foreign import javascript unsafe "window[\"ReadableStreamDefaultController\"]" gTypeReadableStreamDefaultController :: GType -- | Functions for this inteface are in "GHCJS.DOM.ReadableStreamDefaultReader". -- -- newtype ReadableStreamDefaultReader = ReadableStreamDefaultReader { unReadableStreamDefaultReader :: JSVal } instance Eq (ReadableStreamDefaultReader) where (ReadableStreamDefaultReader a) == (ReadableStreamDefaultReader b) = js_eq a b instance PToJSVal ReadableStreamDefaultReader where pToJSVal = unReadableStreamDefaultReader {-# INLINE pToJSVal #-} instance PFromJSVal ReadableStreamDefaultReader where pFromJSVal = ReadableStreamDefaultReader {-# INLINE pFromJSVal #-} instance ToJSVal ReadableStreamDefaultReader where toJSVal = return . unReadableStreamDefaultReader {-# INLINE toJSVal #-} instance FromJSVal ReadableStreamDefaultReader where fromJSVal = return . fmap ReadableStreamDefaultReader . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject ReadableStreamDefaultReader where typeGType _ = gTypeReadableStreamDefaultReader {-# INLINE typeGType #-} noReadableStreamDefaultReader :: Maybe ReadableStreamDefaultReader noReadableStreamDefaultReader = Nothing {-# INLINE noReadableStreamDefaultReader #-} foreign import javascript unsafe "window[\"ReadableStreamDefaultReader\"]" gTypeReadableStreamDefaultReader :: GType -- | Functions for this inteface are in "GHCJS.DOM.ReadableStreamSource". -- -- newtype ReadableStreamSource = ReadableStreamSource { unReadableStreamSource :: JSVal } instance Eq (ReadableStreamSource) where (ReadableStreamSource a) == (ReadableStreamSource b) = js_eq a b instance PToJSVal ReadableStreamSource where pToJSVal = unReadableStreamSource {-# INLINE pToJSVal #-} instance PFromJSVal ReadableStreamSource where pFromJSVal = ReadableStreamSource {-# INLINE pFromJSVal #-} instance ToJSVal ReadableStreamSource where toJSVal = return . unReadableStreamSource {-# INLINE toJSVal #-} instance FromJSVal ReadableStreamSource where fromJSVal = return . fmap ReadableStreamSource . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject ReadableStreamSource where typeGType _ = gTypeReadableStreamSource {-# INLINE typeGType #-} noReadableStreamSource :: Maybe ReadableStreamSource noReadableStreamSource = Nothing {-# INLINE noReadableStreamSource #-} foreign import javascript unsafe "window[\"ReadableStreamSource\"]" gTypeReadableStreamSource :: GType -- | Functions for this inteface are in "GHCJS.DOM.Rect". -- -- newtype Rect = Rect { unRect :: JSVal } instance Eq (Rect) where (Rect a) == (Rect b) = js_eq a b instance PToJSVal Rect where pToJSVal = unRect {-# INLINE pToJSVal #-} instance PFromJSVal Rect where pFromJSVal = Rect {-# INLINE pFromJSVal #-} instance ToJSVal Rect where toJSVal = return . unRect {-# INLINE toJSVal #-} instance FromJSVal Rect where fromJSVal = return . fmap Rect . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject Rect where typeGType _ = gTypeRect {-# INLINE typeGType #-} noRect :: Maybe Rect noRect = Nothing {-# INLINE noRect #-} foreign import javascript unsafe "window[\"Rect\"]" gTypeRect :: GType -- | Functions for this inteface are in "GHCJS.DOM.Request". -- Base interface functions are in: -- -- * "GHCJS.DOM.Body" -- -- newtype Request = Request { unRequest :: JSVal } instance Eq (Request) where (Request a) == (Request b) = js_eq a b instance PToJSVal Request where pToJSVal = unRequest {-# INLINE pToJSVal #-} instance PFromJSVal Request where pFromJSVal = Request {-# INLINE pFromJSVal #-} instance ToJSVal Request where toJSVal = return . unRequest {-# INLINE toJSVal #-} instance FromJSVal Request where fromJSVal = return . fmap Request . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsBody Request instance IsGObject Request where typeGType _ = gTypeRequest {-# INLINE typeGType #-} noRequest :: Maybe Request noRequest = Nothing {-# INLINE noRequest #-} foreign import javascript unsafe "window[\"Request\"]" gTypeRequest :: GType -- | Functions for this inteface are in "GHCJS.DOM.RequestInit". -- -- newtype RequestInit = RequestInit { unRequestInit :: JSVal } instance Eq (RequestInit) where (RequestInit a) == (RequestInit b) = js_eq a b instance PToJSVal RequestInit where pToJSVal = unRequestInit {-# INLINE pToJSVal #-} instance PFromJSVal RequestInit where pFromJSVal = RequestInit {-# INLINE pFromJSVal #-} instance ToJSVal RequestInit where toJSVal = return . unRequestInit {-# INLINE toJSVal #-} instance FromJSVal RequestInit where fromJSVal = return . fmap RequestInit . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject RequestInit where typeGType _ = gTypeRequestInit {-# INLINE typeGType #-} noRequestInit :: Maybe RequestInit noRequestInit = Nothing {-# INLINE noRequestInit #-} foreign import javascript unsafe "window[\"RequestInit\"]" gTypeRequestInit :: GType -- | Functions for this inteface are in "GHCJS.DOM.Response". -- -- newtype Response = Response { unResponse :: JSVal } instance Eq (Response) where (Response a) == (Response b) = js_eq a b instance PToJSVal Response where pToJSVal = unResponse {-# INLINE pToJSVal #-} instance PFromJSVal Response where pFromJSVal = Response {-# INLINE pFromJSVal #-} instance ToJSVal Response where toJSVal = return . unResponse {-# INLINE toJSVal #-} instance FromJSVal Response where fromJSVal = return . fmap Response . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject Response where typeGType _ = gTypeResponse {-# INLINE typeGType #-} noResponse :: Maybe Response noResponse = Nothing {-# INLINE noResponse #-} foreign import javascript unsafe "window[\"Response\"]" gTypeResponse :: GType -- | Functions for this inteface are in "GHCJS.DOM.RotationRate". -- -- newtype RotationRate = RotationRate { unRotationRate :: JSVal } instance Eq (RotationRate) where (RotationRate a) == (RotationRate b) = js_eq a b instance PToJSVal RotationRate where pToJSVal = unRotationRate {-# INLINE pToJSVal #-} instance PFromJSVal RotationRate where pFromJSVal = RotationRate {-# INLINE pFromJSVal #-} instance ToJSVal RotationRate where toJSVal = return . unRotationRate {-# INLINE toJSVal #-} instance FromJSVal RotationRate where fromJSVal = return . fmap RotationRate . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject RotationRate where typeGType _ = gTypeRotationRate {-# INLINE typeGType #-} noRotationRate :: Maybe RotationRate noRotationRate = Nothing {-# INLINE noRotationRate #-} foreign import javascript unsafe "window[\"RotationRate\"]" gTypeRotationRate :: GType -- | Functions for this inteface are in "GHCJS.DOM.RsaHashedImportParams". -- Base interface functions are in: -- -- * "GHCJS.DOM.CryptoAlgorithmParameters" -- -- newtype RsaHashedImportParams = RsaHashedImportParams { unRsaHashedImportParams :: JSVal } instance Eq (RsaHashedImportParams) where (RsaHashedImportParams a) == (RsaHashedImportParams b) = js_eq a b instance PToJSVal RsaHashedImportParams where pToJSVal = unRsaHashedImportParams {-# INLINE pToJSVal #-} instance PFromJSVal RsaHashedImportParams where pFromJSVal = RsaHashedImportParams {-# INLINE pFromJSVal #-} instance ToJSVal RsaHashedImportParams where toJSVal = return . unRsaHashedImportParams {-# INLINE toJSVal #-} instance FromJSVal RsaHashedImportParams where fromJSVal = return . fmap RsaHashedImportParams . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsCryptoAlgorithmParameters RsaHashedImportParams instance IsGObject RsaHashedImportParams where typeGType _ = gTypeRsaHashedImportParams {-# INLINE typeGType #-} noRsaHashedImportParams :: Maybe RsaHashedImportParams noRsaHashedImportParams = Nothing {-# INLINE noRsaHashedImportParams #-} foreign import javascript unsafe "window[\"RsaHashedImportParams\"]" gTypeRsaHashedImportParams :: GType -- | Functions for this inteface are in "GHCJS.DOM.RsaHashedKeyGenParams". -- Base interface functions are in: -- -- * "GHCJS.DOM.RsaKeyGenParams" -- * "GHCJS.DOM.CryptoAlgorithmParameters" -- -- newtype RsaHashedKeyGenParams = RsaHashedKeyGenParams { unRsaHashedKeyGenParams :: JSVal } instance Eq (RsaHashedKeyGenParams) where (RsaHashedKeyGenParams a) == (RsaHashedKeyGenParams b) = js_eq a b instance PToJSVal RsaHashedKeyGenParams where pToJSVal = unRsaHashedKeyGenParams {-# INLINE pToJSVal #-} instance PFromJSVal RsaHashedKeyGenParams where pFromJSVal = RsaHashedKeyGenParams {-# INLINE pFromJSVal #-} instance ToJSVal RsaHashedKeyGenParams where toJSVal = return . unRsaHashedKeyGenParams {-# INLINE toJSVal #-} instance FromJSVal RsaHashedKeyGenParams where fromJSVal = return . fmap RsaHashedKeyGenParams . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsRsaKeyGenParams RsaHashedKeyGenParams instance IsCryptoAlgorithmParameters RsaHashedKeyGenParams instance IsGObject RsaHashedKeyGenParams where typeGType _ = gTypeRsaHashedKeyGenParams {-# INLINE typeGType #-} noRsaHashedKeyGenParams :: Maybe RsaHashedKeyGenParams noRsaHashedKeyGenParams = Nothing {-# INLINE noRsaHashedKeyGenParams #-} foreign import javascript unsafe "window[\"RsaHashedKeyGenParams\"]" gTypeRsaHashedKeyGenParams :: GType -- | Functions for this inteface are in "GHCJS.DOM.RsaKeyGenParams". -- Base interface functions are in: -- -- * "GHCJS.DOM.CryptoAlgorithmParameters" -- -- newtype RsaKeyGenParams = RsaKeyGenParams { unRsaKeyGenParams :: JSVal } instance Eq (RsaKeyGenParams) where (RsaKeyGenParams a) == (RsaKeyGenParams b) = js_eq a b instance PToJSVal RsaKeyGenParams where pToJSVal = unRsaKeyGenParams {-# INLINE pToJSVal #-} instance PFromJSVal RsaKeyGenParams where pFromJSVal = RsaKeyGenParams {-# INLINE pFromJSVal #-} instance ToJSVal RsaKeyGenParams where toJSVal = return . unRsaKeyGenParams {-# INLINE toJSVal #-} instance FromJSVal RsaKeyGenParams where fromJSVal = return . fmap RsaKeyGenParams . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsCryptoAlgorithmParameters o, IsGObject o) => IsRsaKeyGenParams o toRsaKeyGenParams :: IsRsaKeyGenParams o => o -> RsaKeyGenParams toRsaKeyGenParams = RsaKeyGenParams . coerce instance IsRsaKeyGenParams RsaKeyGenParams instance IsCryptoAlgorithmParameters RsaKeyGenParams instance IsGObject RsaKeyGenParams where typeGType _ = gTypeRsaKeyGenParams {-# INLINE typeGType #-} noRsaKeyGenParams :: Maybe RsaKeyGenParams noRsaKeyGenParams = Nothing {-# INLINE noRsaKeyGenParams #-} foreign import javascript unsafe "window[\"RsaKeyGenParams\"]" gTypeRsaKeyGenParams :: GType -- | Functions for this inteface are in "GHCJS.DOM.RsaOaepParams". -- Base interface functions are in: -- -- * "GHCJS.DOM.CryptoAlgorithmParameters" -- -- newtype RsaOaepParams = RsaOaepParams { unRsaOaepParams :: JSVal } instance Eq (RsaOaepParams) where (RsaOaepParams a) == (RsaOaepParams b) = js_eq a b instance PToJSVal RsaOaepParams where pToJSVal = unRsaOaepParams {-# INLINE pToJSVal #-} instance PFromJSVal RsaOaepParams where pFromJSVal = RsaOaepParams {-# INLINE pFromJSVal #-} instance ToJSVal RsaOaepParams where toJSVal = return . unRsaOaepParams {-# INLINE toJSVal #-} instance FromJSVal RsaOaepParams where fromJSVal = return . fmap RsaOaepParams . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsCryptoAlgorithmParameters RsaOaepParams instance IsGObject RsaOaepParams where typeGType _ = gTypeRsaOaepParams {-# INLINE typeGType #-} noRsaOaepParams :: Maybe RsaOaepParams noRsaOaepParams = Nothing {-# INLINE noRsaOaepParams #-} foreign import javascript unsafe "window[\"RsaOaepParams\"]" gTypeRsaOaepParams :: GType -- | Functions for this inteface are in "GHCJS.DOM.RsaOtherPrimesInfo". -- -- newtype RsaOtherPrimesInfo = RsaOtherPrimesInfo { unRsaOtherPrimesInfo :: JSVal } instance Eq (RsaOtherPrimesInfo) where (RsaOtherPrimesInfo a) == (RsaOtherPrimesInfo b) = js_eq a b instance PToJSVal RsaOtherPrimesInfo where pToJSVal = unRsaOtherPrimesInfo {-# INLINE pToJSVal #-} instance PFromJSVal RsaOtherPrimesInfo where pFromJSVal = RsaOtherPrimesInfo {-# INLINE pFromJSVal #-} instance ToJSVal RsaOtherPrimesInfo where toJSVal = return . unRsaOtherPrimesInfo {-# INLINE toJSVal #-} instance FromJSVal RsaOtherPrimesInfo where fromJSVal = return . fmap RsaOtherPrimesInfo . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject RsaOtherPrimesInfo where typeGType _ = gTypeRsaOtherPrimesInfo {-# INLINE typeGType #-} noRsaOtherPrimesInfo :: Maybe RsaOtherPrimesInfo noRsaOtherPrimesInfo = Nothing {-# INLINE noRsaOtherPrimesInfo #-} foreign import javascript unsafe "window[\"RsaOtherPrimesInfo\"]" gTypeRsaOtherPrimesInfo :: GType -- | Functions for this inteface are in "GHCJS.DOM.SQLError". -- -- newtype SQLError = SQLError { unSQLError :: JSVal } instance Eq (SQLError) where (SQLError a) == (SQLError b) = js_eq a b instance PToJSVal SQLError where pToJSVal = unSQLError {-# INLINE pToJSVal #-} instance PFromJSVal SQLError where pFromJSVal = SQLError {-# INLINE pFromJSVal #-} instance ToJSVal SQLError where toJSVal = return . unSQLError {-# INLINE toJSVal #-} instance FromJSVal SQLError where fromJSVal = return . fmap SQLError . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject SQLError where typeGType _ = gTypeSQLError {-# INLINE typeGType #-} noSQLError :: Maybe SQLError noSQLError = Nothing {-# INLINE noSQLError #-} foreign import javascript unsafe "window[\"SQLError\"]" gTypeSQLError :: GType -- | Functions for this inteface are in "GHCJS.DOM.SQLException". -- -- newtype SQLException = SQLException { unSQLException :: JSVal } instance Eq (SQLException) where (SQLException a) == (SQLException b) = js_eq a b instance PToJSVal SQLException where pToJSVal = unSQLException {-# INLINE pToJSVal #-} instance PFromJSVal SQLException where pFromJSVal = SQLException {-# INLINE pFromJSVal #-} instance ToJSVal SQLException where toJSVal = return . unSQLException {-# INLINE toJSVal #-} instance FromJSVal SQLException where fromJSVal = return . fmap SQLException . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject SQLException where typeGType _ = gTypeSQLException {-# INLINE typeGType #-} noSQLException :: Maybe SQLException noSQLException = Nothing {-# INLINE noSQLException #-} foreign import javascript unsafe "window[\"SQLException\"]" gTypeSQLException :: GType -- | Functions for this inteface are in "GHCJS.DOM.SQLResultSet". -- -- newtype SQLResultSet = SQLResultSet { unSQLResultSet :: JSVal } instance Eq (SQLResultSet) where (SQLResultSet a) == (SQLResultSet b) = js_eq a b instance PToJSVal SQLResultSet where pToJSVal = unSQLResultSet {-# INLINE pToJSVal #-} instance PFromJSVal SQLResultSet where pFromJSVal = SQLResultSet {-# INLINE pFromJSVal #-} instance ToJSVal SQLResultSet where toJSVal = return . unSQLResultSet {-# INLINE toJSVal #-} instance FromJSVal SQLResultSet where fromJSVal = return . fmap SQLResultSet . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject SQLResultSet where typeGType _ = gTypeSQLResultSet {-# INLINE typeGType #-} noSQLResultSet :: Maybe SQLResultSet noSQLResultSet = Nothing {-# INLINE noSQLResultSet #-} foreign import javascript unsafe "window[\"SQLResultSet\"]" gTypeSQLResultSet :: GType -- | Functions for this inteface are in "GHCJS.DOM.SQLResultSetRowList". -- -- newtype SQLResultSetRowList = SQLResultSetRowList { unSQLResultSetRowList :: JSVal } instance Eq (SQLResultSetRowList) where (SQLResultSetRowList a) == (SQLResultSetRowList b) = js_eq a b instance PToJSVal SQLResultSetRowList where pToJSVal = unSQLResultSetRowList {-# INLINE pToJSVal #-} instance PFromJSVal SQLResultSetRowList where pFromJSVal = SQLResultSetRowList {-# INLINE pFromJSVal #-} instance ToJSVal SQLResultSetRowList where toJSVal = return . unSQLResultSetRowList {-# INLINE toJSVal #-} instance FromJSVal SQLResultSetRowList where fromJSVal = return . fmap SQLResultSetRowList . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject SQLResultSetRowList where typeGType _ = gTypeSQLResultSetRowList {-# INLINE typeGType #-} noSQLResultSetRowList :: Maybe SQLResultSetRowList noSQLResultSetRowList = Nothing {-# INLINE noSQLResultSetRowList #-} foreign import javascript unsafe "window[\"SQLResultSetRowList\"]" gTypeSQLResultSetRowList :: GType -- | Functions for this inteface are in "GHCJS.DOM.SQLTransaction". -- -- newtype SQLTransaction = SQLTransaction { unSQLTransaction :: JSVal } instance Eq (SQLTransaction) where (SQLTransaction a) == (SQLTransaction b) = js_eq a b instance PToJSVal SQLTransaction where pToJSVal = unSQLTransaction {-# INLINE pToJSVal #-} instance PFromJSVal SQLTransaction where pFromJSVal = SQLTransaction {-# INLINE pFromJSVal #-} instance ToJSVal SQLTransaction where toJSVal = return . unSQLTransaction {-# INLINE toJSVal #-} instance FromJSVal SQLTransaction where fromJSVal = return . fmap SQLTransaction . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject SQLTransaction where typeGType _ = gTypeSQLTransaction {-# INLINE typeGType #-} noSQLTransaction :: Maybe SQLTransaction noSQLTransaction = Nothing {-# INLINE noSQLTransaction #-} foreign import javascript unsafe "window[\"SQLTransaction\"]" gTypeSQLTransaction :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGAElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGGraphicsElement" -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- * "GHCJS.DOM.SVGTests" -- * "GHCJS.DOM.SVGURIReference" -- * "GHCJS.DOM.SVGExternalResourcesRequired" -- -- newtype SVGAElement = SVGAElement { unSVGAElement :: JSVal } instance Eq (SVGAElement) where (SVGAElement a) == (SVGAElement b) = js_eq a b instance PToJSVal SVGAElement where pToJSVal = unSVGAElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGAElement where pFromJSVal = SVGAElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGAElement where toJSVal = return . unSVGAElement {-# INLINE toJSVal #-} instance FromJSVal SVGAElement where fromJSVal = return . fmap SVGAElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGGraphicsElement SVGAElement instance IsSVGElement SVGAElement instance IsElement SVGAElement instance IsNode SVGAElement instance IsEventTarget SVGAElement instance IsSlotable SVGAElement instance IsParentNode SVGAElement instance IsNonDocumentTypeChildNode SVGAElement instance IsDocumentAndElementEventHandlers SVGAElement instance IsChildNode SVGAElement instance IsAnimatable SVGAElement instance IsGlobalEventHandlers SVGAElement instance IsElementCSSInlineStyle SVGAElement instance IsSVGTests SVGAElement instance IsSVGURIReference SVGAElement instance IsSVGExternalResourcesRequired SVGAElement instance IsGObject SVGAElement where typeGType _ = gTypeSVGAElement {-# INLINE typeGType #-} noSVGAElement :: Maybe SVGAElement noSVGAElement = Nothing {-# INLINE noSVGAElement #-} foreign import javascript unsafe "window[\"SVGAElement\"]" gTypeSVGAElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGAltGlyphDefElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype SVGAltGlyphDefElement = SVGAltGlyphDefElement { unSVGAltGlyphDefElement :: JSVal } instance Eq (SVGAltGlyphDefElement) where (SVGAltGlyphDefElement a) == (SVGAltGlyphDefElement b) = js_eq a b instance PToJSVal SVGAltGlyphDefElement where pToJSVal = unSVGAltGlyphDefElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGAltGlyphDefElement where pFromJSVal = SVGAltGlyphDefElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGAltGlyphDefElement where toJSVal = return . unSVGAltGlyphDefElement {-# INLINE toJSVal #-} instance FromJSVal SVGAltGlyphDefElement where fromJSVal = return . fmap SVGAltGlyphDefElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGElement SVGAltGlyphDefElement instance IsElement SVGAltGlyphDefElement instance IsNode SVGAltGlyphDefElement instance IsEventTarget SVGAltGlyphDefElement instance IsSlotable SVGAltGlyphDefElement instance IsParentNode SVGAltGlyphDefElement instance IsNonDocumentTypeChildNode SVGAltGlyphDefElement instance IsDocumentAndElementEventHandlers SVGAltGlyphDefElement instance IsChildNode SVGAltGlyphDefElement instance IsAnimatable SVGAltGlyphDefElement instance IsGlobalEventHandlers SVGAltGlyphDefElement instance IsElementCSSInlineStyle SVGAltGlyphDefElement instance IsGObject SVGAltGlyphDefElement where typeGType _ = gTypeSVGAltGlyphDefElement {-# INLINE typeGType #-} noSVGAltGlyphDefElement :: Maybe SVGAltGlyphDefElement noSVGAltGlyphDefElement = Nothing {-# INLINE noSVGAltGlyphDefElement #-} foreign import javascript unsafe "window[\"SVGAltGlyphDefElement\"]" gTypeSVGAltGlyphDefElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGAltGlyphElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGTextPositioningElement" -- * "GHCJS.DOM.SVGTextContentElement" -- * "GHCJS.DOM.SVGGraphicsElement" -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- * "GHCJS.DOM.SVGTests" -- * "GHCJS.DOM.SVGExternalResourcesRequired" -- * "GHCJS.DOM.SVGURIReference" -- -- newtype SVGAltGlyphElement = SVGAltGlyphElement { unSVGAltGlyphElement :: JSVal } instance Eq (SVGAltGlyphElement) where (SVGAltGlyphElement a) == (SVGAltGlyphElement b) = js_eq a b instance PToJSVal SVGAltGlyphElement where pToJSVal = unSVGAltGlyphElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGAltGlyphElement where pFromJSVal = SVGAltGlyphElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGAltGlyphElement where toJSVal = return . unSVGAltGlyphElement {-# INLINE toJSVal #-} instance FromJSVal SVGAltGlyphElement where fromJSVal = return . fmap SVGAltGlyphElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGTextPositioningElement SVGAltGlyphElement instance IsSVGTextContentElement SVGAltGlyphElement instance IsSVGGraphicsElement SVGAltGlyphElement instance IsSVGElement SVGAltGlyphElement instance IsElement SVGAltGlyphElement instance IsNode SVGAltGlyphElement instance IsEventTarget SVGAltGlyphElement instance IsSlotable SVGAltGlyphElement instance IsParentNode SVGAltGlyphElement instance IsNonDocumentTypeChildNode SVGAltGlyphElement instance IsDocumentAndElementEventHandlers SVGAltGlyphElement instance IsChildNode SVGAltGlyphElement instance IsAnimatable SVGAltGlyphElement instance IsGlobalEventHandlers SVGAltGlyphElement instance IsElementCSSInlineStyle SVGAltGlyphElement instance IsSVGTests SVGAltGlyphElement instance IsSVGExternalResourcesRequired SVGAltGlyphElement instance IsSVGURIReference SVGAltGlyphElement instance IsGObject SVGAltGlyphElement where typeGType _ = gTypeSVGAltGlyphElement {-# INLINE typeGType #-} noSVGAltGlyphElement :: Maybe SVGAltGlyphElement noSVGAltGlyphElement = Nothing {-# INLINE noSVGAltGlyphElement #-} foreign import javascript unsafe "window[\"SVGAltGlyphElement\"]" gTypeSVGAltGlyphElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGAltGlyphItemElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype SVGAltGlyphItemElement = SVGAltGlyphItemElement { unSVGAltGlyphItemElement :: JSVal } instance Eq (SVGAltGlyphItemElement) where (SVGAltGlyphItemElement a) == (SVGAltGlyphItemElement b) = js_eq a b instance PToJSVal SVGAltGlyphItemElement where pToJSVal = unSVGAltGlyphItemElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGAltGlyphItemElement where pFromJSVal = SVGAltGlyphItemElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGAltGlyphItemElement where toJSVal = return . unSVGAltGlyphItemElement {-# INLINE toJSVal #-} instance FromJSVal SVGAltGlyphItemElement where fromJSVal = return . fmap SVGAltGlyphItemElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGElement SVGAltGlyphItemElement instance IsElement SVGAltGlyphItemElement instance IsNode SVGAltGlyphItemElement instance IsEventTarget SVGAltGlyphItemElement instance IsSlotable SVGAltGlyphItemElement instance IsParentNode SVGAltGlyphItemElement instance IsNonDocumentTypeChildNode SVGAltGlyphItemElement instance IsDocumentAndElementEventHandlers SVGAltGlyphItemElement instance IsChildNode SVGAltGlyphItemElement instance IsAnimatable SVGAltGlyphItemElement instance IsGlobalEventHandlers SVGAltGlyphItemElement instance IsElementCSSInlineStyle SVGAltGlyphItemElement instance IsGObject SVGAltGlyphItemElement where typeGType _ = gTypeSVGAltGlyphItemElement {-# INLINE typeGType #-} noSVGAltGlyphItemElement :: Maybe SVGAltGlyphItemElement noSVGAltGlyphItemElement = Nothing {-# INLINE noSVGAltGlyphItemElement #-} foreign import javascript unsafe "window[\"SVGAltGlyphItemElement\"]" gTypeSVGAltGlyphItemElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGAngle". -- -- newtype SVGAngle = SVGAngle { unSVGAngle :: JSVal } instance Eq (SVGAngle) where (SVGAngle a) == (SVGAngle b) = js_eq a b instance PToJSVal SVGAngle where pToJSVal = unSVGAngle {-# INLINE pToJSVal #-} instance PFromJSVal SVGAngle where pFromJSVal = SVGAngle {-# INLINE pFromJSVal #-} instance ToJSVal SVGAngle where toJSVal = return . unSVGAngle {-# INLINE toJSVal #-} instance FromJSVal SVGAngle where fromJSVal = return . fmap SVGAngle . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject SVGAngle where typeGType _ = gTypeSVGAngle {-# INLINE typeGType #-} noSVGAngle :: Maybe SVGAngle noSVGAngle = Nothing {-# INLINE noSVGAngle #-} foreign import javascript unsafe "window[\"SVGAngle\"]" gTypeSVGAngle :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGAnimateColorElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGAnimationElement" -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- * "GHCJS.DOM.SVGTests" -- * "GHCJS.DOM.SVGExternalResourcesRequired" -- -- newtype SVGAnimateColorElement = SVGAnimateColorElement { unSVGAnimateColorElement :: JSVal } instance Eq (SVGAnimateColorElement) where (SVGAnimateColorElement a) == (SVGAnimateColorElement b) = js_eq a b instance PToJSVal SVGAnimateColorElement where pToJSVal = unSVGAnimateColorElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGAnimateColorElement where pFromJSVal = SVGAnimateColorElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGAnimateColorElement where toJSVal = return . unSVGAnimateColorElement {-# INLINE toJSVal #-} instance FromJSVal SVGAnimateColorElement where fromJSVal = return . fmap SVGAnimateColorElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGAnimationElement SVGAnimateColorElement instance IsSVGElement SVGAnimateColorElement instance IsElement SVGAnimateColorElement instance IsNode SVGAnimateColorElement instance IsEventTarget SVGAnimateColorElement instance IsSlotable SVGAnimateColorElement instance IsParentNode SVGAnimateColorElement instance IsNonDocumentTypeChildNode SVGAnimateColorElement instance IsDocumentAndElementEventHandlers SVGAnimateColorElement instance IsChildNode SVGAnimateColorElement instance IsAnimatable SVGAnimateColorElement instance IsGlobalEventHandlers SVGAnimateColorElement instance IsElementCSSInlineStyle SVGAnimateColorElement instance IsSVGTests SVGAnimateColorElement instance IsSVGExternalResourcesRequired SVGAnimateColorElement instance IsGObject SVGAnimateColorElement where typeGType _ = gTypeSVGAnimateColorElement {-# INLINE typeGType #-} noSVGAnimateColorElement :: Maybe SVGAnimateColorElement noSVGAnimateColorElement = Nothing {-# INLINE noSVGAnimateColorElement #-} foreign import javascript unsafe "window[\"SVGAnimateColorElement\"]" gTypeSVGAnimateColorElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGAnimateElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGAnimationElement" -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- * "GHCJS.DOM.SVGTests" -- * "GHCJS.DOM.SVGExternalResourcesRequired" -- -- newtype SVGAnimateElement = SVGAnimateElement { unSVGAnimateElement :: JSVal } instance Eq (SVGAnimateElement) where (SVGAnimateElement a) == (SVGAnimateElement b) = js_eq a b instance PToJSVal SVGAnimateElement where pToJSVal = unSVGAnimateElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGAnimateElement where pFromJSVal = SVGAnimateElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGAnimateElement where toJSVal = return . unSVGAnimateElement {-# INLINE toJSVal #-} instance FromJSVal SVGAnimateElement where fromJSVal = return . fmap SVGAnimateElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGAnimationElement SVGAnimateElement instance IsSVGElement SVGAnimateElement instance IsElement SVGAnimateElement instance IsNode SVGAnimateElement instance IsEventTarget SVGAnimateElement instance IsSlotable SVGAnimateElement instance IsParentNode SVGAnimateElement instance IsNonDocumentTypeChildNode SVGAnimateElement instance IsDocumentAndElementEventHandlers SVGAnimateElement instance IsChildNode SVGAnimateElement instance IsAnimatable SVGAnimateElement instance IsGlobalEventHandlers SVGAnimateElement instance IsElementCSSInlineStyle SVGAnimateElement instance IsSVGTests SVGAnimateElement instance IsSVGExternalResourcesRequired SVGAnimateElement instance IsGObject SVGAnimateElement where typeGType _ = gTypeSVGAnimateElement {-# INLINE typeGType #-} noSVGAnimateElement :: Maybe SVGAnimateElement noSVGAnimateElement = Nothing {-# INLINE noSVGAnimateElement #-} foreign import javascript unsafe "window[\"SVGAnimateElement\"]" gTypeSVGAnimateElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGAnimateMotionElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGAnimationElement" -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- * "GHCJS.DOM.SVGTests" -- * "GHCJS.DOM.SVGExternalResourcesRequired" -- -- newtype SVGAnimateMotionElement = SVGAnimateMotionElement { unSVGAnimateMotionElement :: JSVal } instance Eq (SVGAnimateMotionElement) where (SVGAnimateMotionElement a) == (SVGAnimateMotionElement b) = js_eq a b instance PToJSVal SVGAnimateMotionElement where pToJSVal = unSVGAnimateMotionElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGAnimateMotionElement where pFromJSVal = SVGAnimateMotionElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGAnimateMotionElement where toJSVal = return . unSVGAnimateMotionElement {-# INLINE toJSVal #-} instance FromJSVal SVGAnimateMotionElement where fromJSVal = return . fmap SVGAnimateMotionElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGAnimationElement SVGAnimateMotionElement instance IsSVGElement SVGAnimateMotionElement instance IsElement SVGAnimateMotionElement instance IsNode SVGAnimateMotionElement instance IsEventTarget SVGAnimateMotionElement instance IsSlotable SVGAnimateMotionElement instance IsParentNode SVGAnimateMotionElement instance IsNonDocumentTypeChildNode SVGAnimateMotionElement instance IsDocumentAndElementEventHandlers SVGAnimateMotionElement instance IsChildNode SVGAnimateMotionElement instance IsAnimatable SVGAnimateMotionElement instance IsGlobalEventHandlers SVGAnimateMotionElement instance IsElementCSSInlineStyle SVGAnimateMotionElement instance IsSVGTests SVGAnimateMotionElement instance IsSVGExternalResourcesRequired SVGAnimateMotionElement instance IsGObject SVGAnimateMotionElement where typeGType _ = gTypeSVGAnimateMotionElement {-# INLINE typeGType #-} noSVGAnimateMotionElement :: Maybe SVGAnimateMotionElement noSVGAnimateMotionElement = Nothing {-# INLINE noSVGAnimateMotionElement #-} foreign import javascript unsafe "window[\"SVGAnimateMotionElement\"]" gTypeSVGAnimateMotionElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGAnimateTransformElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGAnimationElement" -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- * "GHCJS.DOM.SVGTests" -- * "GHCJS.DOM.SVGExternalResourcesRequired" -- -- newtype SVGAnimateTransformElement = SVGAnimateTransformElement { unSVGAnimateTransformElement :: JSVal } instance Eq (SVGAnimateTransformElement) where (SVGAnimateTransformElement a) == (SVGAnimateTransformElement b) = js_eq a b instance PToJSVal SVGAnimateTransformElement where pToJSVal = unSVGAnimateTransformElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGAnimateTransformElement where pFromJSVal = SVGAnimateTransformElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGAnimateTransformElement where toJSVal = return . unSVGAnimateTransformElement {-# INLINE toJSVal #-} instance FromJSVal SVGAnimateTransformElement where fromJSVal = return . fmap SVGAnimateTransformElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGAnimationElement SVGAnimateTransformElement instance IsSVGElement SVGAnimateTransformElement instance IsElement SVGAnimateTransformElement instance IsNode SVGAnimateTransformElement instance IsEventTarget SVGAnimateTransformElement instance IsSlotable SVGAnimateTransformElement instance IsParentNode SVGAnimateTransformElement instance IsNonDocumentTypeChildNode SVGAnimateTransformElement instance IsDocumentAndElementEventHandlers SVGAnimateTransformElement instance IsChildNode SVGAnimateTransformElement instance IsAnimatable SVGAnimateTransformElement instance IsGlobalEventHandlers SVGAnimateTransformElement instance IsElementCSSInlineStyle SVGAnimateTransformElement instance IsSVGTests SVGAnimateTransformElement instance IsSVGExternalResourcesRequired SVGAnimateTransformElement instance IsGObject SVGAnimateTransformElement where typeGType _ = gTypeSVGAnimateTransformElement {-# INLINE typeGType #-} noSVGAnimateTransformElement :: Maybe SVGAnimateTransformElement noSVGAnimateTransformElement = Nothing {-# INLINE noSVGAnimateTransformElement #-} foreign import javascript unsafe "window[\"SVGAnimateTransformElement\"]" gTypeSVGAnimateTransformElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGAnimatedAngle". -- -- newtype SVGAnimatedAngle = SVGAnimatedAngle { unSVGAnimatedAngle :: JSVal } instance Eq (SVGAnimatedAngle) where (SVGAnimatedAngle a) == (SVGAnimatedAngle b) = js_eq a b instance PToJSVal SVGAnimatedAngle where pToJSVal = unSVGAnimatedAngle {-# INLINE pToJSVal #-} instance PFromJSVal SVGAnimatedAngle where pFromJSVal = SVGAnimatedAngle {-# INLINE pFromJSVal #-} instance ToJSVal SVGAnimatedAngle where toJSVal = return . unSVGAnimatedAngle {-# INLINE toJSVal #-} instance FromJSVal SVGAnimatedAngle where fromJSVal = return . fmap SVGAnimatedAngle . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject SVGAnimatedAngle where typeGType _ = gTypeSVGAnimatedAngle {-# INLINE typeGType #-} noSVGAnimatedAngle :: Maybe SVGAnimatedAngle noSVGAnimatedAngle = Nothing {-# INLINE noSVGAnimatedAngle #-} foreign import javascript unsafe "window[\"SVGAnimatedAngle\"]" gTypeSVGAnimatedAngle :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGAnimatedBoolean". -- -- newtype SVGAnimatedBoolean = SVGAnimatedBoolean { unSVGAnimatedBoolean :: JSVal } instance Eq (SVGAnimatedBoolean) where (SVGAnimatedBoolean a) == (SVGAnimatedBoolean b) = js_eq a b instance PToJSVal SVGAnimatedBoolean where pToJSVal = unSVGAnimatedBoolean {-# INLINE pToJSVal #-} instance PFromJSVal SVGAnimatedBoolean where pFromJSVal = SVGAnimatedBoolean {-# INLINE pFromJSVal #-} instance ToJSVal SVGAnimatedBoolean where toJSVal = return . unSVGAnimatedBoolean {-# INLINE toJSVal #-} instance FromJSVal SVGAnimatedBoolean where fromJSVal = return . fmap SVGAnimatedBoolean . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject SVGAnimatedBoolean where typeGType _ = gTypeSVGAnimatedBoolean {-# INLINE typeGType #-} noSVGAnimatedBoolean :: Maybe SVGAnimatedBoolean noSVGAnimatedBoolean = Nothing {-# INLINE noSVGAnimatedBoolean #-} foreign import javascript unsafe "window[\"SVGAnimatedBoolean\"]" gTypeSVGAnimatedBoolean :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGAnimatedEnumeration". -- -- newtype SVGAnimatedEnumeration = SVGAnimatedEnumeration { unSVGAnimatedEnumeration :: JSVal } instance Eq (SVGAnimatedEnumeration) where (SVGAnimatedEnumeration a) == (SVGAnimatedEnumeration b) = js_eq a b instance PToJSVal SVGAnimatedEnumeration where pToJSVal = unSVGAnimatedEnumeration {-# INLINE pToJSVal #-} instance PFromJSVal SVGAnimatedEnumeration where pFromJSVal = SVGAnimatedEnumeration {-# INLINE pFromJSVal #-} instance ToJSVal SVGAnimatedEnumeration where toJSVal = return . unSVGAnimatedEnumeration {-# INLINE toJSVal #-} instance FromJSVal SVGAnimatedEnumeration where fromJSVal = return . fmap SVGAnimatedEnumeration . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject SVGAnimatedEnumeration where typeGType _ = gTypeSVGAnimatedEnumeration {-# INLINE typeGType #-} noSVGAnimatedEnumeration :: Maybe SVGAnimatedEnumeration noSVGAnimatedEnumeration = Nothing {-# INLINE noSVGAnimatedEnumeration #-} foreign import javascript unsafe "window[\"SVGAnimatedEnumeration\"]" gTypeSVGAnimatedEnumeration :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGAnimatedInteger". -- -- newtype SVGAnimatedInteger = SVGAnimatedInteger { unSVGAnimatedInteger :: JSVal } instance Eq (SVGAnimatedInteger) where (SVGAnimatedInteger a) == (SVGAnimatedInteger b) = js_eq a b instance PToJSVal SVGAnimatedInteger where pToJSVal = unSVGAnimatedInteger {-# INLINE pToJSVal #-} instance PFromJSVal SVGAnimatedInteger where pFromJSVal = SVGAnimatedInteger {-# INLINE pFromJSVal #-} instance ToJSVal SVGAnimatedInteger where toJSVal = return . unSVGAnimatedInteger {-# INLINE toJSVal #-} instance FromJSVal SVGAnimatedInteger where fromJSVal = return . fmap SVGAnimatedInteger . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject SVGAnimatedInteger where typeGType _ = gTypeSVGAnimatedInteger {-# INLINE typeGType #-} noSVGAnimatedInteger :: Maybe SVGAnimatedInteger noSVGAnimatedInteger = Nothing {-# INLINE noSVGAnimatedInteger #-} foreign import javascript unsafe "window[\"SVGAnimatedInteger\"]" gTypeSVGAnimatedInteger :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGAnimatedLength". -- -- newtype SVGAnimatedLength = SVGAnimatedLength { unSVGAnimatedLength :: JSVal } instance Eq (SVGAnimatedLength) where (SVGAnimatedLength a) == (SVGAnimatedLength b) = js_eq a b instance PToJSVal SVGAnimatedLength where pToJSVal = unSVGAnimatedLength {-# INLINE pToJSVal #-} instance PFromJSVal SVGAnimatedLength where pFromJSVal = SVGAnimatedLength {-# INLINE pFromJSVal #-} instance ToJSVal SVGAnimatedLength where toJSVal = return . unSVGAnimatedLength {-# INLINE toJSVal #-} instance FromJSVal SVGAnimatedLength where fromJSVal = return . fmap SVGAnimatedLength . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject SVGAnimatedLength where typeGType _ = gTypeSVGAnimatedLength {-# INLINE typeGType #-} noSVGAnimatedLength :: Maybe SVGAnimatedLength noSVGAnimatedLength = Nothing {-# INLINE noSVGAnimatedLength #-} foreign import javascript unsafe "window[\"SVGAnimatedLength\"]" gTypeSVGAnimatedLength :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGAnimatedLengthList". -- -- newtype SVGAnimatedLengthList = SVGAnimatedLengthList { unSVGAnimatedLengthList :: JSVal } instance Eq (SVGAnimatedLengthList) where (SVGAnimatedLengthList a) == (SVGAnimatedLengthList b) = js_eq a b instance PToJSVal SVGAnimatedLengthList where pToJSVal = unSVGAnimatedLengthList {-# INLINE pToJSVal #-} instance PFromJSVal SVGAnimatedLengthList where pFromJSVal = SVGAnimatedLengthList {-# INLINE pFromJSVal #-} instance ToJSVal SVGAnimatedLengthList where toJSVal = return . unSVGAnimatedLengthList {-# INLINE toJSVal #-} instance FromJSVal SVGAnimatedLengthList where fromJSVal = return . fmap SVGAnimatedLengthList . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject SVGAnimatedLengthList where typeGType _ = gTypeSVGAnimatedLengthList {-# INLINE typeGType #-} noSVGAnimatedLengthList :: Maybe SVGAnimatedLengthList noSVGAnimatedLengthList = Nothing {-# INLINE noSVGAnimatedLengthList #-} foreign import javascript unsafe "window[\"SVGAnimatedLengthList\"]" gTypeSVGAnimatedLengthList :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGAnimatedNumber". -- -- newtype SVGAnimatedNumber = SVGAnimatedNumber { unSVGAnimatedNumber :: JSVal } instance Eq (SVGAnimatedNumber) where (SVGAnimatedNumber a) == (SVGAnimatedNumber b) = js_eq a b instance PToJSVal SVGAnimatedNumber where pToJSVal = unSVGAnimatedNumber {-# INLINE pToJSVal #-} instance PFromJSVal SVGAnimatedNumber where pFromJSVal = SVGAnimatedNumber {-# INLINE pFromJSVal #-} instance ToJSVal SVGAnimatedNumber where toJSVal = return . unSVGAnimatedNumber {-# INLINE toJSVal #-} instance FromJSVal SVGAnimatedNumber where fromJSVal = return . fmap SVGAnimatedNumber . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject SVGAnimatedNumber where typeGType _ = gTypeSVGAnimatedNumber {-# INLINE typeGType #-} noSVGAnimatedNumber :: Maybe SVGAnimatedNumber noSVGAnimatedNumber = Nothing {-# INLINE noSVGAnimatedNumber #-} foreign import javascript unsafe "window[\"SVGAnimatedNumber\"]" gTypeSVGAnimatedNumber :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGAnimatedNumberList". -- -- newtype SVGAnimatedNumberList = SVGAnimatedNumberList { unSVGAnimatedNumberList :: JSVal } instance Eq (SVGAnimatedNumberList) where (SVGAnimatedNumberList a) == (SVGAnimatedNumberList b) = js_eq a b instance PToJSVal SVGAnimatedNumberList where pToJSVal = unSVGAnimatedNumberList {-# INLINE pToJSVal #-} instance PFromJSVal SVGAnimatedNumberList where pFromJSVal = SVGAnimatedNumberList {-# INLINE pFromJSVal #-} instance ToJSVal SVGAnimatedNumberList where toJSVal = return . unSVGAnimatedNumberList {-# INLINE toJSVal #-} instance FromJSVal SVGAnimatedNumberList where fromJSVal = return . fmap SVGAnimatedNumberList . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject SVGAnimatedNumberList where typeGType _ = gTypeSVGAnimatedNumberList {-# INLINE typeGType #-} noSVGAnimatedNumberList :: Maybe SVGAnimatedNumberList noSVGAnimatedNumberList = Nothing {-# INLINE noSVGAnimatedNumberList #-} foreign import javascript unsafe "window[\"SVGAnimatedNumberList\"]" gTypeSVGAnimatedNumberList :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGAnimatedPreserveAspectRatio". -- -- newtype SVGAnimatedPreserveAspectRatio = SVGAnimatedPreserveAspectRatio { unSVGAnimatedPreserveAspectRatio :: JSVal } instance Eq (SVGAnimatedPreserveAspectRatio) where (SVGAnimatedPreserveAspectRatio a) == (SVGAnimatedPreserveAspectRatio b) = js_eq a b instance PToJSVal SVGAnimatedPreserveAspectRatio where pToJSVal = unSVGAnimatedPreserveAspectRatio {-# INLINE pToJSVal #-} instance PFromJSVal SVGAnimatedPreserveAspectRatio where pFromJSVal = SVGAnimatedPreserveAspectRatio {-# INLINE pFromJSVal #-} instance ToJSVal SVGAnimatedPreserveAspectRatio where toJSVal = return . unSVGAnimatedPreserveAspectRatio {-# INLINE toJSVal #-} instance FromJSVal SVGAnimatedPreserveAspectRatio where fromJSVal = return . fmap SVGAnimatedPreserveAspectRatio . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject SVGAnimatedPreserveAspectRatio where typeGType _ = gTypeSVGAnimatedPreserveAspectRatio {-# INLINE typeGType #-} noSVGAnimatedPreserveAspectRatio :: Maybe SVGAnimatedPreserveAspectRatio noSVGAnimatedPreserveAspectRatio = Nothing {-# INLINE noSVGAnimatedPreserveAspectRatio #-} foreign import javascript unsafe "window[\"SVGAnimatedPreserveAspectRatio\"]" gTypeSVGAnimatedPreserveAspectRatio :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGAnimatedRect". -- -- newtype SVGAnimatedRect = SVGAnimatedRect { unSVGAnimatedRect :: JSVal } instance Eq (SVGAnimatedRect) where (SVGAnimatedRect a) == (SVGAnimatedRect b) = js_eq a b instance PToJSVal SVGAnimatedRect where pToJSVal = unSVGAnimatedRect {-# INLINE pToJSVal #-} instance PFromJSVal SVGAnimatedRect where pFromJSVal = SVGAnimatedRect {-# INLINE pFromJSVal #-} instance ToJSVal SVGAnimatedRect where toJSVal = return . unSVGAnimatedRect {-# INLINE toJSVal #-} instance FromJSVal SVGAnimatedRect where fromJSVal = return . fmap SVGAnimatedRect . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject SVGAnimatedRect where typeGType _ = gTypeSVGAnimatedRect {-# INLINE typeGType #-} noSVGAnimatedRect :: Maybe SVGAnimatedRect noSVGAnimatedRect = Nothing {-# INLINE noSVGAnimatedRect #-} foreign import javascript unsafe "window[\"SVGAnimatedRect\"]" gTypeSVGAnimatedRect :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGAnimatedString". -- -- newtype SVGAnimatedString = SVGAnimatedString { unSVGAnimatedString :: JSVal } instance Eq (SVGAnimatedString) where (SVGAnimatedString a) == (SVGAnimatedString b) = js_eq a b instance PToJSVal SVGAnimatedString where pToJSVal = unSVGAnimatedString {-# INLINE pToJSVal #-} instance PFromJSVal SVGAnimatedString where pFromJSVal = SVGAnimatedString {-# INLINE pFromJSVal #-} instance ToJSVal SVGAnimatedString where toJSVal = return . unSVGAnimatedString {-# INLINE toJSVal #-} instance FromJSVal SVGAnimatedString where fromJSVal = return . fmap SVGAnimatedString . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject SVGAnimatedString where typeGType _ = gTypeSVGAnimatedString {-# INLINE typeGType #-} noSVGAnimatedString :: Maybe SVGAnimatedString noSVGAnimatedString = Nothing {-# INLINE noSVGAnimatedString #-} foreign import javascript unsafe "window[\"SVGAnimatedString\"]" gTypeSVGAnimatedString :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGAnimatedTransformList". -- -- newtype SVGAnimatedTransformList = SVGAnimatedTransformList { unSVGAnimatedTransformList :: JSVal } instance Eq (SVGAnimatedTransformList) where (SVGAnimatedTransformList a) == (SVGAnimatedTransformList b) = js_eq a b instance PToJSVal SVGAnimatedTransformList where pToJSVal = unSVGAnimatedTransformList {-# INLINE pToJSVal #-} instance PFromJSVal SVGAnimatedTransformList where pFromJSVal = SVGAnimatedTransformList {-# INLINE pFromJSVal #-} instance ToJSVal SVGAnimatedTransformList where toJSVal = return . unSVGAnimatedTransformList {-# INLINE toJSVal #-} instance FromJSVal SVGAnimatedTransformList where fromJSVal = return . fmap SVGAnimatedTransformList . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject SVGAnimatedTransformList where typeGType _ = gTypeSVGAnimatedTransformList {-# INLINE typeGType #-} noSVGAnimatedTransformList :: Maybe SVGAnimatedTransformList noSVGAnimatedTransformList = Nothing {-# INLINE noSVGAnimatedTransformList #-} foreign import javascript unsafe "window[\"SVGAnimatedTransformList\"]" gTypeSVGAnimatedTransformList :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGAnimationElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- * "GHCJS.DOM.SVGTests" -- * "GHCJS.DOM.SVGExternalResourcesRequired" -- -- newtype SVGAnimationElement = SVGAnimationElement { unSVGAnimationElement :: JSVal } instance Eq (SVGAnimationElement) where (SVGAnimationElement a) == (SVGAnimationElement b) = js_eq a b instance PToJSVal SVGAnimationElement where pToJSVal = unSVGAnimationElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGAnimationElement where pFromJSVal = SVGAnimationElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGAnimationElement where toJSVal = return . unSVGAnimationElement {-# INLINE toJSVal #-} instance FromJSVal SVGAnimationElement where fromJSVal = return . fmap SVGAnimationElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsSVGElement o, IsElement o, IsNode o, IsEventTarget o, IsSlotable o, IsParentNode o, IsNonDocumentTypeChildNode o, IsDocumentAndElementEventHandlers o, IsChildNode o, IsAnimatable o, IsGlobalEventHandlers o, IsElementCSSInlineStyle o, IsSVGTests o, IsSVGExternalResourcesRequired o, IsGObject o) => IsSVGAnimationElement o toSVGAnimationElement :: IsSVGAnimationElement o => o -> SVGAnimationElement toSVGAnimationElement = SVGAnimationElement . coerce instance IsSVGAnimationElement SVGAnimationElement instance IsSVGElement SVGAnimationElement instance IsElement SVGAnimationElement instance IsNode SVGAnimationElement instance IsEventTarget SVGAnimationElement instance IsSlotable SVGAnimationElement instance IsParentNode SVGAnimationElement instance IsNonDocumentTypeChildNode SVGAnimationElement instance IsDocumentAndElementEventHandlers SVGAnimationElement instance IsChildNode SVGAnimationElement instance IsAnimatable SVGAnimationElement instance IsGlobalEventHandlers SVGAnimationElement instance IsElementCSSInlineStyle SVGAnimationElement instance IsSVGTests SVGAnimationElement instance IsSVGExternalResourcesRequired SVGAnimationElement instance IsGObject SVGAnimationElement where typeGType _ = gTypeSVGAnimationElement {-# INLINE typeGType #-} noSVGAnimationElement :: Maybe SVGAnimationElement noSVGAnimationElement = Nothing {-# INLINE noSVGAnimationElement #-} foreign import javascript unsafe "window[\"SVGAnimationElement\"]" gTypeSVGAnimationElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGCircleElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGGraphicsElement" -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- * "GHCJS.DOM.SVGTests" -- * "GHCJS.DOM.SVGExternalResourcesRequired" -- -- newtype SVGCircleElement = SVGCircleElement { unSVGCircleElement :: JSVal } instance Eq (SVGCircleElement) where (SVGCircleElement a) == (SVGCircleElement b) = js_eq a b instance PToJSVal SVGCircleElement where pToJSVal = unSVGCircleElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGCircleElement where pFromJSVal = SVGCircleElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGCircleElement where toJSVal = return . unSVGCircleElement {-# INLINE toJSVal #-} instance FromJSVal SVGCircleElement where fromJSVal = return . fmap SVGCircleElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGGraphicsElement SVGCircleElement instance IsSVGElement SVGCircleElement instance IsElement SVGCircleElement instance IsNode SVGCircleElement instance IsEventTarget SVGCircleElement instance IsSlotable SVGCircleElement instance IsParentNode SVGCircleElement instance IsNonDocumentTypeChildNode SVGCircleElement instance IsDocumentAndElementEventHandlers SVGCircleElement instance IsChildNode SVGCircleElement instance IsAnimatable SVGCircleElement instance IsGlobalEventHandlers SVGCircleElement instance IsElementCSSInlineStyle SVGCircleElement instance IsSVGTests SVGCircleElement instance IsSVGExternalResourcesRequired SVGCircleElement instance IsGObject SVGCircleElement where typeGType _ = gTypeSVGCircleElement {-# INLINE typeGType #-} noSVGCircleElement :: Maybe SVGCircleElement noSVGCircleElement = Nothing {-# INLINE noSVGCircleElement #-} foreign import javascript unsafe "window[\"SVGCircleElement\"]" gTypeSVGCircleElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGClipPathElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGGraphicsElement" -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- * "GHCJS.DOM.SVGTests" -- * "GHCJS.DOM.SVGExternalResourcesRequired" -- -- newtype SVGClipPathElement = SVGClipPathElement { unSVGClipPathElement :: JSVal } instance Eq (SVGClipPathElement) where (SVGClipPathElement a) == (SVGClipPathElement b) = js_eq a b instance PToJSVal SVGClipPathElement where pToJSVal = unSVGClipPathElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGClipPathElement where pFromJSVal = SVGClipPathElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGClipPathElement where toJSVal = return . unSVGClipPathElement {-# INLINE toJSVal #-} instance FromJSVal SVGClipPathElement where fromJSVal = return . fmap SVGClipPathElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGGraphicsElement SVGClipPathElement instance IsSVGElement SVGClipPathElement instance IsElement SVGClipPathElement instance IsNode SVGClipPathElement instance IsEventTarget SVGClipPathElement instance IsSlotable SVGClipPathElement instance IsParentNode SVGClipPathElement instance IsNonDocumentTypeChildNode SVGClipPathElement instance IsDocumentAndElementEventHandlers SVGClipPathElement instance IsChildNode SVGClipPathElement instance IsAnimatable SVGClipPathElement instance IsGlobalEventHandlers SVGClipPathElement instance IsElementCSSInlineStyle SVGClipPathElement instance IsSVGTests SVGClipPathElement instance IsSVGExternalResourcesRequired SVGClipPathElement instance IsGObject SVGClipPathElement where typeGType _ = gTypeSVGClipPathElement {-# INLINE typeGType #-} noSVGClipPathElement :: Maybe SVGClipPathElement noSVGClipPathElement = Nothing {-# INLINE noSVGClipPathElement #-} foreign import javascript unsafe "window[\"SVGClipPathElement\"]" gTypeSVGClipPathElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGComponentTransferFunctionElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype SVGComponentTransferFunctionElement = SVGComponentTransferFunctionElement { unSVGComponentTransferFunctionElement :: JSVal } instance Eq (SVGComponentTransferFunctionElement) where (SVGComponentTransferFunctionElement a) == (SVGComponentTransferFunctionElement b) = js_eq a b instance PToJSVal SVGComponentTransferFunctionElement where pToJSVal = unSVGComponentTransferFunctionElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGComponentTransferFunctionElement where pFromJSVal = SVGComponentTransferFunctionElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGComponentTransferFunctionElement where toJSVal = return . unSVGComponentTransferFunctionElement {-# INLINE toJSVal #-} instance FromJSVal SVGComponentTransferFunctionElement where fromJSVal = return . fmap SVGComponentTransferFunctionElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsSVGElement o, IsElement o, IsNode o, IsEventTarget o, IsSlotable o, IsParentNode o, IsNonDocumentTypeChildNode o, IsDocumentAndElementEventHandlers o, IsChildNode o, IsAnimatable o, IsGlobalEventHandlers o, IsElementCSSInlineStyle o, IsGObject o) => IsSVGComponentTransferFunctionElement o toSVGComponentTransferFunctionElement :: IsSVGComponentTransferFunctionElement o => o -> SVGComponentTransferFunctionElement toSVGComponentTransferFunctionElement = SVGComponentTransferFunctionElement . coerce instance IsSVGComponentTransferFunctionElement SVGComponentTransferFunctionElement instance IsSVGElement SVGComponentTransferFunctionElement instance IsElement SVGComponentTransferFunctionElement instance IsNode SVGComponentTransferFunctionElement instance IsEventTarget SVGComponentTransferFunctionElement instance IsSlotable SVGComponentTransferFunctionElement instance IsParentNode SVGComponentTransferFunctionElement instance IsNonDocumentTypeChildNode SVGComponentTransferFunctionElement instance IsDocumentAndElementEventHandlers SVGComponentTransferFunctionElement instance IsChildNode SVGComponentTransferFunctionElement instance IsAnimatable SVGComponentTransferFunctionElement instance IsGlobalEventHandlers SVGComponentTransferFunctionElement instance IsElementCSSInlineStyle SVGComponentTransferFunctionElement instance IsGObject SVGComponentTransferFunctionElement where typeGType _ = gTypeSVGComponentTransferFunctionElement {-# INLINE typeGType #-} noSVGComponentTransferFunctionElement :: Maybe SVGComponentTransferFunctionElement noSVGComponentTransferFunctionElement = Nothing {-# INLINE noSVGComponentTransferFunctionElement #-} foreign import javascript unsafe "window[\"SVGComponentTransferFunctionElement\"]" gTypeSVGComponentTransferFunctionElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGCursorElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- * "GHCJS.DOM.SVGURIReference" -- * "GHCJS.DOM.SVGTests" -- * "GHCJS.DOM.SVGExternalResourcesRequired" -- -- newtype SVGCursorElement = SVGCursorElement { unSVGCursorElement :: JSVal } instance Eq (SVGCursorElement) where (SVGCursorElement a) == (SVGCursorElement b) = js_eq a b instance PToJSVal SVGCursorElement where pToJSVal = unSVGCursorElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGCursorElement where pFromJSVal = SVGCursorElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGCursorElement where toJSVal = return . unSVGCursorElement {-# INLINE toJSVal #-} instance FromJSVal SVGCursorElement where fromJSVal = return . fmap SVGCursorElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGElement SVGCursorElement instance IsElement SVGCursorElement instance IsNode SVGCursorElement instance IsEventTarget SVGCursorElement instance IsSlotable SVGCursorElement instance IsParentNode SVGCursorElement instance IsNonDocumentTypeChildNode SVGCursorElement instance IsDocumentAndElementEventHandlers SVGCursorElement instance IsChildNode SVGCursorElement instance IsAnimatable SVGCursorElement instance IsGlobalEventHandlers SVGCursorElement instance IsElementCSSInlineStyle SVGCursorElement instance IsSVGURIReference SVGCursorElement instance IsSVGTests SVGCursorElement instance IsSVGExternalResourcesRequired SVGCursorElement instance IsGObject SVGCursorElement where typeGType _ = gTypeSVGCursorElement {-# INLINE typeGType #-} noSVGCursorElement :: Maybe SVGCursorElement noSVGCursorElement = Nothing {-# INLINE noSVGCursorElement #-} foreign import javascript unsafe "window[\"SVGCursorElement\"]" gTypeSVGCursorElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGDefsElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGGraphicsElement" -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- * "GHCJS.DOM.SVGTests" -- * "GHCJS.DOM.SVGExternalResourcesRequired" -- -- newtype SVGDefsElement = SVGDefsElement { unSVGDefsElement :: JSVal } instance Eq (SVGDefsElement) where (SVGDefsElement a) == (SVGDefsElement b) = js_eq a b instance PToJSVal SVGDefsElement where pToJSVal = unSVGDefsElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGDefsElement where pFromJSVal = SVGDefsElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGDefsElement where toJSVal = return . unSVGDefsElement {-# INLINE toJSVal #-} instance FromJSVal SVGDefsElement where fromJSVal = return . fmap SVGDefsElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGGraphicsElement SVGDefsElement instance IsSVGElement SVGDefsElement instance IsElement SVGDefsElement instance IsNode SVGDefsElement instance IsEventTarget SVGDefsElement instance IsSlotable SVGDefsElement instance IsParentNode SVGDefsElement instance IsNonDocumentTypeChildNode SVGDefsElement instance IsDocumentAndElementEventHandlers SVGDefsElement instance IsChildNode SVGDefsElement instance IsAnimatable SVGDefsElement instance IsGlobalEventHandlers SVGDefsElement instance IsElementCSSInlineStyle SVGDefsElement instance IsSVGTests SVGDefsElement instance IsSVGExternalResourcesRequired SVGDefsElement instance IsGObject SVGDefsElement where typeGType _ = gTypeSVGDefsElement {-# INLINE typeGType #-} noSVGDefsElement :: Maybe SVGDefsElement noSVGDefsElement = Nothing {-# INLINE noSVGDefsElement #-} foreign import javascript unsafe "window[\"SVGDefsElement\"]" gTypeSVGDefsElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGDescElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype SVGDescElement = SVGDescElement { unSVGDescElement :: JSVal } instance Eq (SVGDescElement) where (SVGDescElement a) == (SVGDescElement b) = js_eq a b instance PToJSVal SVGDescElement where pToJSVal = unSVGDescElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGDescElement where pFromJSVal = SVGDescElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGDescElement where toJSVal = return . unSVGDescElement {-# INLINE toJSVal #-} instance FromJSVal SVGDescElement where fromJSVal = return . fmap SVGDescElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGElement SVGDescElement instance IsElement SVGDescElement instance IsNode SVGDescElement instance IsEventTarget SVGDescElement instance IsSlotable SVGDescElement instance IsParentNode SVGDescElement instance IsNonDocumentTypeChildNode SVGDescElement instance IsDocumentAndElementEventHandlers SVGDescElement instance IsChildNode SVGDescElement instance IsAnimatable SVGDescElement instance IsGlobalEventHandlers SVGDescElement instance IsElementCSSInlineStyle SVGDescElement instance IsGObject SVGDescElement where typeGType _ = gTypeSVGDescElement {-# INLINE typeGType #-} noSVGDescElement :: Maybe SVGDescElement noSVGDescElement = Nothing {-# INLINE noSVGDescElement #-} foreign import javascript unsafe "window[\"SVGDescElement\"]" gTypeSVGDescElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype SVGElement = SVGElement { unSVGElement :: JSVal } instance Eq (SVGElement) where (SVGElement a) == (SVGElement b) = js_eq a b instance PToJSVal SVGElement where pToJSVal = unSVGElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGElement where pFromJSVal = SVGElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGElement where toJSVal = return . unSVGElement {-# INLINE toJSVal #-} instance FromJSVal SVGElement where fromJSVal = return . fmap SVGElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsElement o, IsNode o, IsEventTarget o, IsSlotable o, IsParentNode o, IsNonDocumentTypeChildNode o, IsDocumentAndElementEventHandlers o, IsChildNode o, IsAnimatable o, IsGlobalEventHandlers o, IsElementCSSInlineStyle o, IsGObject o) => IsSVGElement o toSVGElement :: IsSVGElement o => o -> SVGElement toSVGElement = SVGElement . coerce instance IsSVGElement SVGElement instance IsElement SVGElement instance IsNode SVGElement instance IsEventTarget SVGElement instance IsSlotable SVGElement instance IsParentNode SVGElement instance IsNonDocumentTypeChildNode SVGElement instance IsDocumentAndElementEventHandlers SVGElement instance IsChildNode SVGElement instance IsAnimatable SVGElement instance IsGlobalEventHandlers SVGElement instance IsElementCSSInlineStyle SVGElement instance IsGObject SVGElement where typeGType _ = gTypeSVGElement {-# INLINE typeGType #-} noSVGElement :: Maybe SVGElement noSVGElement = Nothing {-# INLINE noSVGElement #-} foreign import javascript unsafe "window[\"SVGElement\"]" gTypeSVGElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGEllipseElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGGraphicsElement" -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- * "GHCJS.DOM.SVGTests" -- * "GHCJS.DOM.SVGExternalResourcesRequired" -- -- newtype SVGEllipseElement = SVGEllipseElement { unSVGEllipseElement :: JSVal } instance Eq (SVGEllipseElement) where (SVGEllipseElement a) == (SVGEllipseElement b) = js_eq a b instance PToJSVal SVGEllipseElement where pToJSVal = unSVGEllipseElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGEllipseElement where pFromJSVal = SVGEllipseElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGEllipseElement where toJSVal = return . unSVGEllipseElement {-# INLINE toJSVal #-} instance FromJSVal SVGEllipseElement where fromJSVal = return . fmap SVGEllipseElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGGraphicsElement SVGEllipseElement instance IsSVGElement SVGEllipseElement instance IsElement SVGEllipseElement instance IsNode SVGEllipseElement instance IsEventTarget SVGEllipseElement instance IsSlotable SVGEllipseElement instance IsParentNode SVGEllipseElement instance IsNonDocumentTypeChildNode SVGEllipseElement instance IsDocumentAndElementEventHandlers SVGEllipseElement instance IsChildNode SVGEllipseElement instance IsAnimatable SVGEllipseElement instance IsGlobalEventHandlers SVGEllipseElement instance IsElementCSSInlineStyle SVGEllipseElement instance IsSVGTests SVGEllipseElement instance IsSVGExternalResourcesRequired SVGEllipseElement instance IsGObject SVGEllipseElement where typeGType _ = gTypeSVGEllipseElement {-# INLINE typeGType #-} noSVGEllipseElement :: Maybe SVGEllipseElement noSVGEllipseElement = Nothing {-# INLINE noSVGEllipseElement #-} foreign import javascript unsafe "window[\"SVGEllipseElement\"]" gTypeSVGEllipseElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGException". -- -- newtype SVGException = SVGException { unSVGException :: JSVal } instance Eq (SVGException) where (SVGException a) == (SVGException b) = js_eq a b instance PToJSVal SVGException where pToJSVal = unSVGException {-# INLINE pToJSVal #-} instance PFromJSVal SVGException where pFromJSVal = SVGException {-# INLINE pFromJSVal #-} instance ToJSVal SVGException where toJSVal = return . unSVGException {-# INLINE toJSVal #-} instance FromJSVal SVGException where fromJSVal = return . fmap SVGException . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject SVGException where typeGType _ = gTypeSVGException {-# INLINE typeGType #-} noSVGException :: Maybe SVGException noSVGException = Nothing {-# INLINE noSVGException #-} foreign import javascript unsafe "window[\"SVGException\"]" gTypeSVGException :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGExternalResourcesRequired". -- -- newtype SVGExternalResourcesRequired = SVGExternalResourcesRequired { unSVGExternalResourcesRequired :: JSVal } instance Eq (SVGExternalResourcesRequired) where (SVGExternalResourcesRequired a) == (SVGExternalResourcesRequired b) = js_eq a b instance PToJSVal SVGExternalResourcesRequired where pToJSVal = unSVGExternalResourcesRequired {-# INLINE pToJSVal #-} instance PFromJSVal SVGExternalResourcesRequired where pFromJSVal = SVGExternalResourcesRequired {-# INLINE pFromJSVal #-} instance ToJSVal SVGExternalResourcesRequired where toJSVal = return . unSVGExternalResourcesRequired {-# INLINE toJSVal #-} instance FromJSVal SVGExternalResourcesRequired where fromJSVal = return . fmap SVGExternalResourcesRequired . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsGObject o) => IsSVGExternalResourcesRequired o toSVGExternalResourcesRequired :: IsSVGExternalResourcesRequired o => o -> SVGExternalResourcesRequired toSVGExternalResourcesRequired = SVGExternalResourcesRequired . coerce instance IsSVGExternalResourcesRequired SVGExternalResourcesRequired instance IsGObject SVGExternalResourcesRequired where typeGType _ = gTypeSVGExternalResourcesRequired {-# INLINE typeGType #-} noSVGExternalResourcesRequired :: Maybe SVGExternalResourcesRequired noSVGExternalResourcesRequired = Nothing {-# INLINE noSVGExternalResourcesRequired #-} foreign import javascript unsafe "window[\"SVGExternalResourcesRequired\"]" gTypeSVGExternalResourcesRequired :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGFEBlendElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- * "GHCJS.DOM.SVGFilterPrimitiveStandardAttributes" -- -- newtype SVGFEBlendElement = SVGFEBlendElement { unSVGFEBlendElement :: JSVal } instance Eq (SVGFEBlendElement) where (SVGFEBlendElement a) == (SVGFEBlendElement b) = js_eq a b instance PToJSVal SVGFEBlendElement where pToJSVal = unSVGFEBlendElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGFEBlendElement where pFromJSVal = SVGFEBlendElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGFEBlendElement where toJSVal = return . unSVGFEBlendElement {-# INLINE toJSVal #-} instance FromJSVal SVGFEBlendElement where fromJSVal = return . fmap SVGFEBlendElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGElement SVGFEBlendElement instance IsElement SVGFEBlendElement instance IsNode SVGFEBlendElement instance IsEventTarget SVGFEBlendElement instance IsSlotable SVGFEBlendElement instance IsParentNode SVGFEBlendElement instance IsNonDocumentTypeChildNode SVGFEBlendElement instance IsDocumentAndElementEventHandlers SVGFEBlendElement instance IsChildNode SVGFEBlendElement instance IsAnimatable SVGFEBlendElement instance IsGlobalEventHandlers SVGFEBlendElement instance IsElementCSSInlineStyle SVGFEBlendElement instance IsSVGFilterPrimitiveStandardAttributes SVGFEBlendElement instance IsGObject SVGFEBlendElement where typeGType _ = gTypeSVGFEBlendElement {-# INLINE typeGType #-} noSVGFEBlendElement :: Maybe SVGFEBlendElement noSVGFEBlendElement = Nothing {-# INLINE noSVGFEBlendElement #-} foreign import javascript unsafe "window[\"SVGFEBlendElement\"]" gTypeSVGFEBlendElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGFEColorMatrixElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- * "GHCJS.DOM.SVGFilterPrimitiveStandardAttributes" -- -- newtype SVGFEColorMatrixElement = SVGFEColorMatrixElement { unSVGFEColorMatrixElement :: JSVal } instance Eq (SVGFEColorMatrixElement) where (SVGFEColorMatrixElement a) == (SVGFEColorMatrixElement b) = js_eq a b instance PToJSVal SVGFEColorMatrixElement where pToJSVal = unSVGFEColorMatrixElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGFEColorMatrixElement where pFromJSVal = SVGFEColorMatrixElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGFEColorMatrixElement where toJSVal = return . unSVGFEColorMatrixElement {-# INLINE toJSVal #-} instance FromJSVal SVGFEColorMatrixElement where fromJSVal = return . fmap SVGFEColorMatrixElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGElement SVGFEColorMatrixElement instance IsElement SVGFEColorMatrixElement instance IsNode SVGFEColorMatrixElement instance IsEventTarget SVGFEColorMatrixElement instance IsSlotable SVGFEColorMatrixElement instance IsParentNode SVGFEColorMatrixElement instance IsNonDocumentTypeChildNode SVGFEColorMatrixElement instance IsDocumentAndElementEventHandlers SVGFEColorMatrixElement instance IsChildNode SVGFEColorMatrixElement instance IsAnimatable SVGFEColorMatrixElement instance IsGlobalEventHandlers SVGFEColorMatrixElement instance IsElementCSSInlineStyle SVGFEColorMatrixElement instance IsSVGFilterPrimitiveStandardAttributes SVGFEColorMatrixElement instance IsGObject SVGFEColorMatrixElement where typeGType _ = gTypeSVGFEColorMatrixElement {-# INLINE typeGType #-} noSVGFEColorMatrixElement :: Maybe SVGFEColorMatrixElement noSVGFEColorMatrixElement = Nothing {-# INLINE noSVGFEColorMatrixElement #-} foreign import javascript unsafe "window[\"SVGFEColorMatrixElement\"]" gTypeSVGFEColorMatrixElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGFEComponentTransferElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- * "GHCJS.DOM.SVGFilterPrimitiveStandardAttributes" -- -- newtype SVGFEComponentTransferElement = SVGFEComponentTransferElement { unSVGFEComponentTransferElement :: JSVal } instance Eq (SVGFEComponentTransferElement) where (SVGFEComponentTransferElement a) == (SVGFEComponentTransferElement b) = js_eq a b instance PToJSVal SVGFEComponentTransferElement where pToJSVal = unSVGFEComponentTransferElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGFEComponentTransferElement where pFromJSVal = SVGFEComponentTransferElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGFEComponentTransferElement where toJSVal = return . unSVGFEComponentTransferElement {-# INLINE toJSVal #-} instance FromJSVal SVGFEComponentTransferElement where fromJSVal = return . fmap SVGFEComponentTransferElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGElement SVGFEComponentTransferElement instance IsElement SVGFEComponentTransferElement instance IsNode SVGFEComponentTransferElement instance IsEventTarget SVGFEComponentTransferElement instance IsSlotable SVGFEComponentTransferElement instance IsParentNode SVGFEComponentTransferElement instance IsNonDocumentTypeChildNode SVGFEComponentTransferElement instance IsDocumentAndElementEventHandlers SVGFEComponentTransferElement instance IsChildNode SVGFEComponentTransferElement instance IsAnimatable SVGFEComponentTransferElement instance IsGlobalEventHandlers SVGFEComponentTransferElement instance IsElementCSSInlineStyle SVGFEComponentTransferElement instance IsSVGFilterPrimitiveStandardAttributes SVGFEComponentTransferElement instance IsGObject SVGFEComponentTransferElement where typeGType _ = gTypeSVGFEComponentTransferElement {-# INLINE typeGType #-} noSVGFEComponentTransferElement :: Maybe SVGFEComponentTransferElement noSVGFEComponentTransferElement = Nothing {-# INLINE noSVGFEComponentTransferElement #-} foreign import javascript unsafe "window[\"SVGFEComponentTransferElement\"]" gTypeSVGFEComponentTransferElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGFECompositeElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- * "GHCJS.DOM.SVGFilterPrimitiveStandardAttributes" -- -- newtype SVGFECompositeElement = SVGFECompositeElement { unSVGFECompositeElement :: JSVal } instance Eq (SVGFECompositeElement) where (SVGFECompositeElement a) == (SVGFECompositeElement b) = js_eq a b instance PToJSVal SVGFECompositeElement where pToJSVal = unSVGFECompositeElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGFECompositeElement where pFromJSVal = SVGFECompositeElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGFECompositeElement where toJSVal = return . unSVGFECompositeElement {-# INLINE toJSVal #-} instance FromJSVal SVGFECompositeElement where fromJSVal = return . fmap SVGFECompositeElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGElement SVGFECompositeElement instance IsElement SVGFECompositeElement instance IsNode SVGFECompositeElement instance IsEventTarget SVGFECompositeElement instance IsSlotable SVGFECompositeElement instance IsParentNode SVGFECompositeElement instance IsNonDocumentTypeChildNode SVGFECompositeElement instance IsDocumentAndElementEventHandlers SVGFECompositeElement instance IsChildNode SVGFECompositeElement instance IsAnimatable SVGFECompositeElement instance IsGlobalEventHandlers SVGFECompositeElement instance IsElementCSSInlineStyle SVGFECompositeElement instance IsSVGFilterPrimitiveStandardAttributes SVGFECompositeElement instance IsGObject SVGFECompositeElement where typeGType _ = gTypeSVGFECompositeElement {-# INLINE typeGType #-} noSVGFECompositeElement :: Maybe SVGFECompositeElement noSVGFECompositeElement = Nothing {-# INLINE noSVGFECompositeElement #-} foreign import javascript unsafe "window[\"SVGFECompositeElement\"]" gTypeSVGFECompositeElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGFEConvolveMatrixElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- * "GHCJS.DOM.SVGFilterPrimitiveStandardAttributes" -- -- newtype SVGFEConvolveMatrixElement = SVGFEConvolveMatrixElement { unSVGFEConvolveMatrixElement :: JSVal } instance Eq (SVGFEConvolveMatrixElement) where (SVGFEConvolveMatrixElement a) == (SVGFEConvolveMatrixElement b) = js_eq a b instance PToJSVal SVGFEConvolveMatrixElement where pToJSVal = unSVGFEConvolveMatrixElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGFEConvolveMatrixElement where pFromJSVal = SVGFEConvolveMatrixElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGFEConvolveMatrixElement where toJSVal = return . unSVGFEConvolveMatrixElement {-# INLINE toJSVal #-} instance FromJSVal SVGFEConvolveMatrixElement where fromJSVal = return . fmap SVGFEConvolveMatrixElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGElement SVGFEConvolveMatrixElement instance IsElement SVGFEConvolveMatrixElement instance IsNode SVGFEConvolveMatrixElement instance IsEventTarget SVGFEConvolveMatrixElement instance IsSlotable SVGFEConvolveMatrixElement instance IsParentNode SVGFEConvolveMatrixElement instance IsNonDocumentTypeChildNode SVGFEConvolveMatrixElement instance IsDocumentAndElementEventHandlers SVGFEConvolveMatrixElement instance IsChildNode SVGFEConvolveMatrixElement instance IsAnimatable SVGFEConvolveMatrixElement instance IsGlobalEventHandlers SVGFEConvolveMatrixElement instance IsElementCSSInlineStyle SVGFEConvolveMatrixElement instance IsSVGFilterPrimitiveStandardAttributes SVGFEConvolveMatrixElement instance IsGObject SVGFEConvolveMatrixElement where typeGType _ = gTypeSVGFEConvolveMatrixElement {-# INLINE typeGType #-} noSVGFEConvolveMatrixElement :: Maybe SVGFEConvolveMatrixElement noSVGFEConvolveMatrixElement = Nothing {-# INLINE noSVGFEConvolveMatrixElement #-} foreign import javascript unsafe "window[\"SVGFEConvolveMatrixElement\"]" gTypeSVGFEConvolveMatrixElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGFEDiffuseLightingElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- * "GHCJS.DOM.SVGFilterPrimitiveStandardAttributes" -- -- newtype SVGFEDiffuseLightingElement = SVGFEDiffuseLightingElement { unSVGFEDiffuseLightingElement :: JSVal } instance Eq (SVGFEDiffuseLightingElement) where (SVGFEDiffuseLightingElement a) == (SVGFEDiffuseLightingElement b) = js_eq a b instance PToJSVal SVGFEDiffuseLightingElement where pToJSVal = unSVGFEDiffuseLightingElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGFEDiffuseLightingElement where pFromJSVal = SVGFEDiffuseLightingElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGFEDiffuseLightingElement where toJSVal = return . unSVGFEDiffuseLightingElement {-# INLINE toJSVal #-} instance FromJSVal SVGFEDiffuseLightingElement where fromJSVal = return . fmap SVGFEDiffuseLightingElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGElement SVGFEDiffuseLightingElement instance IsElement SVGFEDiffuseLightingElement instance IsNode SVGFEDiffuseLightingElement instance IsEventTarget SVGFEDiffuseLightingElement instance IsSlotable SVGFEDiffuseLightingElement instance IsParentNode SVGFEDiffuseLightingElement instance IsNonDocumentTypeChildNode SVGFEDiffuseLightingElement instance IsDocumentAndElementEventHandlers SVGFEDiffuseLightingElement instance IsChildNode SVGFEDiffuseLightingElement instance IsAnimatable SVGFEDiffuseLightingElement instance IsGlobalEventHandlers SVGFEDiffuseLightingElement instance IsElementCSSInlineStyle SVGFEDiffuseLightingElement instance IsSVGFilterPrimitiveStandardAttributes SVGFEDiffuseLightingElement instance IsGObject SVGFEDiffuseLightingElement where typeGType _ = gTypeSVGFEDiffuseLightingElement {-# INLINE typeGType #-} noSVGFEDiffuseLightingElement :: Maybe SVGFEDiffuseLightingElement noSVGFEDiffuseLightingElement = Nothing {-# INLINE noSVGFEDiffuseLightingElement #-} foreign import javascript unsafe "window[\"SVGFEDiffuseLightingElement\"]" gTypeSVGFEDiffuseLightingElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGFEDisplacementMapElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- * "GHCJS.DOM.SVGFilterPrimitiveStandardAttributes" -- -- newtype SVGFEDisplacementMapElement = SVGFEDisplacementMapElement { unSVGFEDisplacementMapElement :: JSVal } instance Eq (SVGFEDisplacementMapElement) where (SVGFEDisplacementMapElement a) == (SVGFEDisplacementMapElement b) = js_eq a b instance PToJSVal SVGFEDisplacementMapElement where pToJSVal = unSVGFEDisplacementMapElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGFEDisplacementMapElement where pFromJSVal = SVGFEDisplacementMapElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGFEDisplacementMapElement where toJSVal = return . unSVGFEDisplacementMapElement {-# INLINE toJSVal #-} instance FromJSVal SVGFEDisplacementMapElement where fromJSVal = return . fmap SVGFEDisplacementMapElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGElement SVGFEDisplacementMapElement instance IsElement SVGFEDisplacementMapElement instance IsNode SVGFEDisplacementMapElement instance IsEventTarget SVGFEDisplacementMapElement instance IsSlotable SVGFEDisplacementMapElement instance IsParentNode SVGFEDisplacementMapElement instance IsNonDocumentTypeChildNode SVGFEDisplacementMapElement instance IsDocumentAndElementEventHandlers SVGFEDisplacementMapElement instance IsChildNode SVGFEDisplacementMapElement instance IsAnimatable SVGFEDisplacementMapElement instance IsGlobalEventHandlers SVGFEDisplacementMapElement instance IsElementCSSInlineStyle SVGFEDisplacementMapElement instance IsSVGFilterPrimitiveStandardAttributes SVGFEDisplacementMapElement instance IsGObject SVGFEDisplacementMapElement where typeGType _ = gTypeSVGFEDisplacementMapElement {-# INLINE typeGType #-} noSVGFEDisplacementMapElement :: Maybe SVGFEDisplacementMapElement noSVGFEDisplacementMapElement = Nothing {-# INLINE noSVGFEDisplacementMapElement #-} foreign import javascript unsafe "window[\"SVGFEDisplacementMapElement\"]" gTypeSVGFEDisplacementMapElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGFEDistantLightElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype SVGFEDistantLightElement = SVGFEDistantLightElement { unSVGFEDistantLightElement :: JSVal } instance Eq (SVGFEDistantLightElement) where (SVGFEDistantLightElement a) == (SVGFEDistantLightElement b) = js_eq a b instance PToJSVal SVGFEDistantLightElement where pToJSVal = unSVGFEDistantLightElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGFEDistantLightElement where pFromJSVal = SVGFEDistantLightElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGFEDistantLightElement where toJSVal = return . unSVGFEDistantLightElement {-# INLINE toJSVal #-} instance FromJSVal SVGFEDistantLightElement where fromJSVal = return . fmap SVGFEDistantLightElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGElement SVGFEDistantLightElement instance IsElement SVGFEDistantLightElement instance IsNode SVGFEDistantLightElement instance IsEventTarget SVGFEDistantLightElement instance IsSlotable SVGFEDistantLightElement instance IsParentNode SVGFEDistantLightElement instance IsNonDocumentTypeChildNode SVGFEDistantLightElement instance IsDocumentAndElementEventHandlers SVGFEDistantLightElement instance IsChildNode SVGFEDistantLightElement instance IsAnimatable SVGFEDistantLightElement instance IsGlobalEventHandlers SVGFEDistantLightElement instance IsElementCSSInlineStyle SVGFEDistantLightElement instance IsGObject SVGFEDistantLightElement where typeGType _ = gTypeSVGFEDistantLightElement {-# INLINE typeGType #-} noSVGFEDistantLightElement :: Maybe SVGFEDistantLightElement noSVGFEDistantLightElement = Nothing {-# INLINE noSVGFEDistantLightElement #-} foreign import javascript unsafe "window[\"SVGFEDistantLightElement\"]" gTypeSVGFEDistantLightElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGFEDropShadowElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- * "GHCJS.DOM.SVGFilterPrimitiveStandardAttributes" -- -- newtype SVGFEDropShadowElement = SVGFEDropShadowElement { unSVGFEDropShadowElement :: JSVal } instance Eq (SVGFEDropShadowElement) where (SVGFEDropShadowElement a) == (SVGFEDropShadowElement b) = js_eq a b instance PToJSVal SVGFEDropShadowElement where pToJSVal = unSVGFEDropShadowElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGFEDropShadowElement where pFromJSVal = SVGFEDropShadowElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGFEDropShadowElement where toJSVal = return . unSVGFEDropShadowElement {-# INLINE toJSVal #-} instance FromJSVal SVGFEDropShadowElement where fromJSVal = return . fmap SVGFEDropShadowElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGElement SVGFEDropShadowElement instance IsElement SVGFEDropShadowElement instance IsNode SVGFEDropShadowElement instance IsEventTarget SVGFEDropShadowElement instance IsSlotable SVGFEDropShadowElement instance IsParentNode SVGFEDropShadowElement instance IsNonDocumentTypeChildNode SVGFEDropShadowElement instance IsDocumentAndElementEventHandlers SVGFEDropShadowElement instance IsChildNode SVGFEDropShadowElement instance IsAnimatable SVGFEDropShadowElement instance IsGlobalEventHandlers SVGFEDropShadowElement instance IsElementCSSInlineStyle SVGFEDropShadowElement instance IsSVGFilterPrimitiveStandardAttributes SVGFEDropShadowElement instance IsGObject SVGFEDropShadowElement where typeGType _ = gTypeSVGFEDropShadowElement {-# INLINE typeGType #-} noSVGFEDropShadowElement :: Maybe SVGFEDropShadowElement noSVGFEDropShadowElement = Nothing {-# INLINE noSVGFEDropShadowElement #-} foreign import javascript unsafe "window[\"SVGFEDropShadowElement\"]" gTypeSVGFEDropShadowElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGFEFloodElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- * "GHCJS.DOM.SVGFilterPrimitiveStandardAttributes" -- -- newtype SVGFEFloodElement = SVGFEFloodElement { unSVGFEFloodElement :: JSVal } instance Eq (SVGFEFloodElement) where (SVGFEFloodElement a) == (SVGFEFloodElement b) = js_eq a b instance PToJSVal SVGFEFloodElement where pToJSVal = unSVGFEFloodElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGFEFloodElement where pFromJSVal = SVGFEFloodElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGFEFloodElement where toJSVal = return . unSVGFEFloodElement {-# INLINE toJSVal #-} instance FromJSVal SVGFEFloodElement where fromJSVal = return . fmap SVGFEFloodElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGElement SVGFEFloodElement instance IsElement SVGFEFloodElement instance IsNode SVGFEFloodElement instance IsEventTarget SVGFEFloodElement instance IsSlotable SVGFEFloodElement instance IsParentNode SVGFEFloodElement instance IsNonDocumentTypeChildNode SVGFEFloodElement instance IsDocumentAndElementEventHandlers SVGFEFloodElement instance IsChildNode SVGFEFloodElement instance IsAnimatable SVGFEFloodElement instance IsGlobalEventHandlers SVGFEFloodElement instance IsElementCSSInlineStyle SVGFEFloodElement instance IsSVGFilterPrimitiveStandardAttributes SVGFEFloodElement instance IsGObject SVGFEFloodElement where typeGType _ = gTypeSVGFEFloodElement {-# INLINE typeGType #-} noSVGFEFloodElement :: Maybe SVGFEFloodElement noSVGFEFloodElement = Nothing {-# INLINE noSVGFEFloodElement #-} foreign import javascript unsafe "window[\"SVGFEFloodElement\"]" gTypeSVGFEFloodElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGFEFuncAElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGComponentTransferFunctionElement" -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype SVGFEFuncAElement = SVGFEFuncAElement { unSVGFEFuncAElement :: JSVal } instance Eq (SVGFEFuncAElement) where (SVGFEFuncAElement a) == (SVGFEFuncAElement b) = js_eq a b instance PToJSVal SVGFEFuncAElement where pToJSVal = unSVGFEFuncAElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGFEFuncAElement where pFromJSVal = SVGFEFuncAElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGFEFuncAElement where toJSVal = return . unSVGFEFuncAElement {-# INLINE toJSVal #-} instance FromJSVal SVGFEFuncAElement where fromJSVal = return . fmap SVGFEFuncAElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGComponentTransferFunctionElement SVGFEFuncAElement instance IsSVGElement SVGFEFuncAElement instance IsElement SVGFEFuncAElement instance IsNode SVGFEFuncAElement instance IsEventTarget SVGFEFuncAElement instance IsSlotable SVGFEFuncAElement instance IsParentNode SVGFEFuncAElement instance IsNonDocumentTypeChildNode SVGFEFuncAElement instance IsDocumentAndElementEventHandlers SVGFEFuncAElement instance IsChildNode SVGFEFuncAElement instance IsAnimatable SVGFEFuncAElement instance IsGlobalEventHandlers SVGFEFuncAElement instance IsElementCSSInlineStyle SVGFEFuncAElement instance IsGObject SVGFEFuncAElement where typeGType _ = gTypeSVGFEFuncAElement {-# INLINE typeGType #-} noSVGFEFuncAElement :: Maybe SVGFEFuncAElement noSVGFEFuncAElement = Nothing {-# INLINE noSVGFEFuncAElement #-} foreign import javascript unsafe "window[\"SVGFEFuncAElement\"]" gTypeSVGFEFuncAElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGFEFuncBElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGComponentTransferFunctionElement" -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype SVGFEFuncBElement = SVGFEFuncBElement { unSVGFEFuncBElement :: JSVal } instance Eq (SVGFEFuncBElement) where (SVGFEFuncBElement a) == (SVGFEFuncBElement b) = js_eq a b instance PToJSVal SVGFEFuncBElement where pToJSVal = unSVGFEFuncBElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGFEFuncBElement where pFromJSVal = SVGFEFuncBElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGFEFuncBElement where toJSVal = return . unSVGFEFuncBElement {-# INLINE toJSVal #-} instance FromJSVal SVGFEFuncBElement where fromJSVal = return . fmap SVGFEFuncBElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGComponentTransferFunctionElement SVGFEFuncBElement instance IsSVGElement SVGFEFuncBElement instance IsElement SVGFEFuncBElement instance IsNode SVGFEFuncBElement instance IsEventTarget SVGFEFuncBElement instance IsSlotable SVGFEFuncBElement instance IsParentNode SVGFEFuncBElement instance IsNonDocumentTypeChildNode SVGFEFuncBElement instance IsDocumentAndElementEventHandlers SVGFEFuncBElement instance IsChildNode SVGFEFuncBElement instance IsAnimatable SVGFEFuncBElement instance IsGlobalEventHandlers SVGFEFuncBElement instance IsElementCSSInlineStyle SVGFEFuncBElement instance IsGObject SVGFEFuncBElement where typeGType _ = gTypeSVGFEFuncBElement {-# INLINE typeGType #-} noSVGFEFuncBElement :: Maybe SVGFEFuncBElement noSVGFEFuncBElement = Nothing {-# INLINE noSVGFEFuncBElement #-} foreign import javascript unsafe "window[\"SVGFEFuncBElement\"]" gTypeSVGFEFuncBElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGFEFuncGElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGComponentTransferFunctionElement" -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype SVGFEFuncGElement = SVGFEFuncGElement { unSVGFEFuncGElement :: JSVal } instance Eq (SVGFEFuncGElement) where (SVGFEFuncGElement a) == (SVGFEFuncGElement b) = js_eq a b instance PToJSVal SVGFEFuncGElement where pToJSVal = unSVGFEFuncGElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGFEFuncGElement where pFromJSVal = SVGFEFuncGElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGFEFuncGElement where toJSVal = return . unSVGFEFuncGElement {-# INLINE toJSVal #-} instance FromJSVal SVGFEFuncGElement where fromJSVal = return . fmap SVGFEFuncGElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGComponentTransferFunctionElement SVGFEFuncGElement instance IsSVGElement SVGFEFuncGElement instance IsElement SVGFEFuncGElement instance IsNode SVGFEFuncGElement instance IsEventTarget SVGFEFuncGElement instance IsSlotable SVGFEFuncGElement instance IsParentNode SVGFEFuncGElement instance IsNonDocumentTypeChildNode SVGFEFuncGElement instance IsDocumentAndElementEventHandlers SVGFEFuncGElement instance IsChildNode SVGFEFuncGElement instance IsAnimatable SVGFEFuncGElement instance IsGlobalEventHandlers SVGFEFuncGElement instance IsElementCSSInlineStyle SVGFEFuncGElement instance IsGObject SVGFEFuncGElement where typeGType _ = gTypeSVGFEFuncGElement {-# INLINE typeGType #-} noSVGFEFuncGElement :: Maybe SVGFEFuncGElement noSVGFEFuncGElement = Nothing {-# INLINE noSVGFEFuncGElement #-} foreign import javascript unsafe "window[\"SVGFEFuncGElement\"]" gTypeSVGFEFuncGElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGFEFuncRElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGComponentTransferFunctionElement" -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype SVGFEFuncRElement = SVGFEFuncRElement { unSVGFEFuncRElement :: JSVal } instance Eq (SVGFEFuncRElement) where (SVGFEFuncRElement a) == (SVGFEFuncRElement b) = js_eq a b instance PToJSVal SVGFEFuncRElement where pToJSVal = unSVGFEFuncRElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGFEFuncRElement where pFromJSVal = SVGFEFuncRElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGFEFuncRElement where toJSVal = return . unSVGFEFuncRElement {-# INLINE toJSVal #-} instance FromJSVal SVGFEFuncRElement where fromJSVal = return . fmap SVGFEFuncRElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGComponentTransferFunctionElement SVGFEFuncRElement instance IsSVGElement SVGFEFuncRElement instance IsElement SVGFEFuncRElement instance IsNode SVGFEFuncRElement instance IsEventTarget SVGFEFuncRElement instance IsSlotable SVGFEFuncRElement instance IsParentNode SVGFEFuncRElement instance IsNonDocumentTypeChildNode SVGFEFuncRElement instance IsDocumentAndElementEventHandlers SVGFEFuncRElement instance IsChildNode SVGFEFuncRElement instance IsAnimatable SVGFEFuncRElement instance IsGlobalEventHandlers SVGFEFuncRElement instance IsElementCSSInlineStyle SVGFEFuncRElement instance IsGObject SVGFEFuncRElement where typeGType _ = gTypeSVGFEFuncRElement {-# INLINE typeGType #-} noSVGFEFuncRElement :: Maybe SVGFEFuncRElement noSVGFEFuncRElement = Nothing {-# INLINE noSVGFEFuncRElement #-} foreign import javascript unsafe "window[\"SVGFEFuncRElement\"]" gTypeSVGFEFuncRElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGFEGaussianBlurElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- * "GHCJS.DOM.SVGFilterPrimitiveStandardAttributes" -- -- newtype SVGFEGaussianBlurElement = SVGFEGaussianBlurElement { unSVGFEGaussianBlurElement :: JSVal } instance Eq (SVGFEGaussianBlurElement) where (SVGFEGaussianBlurElement a) == (SVGFEGaussianBlurElement b) = js_eq a b instance PToJSVal SVGFEGaussianBlurElement where pToJSVal = unSVGFEGaussianBlurElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGFEGaussianBlurElement where pFromJSVal = SVGFEGaussianBlurElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGFEGaussianBlurElement where toJSVal = return . unSVGFEGaussianBlurElement {-# INLINE toJSVal #-} instance FromJSVal SVGFEGaussianBlurElement where fromJSVal = return . fmap SVGFEGaussianBlurElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGElement SVGFEGaussianBlurElement instance IsElement SVGFEGaussianBlurElement instance IsNode SVGFEGaussianBlurElement instance IsEventTarget SVGFEGaussianBlurElement instance IsSlotable SVGFEGaussianBlurElement instance IsParentNode SVGFEGaussianBlurElement instance IsNonDocumentTypeChildNode SVGFEGaussianBlurElement instance IsDocumentAndElementEventHandlers SVGFEGaussianBlurElement instance IsChildNode SVGFEGaussianBlurElement instance IsAnimatable SVGFEGaussianBlurElement instance IsGlobalEventHandlers SVGFEGaussianBlurElement instance IsElementCSSInlineStyle SVGFEGaussianBlurElement instance IsSVGFilterPrimitiveStandardAttributes SVGFEGaussianBlurElement instance IsGObject SVGFEGaussianBlurElement where typeGType _ = gTypeSVGFEGaussianBlurElement {-# INLINE typeGType #-} noSVGFEGaussianBlurElement :: Maybe SVGFEGaussianBlurElement noSVGFEGaussianBlurElement = Nothing {-# INLINE noSVGFEGaussianBlurElement #-} foreign import javascript unsafe "window[\"SVGFEGaussianBlurElement\"]" gTypeSVGFEGaussianBlurElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGFEImageElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- * "GHCJS.DOM.SVGURIReference" -- * "GHCJS.DOM.SVGFilterPrimitiveStandardAttributes" -- * "GHCJS.DOM.SVGExternalResourcesRequired" -- -- newtype SVGFEImageElement = SVGFEImageElement { unSVGFEImageElement :: JSVal } instance Eq (SVGFEImageElement) where (SVGFEImageElement a) == (SVGFEImageElement b) = js_eq a b instance PToJSVal SVGFEImageElement where pToJSVal = unSVGFEImageElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGFEImageElement where pFromJSVal = SVGFEImageElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGFEImageElement where toJSVal = return . unSVGFEImageElement {-# INLINE toJSVal #-} instance FromJSVal SVGFEImageElement where fromJSVal = return . fmap SVGFEImageElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGElement SVGFEImageElement instance IsElement SVGFEImageElement instance IsNode SVGFEImageElement instance IsEventTarget SVGFEImageElement instance IsSlotable SVGFEImageElement instance IsParentNode SVGFEImageElement instance IsNonDocumentTypeChildNode SVGFEImageElement instance IsDocumentAndElementEventHandlers SVGFEImageElement instance IsChildNode SVGFEImageElement instance IsAnimatable SVGFEImageElement instance IsGlobalEventHandlers SVGFEImageElement instance IsElementCSSInlineStyle SVGFEImageElement instance IsSVGURIReference SVGFEImageElement instance IsSVGFilterPrimitiveStandardAttributes SVGFEImageElement instance IsSVGExternalResourcesRequired SVGFEImageElement instance IsGObject SVGFEImageElement where typeGType _ = gTypeSVGFEImageElement {-# INLINE typeGType #-} noSVGFEImageElement :: Maybe SVGFEImageElement noSVGFEImageElement = Nothing {-# INLINE noSVGFEImageElement #-} foreign import javascript unsafe "window[\"SVGFEImageElement\"]" gTypeSVGFEImageElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGFEMergeElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- * "GHCJS.DOM.SVGFilterPrimitiveStandardAttributes" -- -- newtype SVGFEMergeElement = SVGFEMergeElement { unSVGFEMergeElement :: JSVal } instance Eq (SVGFEMergeElement) where (SVGFEMergeElement a) == (SVGFEMergeElement b) = js_eq a b instance PToJSVal SVGFEMergeElement where pToJSVal = unSVGFEMergeElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGFEMergeElement where pFromJSVal = SVGFEMergeElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGFEMergeElement where toJSVal = return . unSVGFEMergeElement {-# INLINE toJSVal #-} instance FromJSVal SVGFEMergeElement where fromJSVal = return . fmap SVGFEMergeElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGElement SVGFEMergeElement instance IsElement SVGFEMergeElement instance IsNode SVGFEMergeElement instance IsEventTarget SVGFEMergeElement instance IsSlotable SVGFEMergeElement instance IsParentNode SVGFEMergeElement instance IsNonDocumentTypeChildNode SVGFEMergeElement instance IsDocumentAndElementEventHandlers SVGFEMergeElement instance IsChildNode SVGFEMergeElement instance IsAnimatable SVGFEMergeElement instance IsGlobalEventHandlers SVGFEMergeElement instance IsElementCSSInlineStyle SVGFEMergeElement instance IsSVGFilterPrimitiveStandardAttributes SVGFEMergeElement instance IsGObject SVGFEMergeElement where typeGType _ = gTypeSVGFEMergeElement {-# INLINE typeGType #-} noSVGFEMergeElement :: Maybe SVGFEMergeElement noSVGFEMergeElement = Nothing {-# INLINE noSVGFEMergeElement #-} foreign import javascript unsafe "window[\"SVGFEMergeElement\"]" gTypeSVGFEMergeElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGFEMergeNodeElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype SVGFEMergeNodeElement = SVGFEMergeNodeElement { unSVGFEMergeNodeElement :: JSVal } instance Eq (SVGFEMergeNodeElement) where (SVGFEMergeNodeElement a) == (SVGFEMergeNodeElement b) = js_eq a b instance PToJSVal SVGFEMergeNodeElement where pToJSVal = unSVGFEMergeNodeElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGFEMergeNodeElement where pFromJSVal = SVGFEMergeNodeElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGFEMergeNodeElement where toJSVal = return . unSVGFEMergeNodeElement {-# INLINE toJSVal #-} instance FromJSVal SVGFEMergeNodeElement where fromJSVal = return . fmap SVGFEMergeNodeElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGElement SVGFEMergeNodeElement instance IsElement SVGFEMergeNodeElement instance IsNode SVGFEMergeNodeElement instance IsEventTarget SVGFEMergeNodeElement instance IsSlotable SVGFEMergeNodeElement instance IsParentNode SVGFEMergeNodeElement instance IsNonDocumentTypeChildNode SVGFEMergeNodeElement instance IsDocumentAndElementEventHandlers SVGFEMergeNodeElement instance IsChildNode SVGFEMergeNodeElement instance IsAnimatable SVGFEMergeNodeElement instance IsGlobalEventHandlers SVGFEMergeNodeElement instance IsElementCSSInlineStyle SVGFEMergeNodeElement instance IsGObject SVGFEMergeNodeElement where typeGType _ = gTypeSVGFEMergeNodeElement {-# INLINE typeGType #-} noSVGFEMergeNodeElement :: Maybe SVGFEMergeNodeElement noSVGFEMergeNodeElement = Nothing {-# INLINE noSVGFEMergeNodeElement #-} foreign import javascript unsafe "window[\"SVGFEMergeNodeElement\"]" gTypeSVGFEMergeNodeElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGFEMorphologyElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- * "GHCJS.DOM.SVGFilterPrimitiveStandardAttributes" -- -- newtype SVGFEMorphologyElement = SVGFEMorphologyElement { unSVGFEMorphologyElement :: JSVal } instance Eq (SVGFEMorphologyElement) where (SVGFEMorphologyElement a) == (SVGFEMorphologyElement b) = js_eq a b instance PToJSVal SVGFEMorphologyElement where pToJSVal = unSVGFEMorphologyElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGFEMorphologyElement where pFromJSVal = SVGFEMorphologyElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGFEMorphologyElement where toJSVal = return . unSVGFEMorphologyElement {-# INLINE toJSVal #-} instance FromJSVal SVGFEMorphologyElement where fromJSVal = return . fmap SVGFEMorphologyElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGElement SVGFEMorphologyElement instance IsElement SVGFEMorphologyElement instance IsNode SVGFEMorphologyElement instance IsEventTarget SVGFEMorphologyElement instance IsSlotable SVGFEMorphologyElement instance IsParentNode SVGFEMorphologyElement instance IsNonDocumentTypeChildNode SVGFEMorphologyElement instance IsDocumentAndElementEventHandlers SVGFEMorphologyElement instance IsChildNode SVGFEMorphologyElement instance IsAnimatable SVGFEMorphologyElement instance IsGlobalEventHandlers SVGFEMorphologyElement instance IsElementCSSInlineStyle SVGFEMorphologyElement instance IsSVGFilterPrimitiveStandardAttributes SVGFEMorphologyElement instance IsGObject SVGFEMorphologyElement where typeGType _ = gTypeSVGFEMorphologyElement {-# INLINE typeGType #-} noSVGFEMorphologyElement :: Maybe SVGFEMorphologyElement noSVGFEMorphologyElement = Nothing {-# INLINE noSVGFEMorphologyElement #-} foreign import javascript unsafe "window[\"SVGFEMorphologyElement\"]" gTypeSVGFEMorphologyElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGFEOffsetElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- * "GHCJS.DOM.SVGFilterPrimitiveStandardAttributes" -- -- newtype SVGFEOffsetElement = SVGFEOffsetElement { unSVGFEOffsetElement :: JSVal } instance Eq (SVGFEOffsetElement) where (SVGFEOffsetElement a) == (SVGFEOffsetElement b) = js_eq a b instance PToJSVal SVGFEOffsetElement where pToJSVal = unSVGFEOffsetElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGFEOffsetElement where pFromJSVal = SVGFEOffsetElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGFEOffsetElement where toJSVal = return . unSVGFEOffsetElement {-# INLINE toJSVal #-} instance FromJSVal SVGFEOffsetElement where fromJSVal = return . fmap SVGFEOffsetElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGElement SVGFEOffsetElement instance IsElement SVGFEOffsetElement instance IsNode SVGFEOffsetElement instance IsEventTarget SVGFEOffsetElement instance IsSlotable SVGFEOffsetElement instance IsParentNode SVGFEOffsetElement instance IsNonDocumentTypeChildNode SVGFEOffsetElement instance IsDocumentAndElementEventHandlers SVGFEOffsetElement instance IsChildNode SVGFEOffsetElement instance IsAnimatable SVGFEOffsetElement instance IsGlobalEventHandlers SVGFEOffsetElement instance IsElementCSSInlineStyle SVGFEOffsetElement instance IsSVGFilterPrimitiveStandardAttributes SVGFEOffsetElement instance IsGObject SVGFEOffsetElement where typeGType _ = gTypeSVGFEOffsetElement {-# INLINE typeGType #-} noSVGFEOffsetElement :: Maybe SVGFEOffsetElement noSVGFEOffsetElement = Nothing {-# INLINE noSVGFEOffsetElement #-} foreign import javascript unsafe "window[\"SVGFEOffsetElement\"]" gTypeSVGFEOffsetElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGFEPointLightElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype SVGFEPointLightElement = SVGFEPointLightElement { unSVGFEPointLightElement :: JSVal } instance Eq (SVGFEPointLightElement) where (SVGFEPointLightElement a) == (SVGFEPointLightElement b) = js_eq a b instance PToJSVal SVGFEPointLightElement where pToJSVal = unSVGFEPointLightElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGFEPointLightElement where pFromJSVal = SVGFEPointLightElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGFEPointLightElement where toJSVal = return . unSVGFEPointLightElement {-# INLINE toJSVal #-} instance FromJSVal SVGFEPointLightElement where fromJSVal = return . fmap SVGFEPointLightElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGElement SVGFEPointLightElement instance IsElement SVGFEPointLightElement instance IsNode SVGFEPointLightElement instance IsEventTarget SVGFEPointLightElement instance IsSlotable SVGFEPointLightElement instance IsParentNode SVGFEPointLightElement instance IsNonDocumentTypeChildNode SVGFEPointLightElement instance IsDocumentAndElementEventHandlers SVGFEPointLightElement instance IsChildNode SVGFEPointLightElement instance IsAnimatable SVGFEPointLightElement instance IsGlobalEventHandlers SVGFEPointLightElement instance IsElementCSSInlineStyle SVGFEPointLightElement instance IsGObject SVGFEPointLightElement where typeGType _ = gTypeSVGFEPointLightElement {-# INLINE typeGType #-} noSVGFEPointLightElement :: Maybe SVGFEPointLightElement noSVGFEPointLightElement = Nothing {-# INLINE noSVGFEPointLightElement #-} foreign import javascript unsafe "window[\"SVGFEPointLightElement\"]" gTypeSVGFEPointLightElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGFESpecularLightingElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- * "GHCJS.DOM.SVGFilterPrimitiveStandardAttributes" -- -- newtype SVGFESpecularLightingElement = SVGFESpecularLightingElement { unSVGFESpecularLightingElement :: JSVal } instance Eq (SVGFESpecularLightingElement) where (SVGFESpecularLightingElement a) == (SVGFESpecularLightingElement b) = js_eq a b instance PToJSVal SVGFESpecularLightingElement where pToJSVal = unSVGFESpecularLightingElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGFESpecularLightingElement where pFromJSVal = SVGFESpecularLightingElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGFESpecularLightingElement where toJSVal = return . unSVGFESpecularLightingElement {-# INLINE toJSVal #-} instance FromJSVal SVGFESpecularLightingElement where fromJSVal = return . fmap SVGFESpecularLightingElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGElement SVGFESpecularLightingElement instance IsElement SVGFESpecularLightingElement instance IsNode SVGFESpecularLightingElement instance IsEventTarget SVGFESpecularLightingElement instance IsSlotable SVGFESpecularLightingElement instance IsParentNode SVGFESpecularLightingElement instance IsNonDocumentTypeChildNode SVGFESpecularLightingElement instance IsDocumentAndElementEventHandlers SVGFESpecularLightingElement instance IsChildNode SVGFESpecularLightingElement instance IsAnimatable SVGFESpecularLightingElement instance IsGlobalEventHandlers SVGFESpecularLightingElement instance IsElementCSSInlineStyle SVGFESpecularLightingElement instance IsSVGFilterPrimitiveStandardAttributes SVGFESpecularLightingElement instance IsGObject SVGFESpecularLightingElement where typeGType _ = gTypeSVGFESpecularLightingElement {-# INLINE typeGType #-} noSVGFESpecularLightingElement :: Maybe SVGFESpecularLightingElement noSVGFESpecularLightingElement = Nothing {-# INLINE noSVGFESpecularLightingElement #-} foreign import javascript unsafe "window[\"SVGFESpecularLightingElement\"]" gTypeSVGFESpecularLightingElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGFESpotLightElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype SVGFESpotLightElement = SVGFESpotLightElement { unSVGFESpotLightElement :: JSVal } instance Eq (SVGFESpotLightElement) where (SVGFESpotLightElement a) == (SVGFESpotLightElement b) = js_eq a b instance PToJSVal SVGFESpotLightElement where pToJSVal = unSVGFESpotLightElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGFESpotLightElement where pFromJSVal = SVGFESpotLightElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGFESpotLightElement where toJSVal = return . unSVGFESpotLightElement {-# INLINE toJSVal #-} instance FromJSVal SVGFESpotLightElement where fromJSVal = return . fmap SVGFESpotLightElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGElement SVGFESpotLightElement instance IsElement SVGFESpotLightElement instance IsNode SVGFESpotLightElement instance IsEventTarget SVGFESpotLightElement instance IsSlotable SVGFESpotLightElement instance IsParentNode SVGFESpotLightElement instance IsNonDocumentTypeChildNode SVGFESpotLightElement instance IsDocumentAndElementEventHandlers SVGFESpotLightElement instance IsChildNode SVGFESpotLightElement instance IsAnimatable SVGFESpotLightElement instance IsGlobalEventHandlers SVGFESpotLightElement instance IsElementCSSInlineStyle SVGFESpotLightElement instance IsGObject SVGFESpotLightElement where typeGType _ = gTypeSVGFESpotLightElement {-# INLINE typeGType #-} noSVGFESpotLightElement :: Maybe SVGFESpotLightElement noSVGFESpotLightElement = Nothing {-# INLINE noSVGFESpotLightElement #-} foreign import javascript unsafe "window[\"SVGFESpotLightElement\"]" gTypeSVGFESpotLightElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGFETileElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- * "GHCJS.DOM.SVGFilterPrimitiveStandardAttributes" -- -- newtype SVGFETileElement = SVGFETileElement { unSVGFETileElement :: JSVal } instance Eq (SVGFETileElement) where (SVGFETileElement a) == (SVGFETileElement b) = js_eq a b instance PToJSVal SVGFETileElement where pToJSVal = unSVGFETileElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGFETileElement where pFromJSVal = SVGFETileElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGFETileElement where toJSVal = return . unSVGFETileElement {-# INLINE toJSVal #-} instance FromJSVal SVGFETileElement where fromJSVal = return . fmap SVGFETileElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGElement SVGFETileElement instance IsElement SVGFETileElement instance IsNode SVGFETileElement instance IsEventTarget SVGFETileElement instance IsSlotable SVGFETileElement instance IsParentNode SVGFETileElement instance IsNonDocumentTypeChildNode SVGFETileElement instance IsDocumentAndElementEventHandlers SVGFETileElement instance IsChildNode SVGFETileElement instance IsAnimatable SVGFETileElement instance IsGlobalEventHandlers SVGFETileElement instance IsElementCSSInlineStyle SVGFETileElement instance IsSVGFilterPrimitiveStandardAttributes SVGFETileElement instance IsGObject SVGFETileElement where typeGType _ = gTypeSVGFETileElement {-# INLINE typeGType #-} noSVGFETileElement :: Maybe SVGFETileElement noSVGFETileElement = Nothing {-# INLINE noSVGFETileElement #-} foreign import javascript unsafe "window[\"SVGFETileElement\"]" gTypeSVGFETileElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGFETurbulenceElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- * "GHCJS.DOM.SVGFilterPrimitiveStandardAttributes" -- -- newtype SVGFETurbulenceElement = SVGFETurbulenceElement { unSVGFETurbulenceElement :: JSVal } instance Eq (SVGFETurbulenceElement) where (SVGFETurbulenceElement a) == (SVGFETurbulenceElement b) = js_eq a b instance PToJSVal SVGFETurbulenceElement where pToJSVal = unSVGFETurbulenceElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGFETurbulenceElement where pFromJSVal = SVGFETurbulenceElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGFETurbulenceElement where toJSVal = return . unSVGFETurbulenceElement {-# INLINE toJSVal #-} instance FromJSVal SVGFETurbulenceElement where fromJSVal = return . fmap SVGFETurbulenceElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGElement SVGFETurbulenceElement instance IsElement SVGFETurbulenceElement instance IsNode SVGFETurbulenceElement instance IsEventTarget SVGFETurbulenceElement instance IsSlotable SVGFETurbulenceElement instance IsParentNode SVGFETurbulenceElement instance IsNonDocumentTypeChildNode SVGFETurbulenceElement instance IsDocumentAndElementEventHandlers SVGFETurbulenceElement instance IsChildNode SVGFETurbulenceElement instance IsAnimatable SVGFETurbulenceElement instance IsGlobalEventHandlers SVGFETurbulenceElement instance IsElementCSSInlineStyle SVGFETurbulenceElement instance IsSVGFilterPrimitiveStandardAttributes SVGFETurbulenceElement instance IsGObject SVGFETurbulenceElement where typeGType _ = gTypeSVGFETurbulenceElement {-# INLINE typeGType #-} noSVGFETurbulenceElement :: Maybe SVGFETurbulenceElement noSVGFETurbulenceElement = Nothing {-# INLINE noSVGFETurbulenceElement #-} foreign import javascript unsafe "window[\"SVGFETurbulenceElement\"]" gTypeSVGFETurbulenceElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGFilterElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- * "GHCJS.DOM.SVGURIReference" -- * "GHCJS.DOM.SVGExternalResourcesRequired" -- -- newtype SVGFilterElement = SVGFilterElement { unSVGFilterElement :: JSVal } instance Eq (SVGFilterElement) where (SVGFilterElement a) == (SVGFilterElement b) = js_eq a b instance PToJSVal SVGFilterElement where pToJSVal = unSVGFilterElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGFilterElement where pFromJSVal = SVGFilterElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGFilterElement where toJSVal = return . unSVGFilterElement {-# INLINE toJSVal #-} instance FromJSVal SVGFilterElement where fromJSVal = return . fmap SVGFilterElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGElement SVGFilterElement instance IsElement SVGFilterElement instance IsNode SVGFilterElement instance IsEventTarget SVGFilterElement instance IsSlotable SVGFilterElement instance IsParentNode SVGFilterElement instance IsNonDocumentTypeChildNode SVGFilterElement instance IsDocumentAndElementEventHandlers SVGFilterElement instance IsChildNode SVGFilterElement instance IsAnimatable SVGFilterElement instance IsGlobalEventHandlers SVGFilterElement instance IsElementCSSInlineStyle SVGFilterElement instance IsSVGURIReference SVGFilterElement instance IsSVGExternalResourcesRequired SVGFilterElement instance IsGObject SVGFilterElement where typeGType _ = gTypeSVGFilterElement {-# INLINE typeGType #-} noSVGFilterElement :: Maybe SVGFilterElement noSVGFilterElement = Nothing {-# INLINE noSVGFilterElement #-} foreign import javascript unsafe "window[\"SVGFilterElement\"]" gTypeSVGFilterElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGFilterPrimitiveStandardAttributes". -- -- newtype SVGFilterPrimitiveStandardAttributes = SVGFilterPrimitiveStandardAttributes { unSVGFilterPrimitiveStandardAttributes :: JSVal } instance Eq (SVGFilterPrimitiveStandardAttributes) where (SVGFilterPrimitiveStandardAttributes a) == (SVGFilterPrimitiveStandardAttributes b) = js_eq a b instance PToJSVal SVGFilterPrimitiveStandardAttributes where pToJSVal = unSVGFilterPrimitiveStandardAttributes {-# INLINE pToJSVal #-} instance PFromJSVal SVGFilterPrimitiveStandardAttributes where pFromJSVal = SVGFilterPrimitiveStandardAttributes {-# INLINE pFromJSVal #-} instance ToJSVal SVGFilterPrimitiveStandardAttributes where toJSVal = return . unSVGFilterPrimitiveStandardAttributes {-# INLINE toJSVal #-} instance FromJSVal SVGFilterPrimitiveStandardAttributes where fromJSVal = return . fmap SVGFilterPrimitiveStandardAttributes . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsGObject o) => IsSVGFilterPrimitiveStandardAttributes o toSVGFilterPrimitiveStandardAttributes :: IsSVGFilterPrimitiveStandardAttributes o => o -> SVGFilterPrimitiveStandardAttributes toSVGFilterPrimitiveStandardAttributes = SVGFilterPrimitiveStandardAttributes . coerce instance IsSVGFilterPrimitiveStandardAttributes SVGFilterPrimitiveStandardAttributes instance IsGObject SVGFilterPrimitiveStandardAttributes where typeGType _ = gTypeSVGFilterPrimitiveStandardAttributes {-# INLINE typeGType #-} noSVGFilterPrimitiveStandardAttributes :: Maybe SVGFilterPrimitiveStandardAttributes noSVGFilterPrimitiveStandardAttributes = Nothing {-# INLINE noSVGFilterPrimitiveStandardAttributes #-} foreign import javascript unsafe "window[\"SVGFilterPrimitiveStandardAttributes\"]" gTypeSVGFilterPrimitiveStandardAttributes :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGFitToViewBox". -- -- newtype SVGFitToViewBox = SVGFitToViewBox { unSVGFitToViewBox :: JSVal } instance Eq (SVGFitToViewBox) where (SVGFitToViewBox a) == (SVGFitToViewBox b) = js_eq a b instance PToJSVal SVGFitToViewBox where pToJSVal = unSVGFitToViewBox {-# INLINE pToJSVal #-} instance PFromJSVal SVGFitToViewBox where pFromJSVal = SVGFitToViewBox {-# INLINE pFromJSVal #-} instance ToJSVal SVGFitToViewBox where toJSVal = return . unSVGFitToViewBox {-# INLINE toJSVal #-} instance FromJSVal SVGFitToViewBox where fromJSVal = return . fmap SVGFitToViewBox . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsGObject o) => IsSVGFitToViewBox o toSVGFitToViewBox :: IsSVGFitToViewBox o => o -> SVGFitToViewBox toSVGFitToViewBox = SVGFitToViewBox . coerce instance IsSVGFitToViewBox SVGFitToViewBox instance IsGObject SVGFitToViewBox where typeGType _ = gTypeSVGFitToViewBox {-# INLINE typeGType #-} noSVGFitToViewBox :: Maybe SVGFitToViewBox noSVGFitToViewBox = Nothing {-# INLINE noSVGFitToViewBox #-} foreign import javascript unsafe "window[\"SVGFitToViewBox\"]" gTypeSVGFitToViewBox :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGFontElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype SVGFontElement = SVGFontElement { unSVGFontElement :: JSVal } instance Eq (SVGFontElement) where (SVGFontElement a) == (SVGFontElement b) = js_eq a b instance PToJSVal SVGFontElement where pToJSVal = unSVGFontElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGFontElement where pFromJSVal = SVGFontElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGFontElement where toJSVal = return . unSVGFontElement {-# INLINE toJSVal #-} instance FromJSVal SVGFontElement where fromJSVal = return . fmap SVGFontElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGElement SVGFontElement instance IsElement SVGFontElement instance IsNode SVGFontElement instance IsEventTarget SVGFontElement instance IsSlotable SVGFontElement instance IsParentNode SVGFontElement instance IsNonDocumentTypeChildNode SVGFontElement instance IsDocumentAndElementEventHandlers SVGFontElement instance IsChildNode SVGFontElement instance IsAnimatable SVGFontElement instance IsGlobalEventHandlers SVGFontElement instance IsElementCSSInlineStyle SVGFontElement instance IsGObject SVGFontElement where typeGType _ = gTypeSVGFontElement {-# INLINE typeGType #-} noSVGFontElement :: Maybe SVGFontElement noSVGFontElement = Nothing {-# INLINE noSVGFontElement #-} foreign import javascript unsafe "window[\"SVGFontElement\"]" gTypeSVGFontElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGFontFaceElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype SVGFontFaceElement = SVGFontFaceElement { unSVGFontFaceElement :: JSVal } instance Eq (SVGFontFaceElement) where (SVGFontFaceElement a) == (SVGFontFaceElement b) = js_eq a b instance PToJSVal SVGFontFaceElement where pToJSVal = unSVGFontFaceElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGFontFaceElement where pFromJSVal = SVGFontFaceElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGFontFaceElement where toJSVal = return . unSVGFontFaceElement {-# INLINE toJSVal #-} instance FromJSVal SVGFontFaceElement where fromJSVal = return . fmap SVGFontFaceElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGElement SVGFontFaceElement instance IsElement SVGFontFaceElement instance IsNode SVGFontFaceElement instance IsEventTarget SVGFontFaceElement instance IsSlotable SVGFontFaceElement instance IsParentNode SVGFontFaceElement instance IsNonDocumentTypeChildNode SVGFontFaceElement instance IsDocumentAndElementEventHandlers SVGFontFaceElement instance IsChildNode SVGFontFaceElement instance IsAnimatable SVGFontFaceElement instance IsGlobalEventHandlers SVGFontFaceElement instance IsElementCSSInlineStyle SVGFontFaceElement instance IsGObject SVGFontFaceElement where typeGType _ = gTypeSVGFontFaceElement {-# INLINE typeGType #-} noSVGFontFaceElement :: Maybe SVGFontFaceElement noSVGFontFaceElement = Nothing {-# INLINE noSVGFontFaceElement #-} foreign import javascript unsafe "window[\"SVGFontFaceElement\"]" gTypeSVGFontFaceElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGFontFaceFormatElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype SVGFontFaceFormatElement = SVGFontFaceFormatElement { unSVGFontFaceFormatElement :: JSVal } instance Eq (SVGFontFaceFormatElement) where (SVGFontFaceFormatElement a) == (SVGFontFaceFormatElement b) = js_eq a b instance PToJSVal SVGFontFaceFormatElement where pToJSVal = unSVGFontFaceFormatElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGFontFaceFormatElement where pFromJSVal = SVGFontFaceFormatElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGFontFaceFormatElement where toJSVal = return . unSVGFontFaceFormatElement {-# INLINE toJSVal #-} instance FromJSVal SVGFontFaceFormatElement where fromJSVal = return . fmap SVGFontFaceFormatElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGElement SVGFontFaceFormatElement instance IsElement SVGFontFaceFormatElement instance IsNode SVGFontFaceFormatElement instance IsEventTarget SVGFontFaceFormatElement instance IsSlotable SVGFontFaceFormatElement instance IsParentNode SVGFontFaceFormatElement instance IsNonDocumentTypeChildNode SVGFontFaceFormatElement instance IsDocumentAndElementEventHandlers SVGFontFaceFormatElement instance IsChildNode SVGFontFaceFormatElement instance IsAnimatable SVGFontFaceFormatElement instance IsGlobalEventHandlers SVGFontFaceFormatElement instance IsElementCSSInlineStyle SVGFontFaceFormatElement instance IsGObject SVGFontFaceFormatElement where typeGType _ = gTypeSVGFontFaceFormatElement {-# INLINE typeGType #-} noSVGFontFaceFormatElement :: Maybe SVGFontFaceFormatElement noSVGFontFaceFormatElement = Nothing {-# INLINE noSVGFontFaceFormatElement #-} foreign import javascript unsafe "window[\"SVGFontFaceFormatElement\"]" gTypeSVGFontFaceFormatElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGFontFaceNameElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype SVGFontFaceNameElement = SVGFontFaceNameElement { unSVGFontFaceNameElement :: JSVal } instance Eq (SVGFontFaceNameElement) where (SVGFontFaceNameElement a) == (SVGFontFaceNameElement b) = js_eq a b instance PToJSVal SVGFontFaceNameElement where pToJSVal = unSVGFontFaceNameElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGFontFaceNameElement where pFromJSVal = SVGFontFaceNameElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGFontFaceNameElement where toJSVal = return . unSVGFontFaceNameElement {-# INLINE toJSVal #-} instance FromJSVal SVGFontFaceNameElement where fromJSVal = return . fmap SVGFontFaceNameElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGElement SVGFontFaceNameElement instance IsElement SVGFontFaceNameElement instance IsNode SVGFontFaceNameElement instance IsEventTarget SVGFontFaceNameElement instance IsSlotable SVGFontFaceNameElement instance IsParentNode SVGFontFaceNameElement instance IsNonDocumentTypeChildNode SVGFontFaceNameElement instance IsDocumentAndElementEventHandlers SVGFontFaceNameElement instance IsChildNode SVGFontFaceNameElement instance IsAnimatable SVGFontFaceNameElement instance IsGlobalEventHandlers SVGFontFaceNameElement instance IsElementCSSInlineStyle SVGFontFaceNameElement instance IsGObject SVGFontFaceNameElement where typeGType _ = gTypeSVGFontFaceNameElement {-# INLINE typeGType #-} noSVGFontFaceNameElement :: Maybe SVGFontFaceNameElement noSVGFontFaceNameElement = Nothing {-# INLINE noSVGFontFaceNameElement #-} foreign import javascript unsafe "window[\"SVGFontFaceNameElement\"]" gTypeSVGFontFaceNameElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGFontFaceSrcElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype SVGFontFaceSrcElement = SVGFontFaceSrcElement { unSVGFontFaceSrcElement :: JSVal } instance Eq (SVGFontFaceSrcElement) where (SVGFontFaceSrcElement a) == (SVGFontFaceSrcElement b) = js_eq a b instance PToJSVal SVGFontFaceSrcElement where pToJSVal = unSVGFontFaceSrcElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGFontFaceSrcElement where pFromJSVal = SVGFontFaceSrcElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGFontFaceSrcElement where toJSVal = return . unSVGFontFaceSrcElement {-# INLINE toJSVal #-} instance FromJSVal SVGFontFaceSrcElement where fromJSVal = return . fmap SVGFontFaceSrcElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGElement SVGFontFaceSrcElement instance IsElement SVGFontFaceSrcElement instance IsNode SVGFontFaceSrcElement instance IsEventTarget SVGFontFaceSrcElement instance IsSlotable SVGFontFaceSrcElement instance IsParentNode SVGFontFaceSrcElement instance IsNonDocumentTypeChildNode SVGFontFaceSrcElement instance IsDocumentAndElementEventHandlers SVGFontFaceSrcElement instance IsChildNode SVGFontFaceSrcElement instance IsAnimatable SVGFontFaceSrcElement instance IsGlobalEventHandlers SVGFontFaceSrcElement instance IsElementCSSInlineStyle SVGFontFaceSrcElement instance IsGObject SVGFontFaceSrcElement where typeGType _ = gTypeSVGFontFaceSrcElement {-# INLINE typeGType #-} noSVGFontFaceSrcElement :: Maybe SVGFontFaceSrcElement noSVGFontFaceSrcElement = Nothing {-# INLINE noSVGFontFaceSrcElement #-} foreign import javascript unsafe "window[\"SVGFontFaceSrcElement\"]" gTypeSVGFontFaceSrcElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGFontFaceUriElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype SVGFontFaceUriElement = SVGFontFaceUriElement { unSVGFontFaceUriElement :: JSVal } instance Eq (SVGFontFaceUriElement) where (SVGFontFaceUriElement a) == (SVGFontFaceUriElement b) = js_eq a b instance PToJSVal SVGFontFaceUriElement where pToJSVal = unSVGFontFaceUriElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGFontFaceUriElement where pFromJSVal = SVGFontFaceUriElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGFontFaceUriElement where toJSVal = return . unSVGFontFaceUriElement {-# INLINE toJSVal #-} instance FromJSVal SVGFontFaceUriElement where fromJSVal = return . fmap SVGFontFaceUriElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGElement SVGFontFaceUriElement instance IsElement SVGFontFaceUriElement instance IsNode SVGFontFaceUriElement instance IsEventTarget SVGFontFaceUriElement instance IsSlotable SVGFontFaceUriElement instance IsParentNode SVGFontFaceUriElement instance IsNonDocumentTypeChildNode SVGFontFaceUriElement instance IsDocumentAndElementEventHandlers SVGFontFaceUriElement instance IsChildNode SVGFontFaceUriElement instance IsAnimatable SVGFontFaceUriElement instance IsGlobalEventHandlers SVGFontFaceUriElement instance IsElementCSSInlineStyle SVGFontFaceUriElement instance IsGObject SVGFontFaceUriElement where typeGType _ = gTypeSVGFontFaceUriElement {-# INLINE typeGType #-} noSVGFontFaceUriElement :: Maybe SVGFontFaceUriElement noSVGFontFaceUriElement = Nothing {-# INLINE noSVGFontFaceUriElement #-} foreign import javascript unsafe "window[\"SVGFontFaceUriElement\"]" gTypeSVGFontFaceUriElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGForeignObjectElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGGraphicsElement" -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- * "GHCJS.DOM.SVGTests" -- * "GHCJS.DOM.SVGExternalResourcesRequired" -- -- newtype SVGForeignObjectElement = SVGForeignObjectElement { unSVGForeignObjectElement :: JSVal } instance Eq (SVGForeignObjectElement) where (SVGForeignObjectElement a) == (SVGForeignObjectElement b) = js_eq a b instance PToJSVal SVGForeignObjectElement where pToJSVal = unSVGForeignObjectElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGForeignObjectElement where pFromJSVal = SVGForeignObjectElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGForeignObjectElement where toJSVal = return . unSVGForeignObjectElement {-# INLINE toJSVal #-} instance FromJSVal SVGForeignObjectElement where fromJSVal = return . fmap SVGForeignObjectElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGGraphicsElement SVGForeignObjectElement instance IsSVGElement SVGForeignObjectElement instance IsElement SVGForeignObjectElement instance IsNode SVGForeignObjectElement instance IsEventTarget SVGForeignObjectElement instance IsSlotable SVGForeignObjectElement instance IsParentNode SVGForeignObjectElement instance IsNonDocumentTypeChildNode SVGForeignObjectElement instance IsDocumentAndElementEventHandlers SVGForeignObjectElement instance IsChildNode SVGForeignObjectElement instance IsAnimatable SVGForeignObjectElement instance IsGlobalEventHandlers SVGForeignObjectElement instance IsElementCSSInlineStyle SVGForeignObjectElement instance IsSVGTests SVGForeignObjectElement instance IsSVGExternalResourcesRequired SVGForeignObjectElement instance IsGObject SVGForeignObjectElement where typeGType _ = gTypeSVGForeignObjectElement {-# INLINE typeGType #-} noSVGForeignObjectElement :: Maybe SVGForeignObjectElement noSVGForeignObjectElement = Nothing {-# INLINE noSVGForeignObjectElement #-} foreign import javascript unsafe "window[\"SVGForeignObjectElement\"]" gTypeSVGForeignObjectElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGGElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGGraphicsElement" -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- * "GHCJS.DOM.SVGTests" -- * "GHCJS.DOM.SVGExternalResourcesRequired" -- -- newtype SVGGElement = SVGGElement { unSVGGElement :: JSVal } instance Eq (SVGGElement) where (SVGGElement a) == (SVGGElement b) = js_eq a b instance PToJSVal SVGGElement where pToJSVal = unSVGGElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGGElement where pFromJSVal = SVGGElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGGElement where toJSVal = return . unSVGGElement {-# INLINE toJSVal #-} instance FromJSVal SVGGElement where fromJSVal = return . fmap SVGGElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGGraphicsElement SVGGElement instance IsSVGElement SVGGElement instance IsElement SVGGElement instance IsNode SVGGElement instance IsEventTarget SVGGElement instance IsSlotable SVGGElement instance IsParentNode SVGGElement instance IsNonDocumentTypeChildNode SVGGElement instance IsDocumentAndElementEventHandlers SVGGElement instance IsChildNode SVGGElement instance IsAnimatable SVGGElement instance IsGlobalEventHandlers SVGGElement instance IsElementCSSInlineStyle SVGGElement instance IsSVGTests SVGGElement instance IsSVGExternalResourcesRequired SVGGElement instance IsGObject SVGGElement where typeGType _ = gTypeSVGGElement {-# INLINE typeGType #-} noSVGGElement :: Maybe SVGGElement noSVGGElement = Nothing {-# INLINE noSVGGElement #-} foreign import javascript unsafe "window[\"SVGGElement\"]" gTypeSVGGElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGGlyphElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype SVGGlyphElement = SVGGlyphElement { unSVGGlyphElement :: JSVal } instance Eq (SVGGlyphElement) where (SVGGlyphElement a) == (SVGGlyphElement b) = js_eq a b instance PToJSVal SVGGlyphElement where pToJSVal = unSVGGlyphElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGGlyphElement where pFromJSVal = SVGGlyphElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGGlyphElement where toJSVal = return . unSVGGlyphElement {-# INLINE toJSVal #-} instance FromJSVal SVGGlyphElement where fromJSVal = return . fmap SVGGlyphElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGElement SVGGlyphElement instance IsElement SVGGlyphElement instance IsNode SVGGlyphElement instance IsEventTarget SVGGlyphElement instance IsSlotable SVGGlyphElement instance IsParentNode SVGGlyphElement instance IsNonDocumentTypeChildNode SVGGlyphElement instance IsDocumentAndElementEventHandlers SVGGlyphElement instance IsChildNode SVGGlyphElement instance IsAnimatable SVGGlyphElement instance IsGlobalEventHandlers SVGGlyphElement instance IsElementCSSInlineStyle SVGGlyphElement instance IsGObject SVGGlyphElement where typeGType _ = gTypeSVGGlyphElement {-# INLINE typeGType #-} noSVGGlyphElement :: Maybe SVGGlyphElement noSVGGlyphElement = Nothing {-# INLINE noSVGGlyphElement #-} foreign import javascript unsafe "window[\"SVGGlyphElement\"]" gTypeSVGGlyphElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGGlyphRefElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- * "GHCJS.DOM.SVGURIReference" -- -- newtype SVGGlyphRefElement = SVGGlyphRefElement { unSVGGlyphRefElement :: JSVal } instance Eq (SVGGlyphRefElement) where (SVGGlyphRefElement a) == (SVGGlyphRefElement b) = js_eq a b instance PToJSVal SVGGlyphRefElement where pToJSVal = unSVGGlyphRefElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGGlyphRefElement where pFromJSVal = SVGGlyphRefElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGGlyphRefElement where toJSVal = return . unSVGGlyphRefElement {-# INLINE toJSVal #-} instance FromJSVal SVGGlyphRefElement where fromJSVal = return . fmap SVGGlyphRefElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGElement SVGGlyphRefElement instance IsElement SVGGlyphRefElement instance IsNode SVGGlyphRefElement instance IsEventTarget SVGGlyphRefElement instance IsSlotable SVGGlyphRefElement instance IsParentNode SVGGlyphRefElement instance IsNonDocumentTypeChildNode SVGGlyphRefElement instance IsDocumentAndElementEventHandlers SVGGlyphRefElement instance IsChildNode SVGGlyphRefElement instance IsAnimatable SVGGlyphRefElement instance IsGlobalEventHandlers SVGGlyphRefElement instance IsElementCSSInlineStyle SVGGlyphRefElement instance IsSVGURIReference SVGGlyphRefElement instance IsGObject SVGGlyphRefElement where typeGType _ = gTypeSVGGlyphRefElement {-# INLINE typeGType #-} noSVGGlyphRefElement :: Maybe SVGGlyphRefElement noSVGGlyphRefElement = Nothing {-# INLINE noSVGGlyphRefElement #-} foreign import javascript unsafe "window[\"SVGGlyphRefElement\"]" gTypeSVGGlyphRefElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGGradientElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- * "GHCJS.DOM.SVGURIReference" -- * "GHCJS.DOM.SVGExternalResourcesRequired" -- -- newtype SVGGradientElement = SVGGradientElement { unSVGGradientElement :: JSVal } instance Eq (SVGGradientElement) where (SVGGradientElement a) == (SVGGradientElement b) = js_eq a b instance PToJSVal SVGGradientElement where pToJSVal = unSVGGradientElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGGradientElement where pFromJSVal = SVGGradientElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGGradientElement where toJSVal = return . unSVGGradientElement {-# INLINE toJSVal #-} instance FromJSVal SVGGradientElement where fromJSVal = return . fmap SVGGradientElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsSVGElement o, IsElement o, IsNode o, IsEventTarget o, IsSlotable o, IsParentNode o, IsNonDocumentTypeChildNode o, IsDocumentAndElementEventHandlers o, IsChildNode o, IsAnimatable o, IsGlobalEventHandlers o, IsElementCSSInlineStyle o, IsSVGURIReference o, IsSVGExternalResourcesRequired o, IsGObject o) => IsSVGGradientElement o toSVGGradientElement :: IsSVGGradientElement o => o -> SVGGradientElement toSVGGradientElement = SVGGradientElement . coerce instance IsSVGGradientElement SVGGradientElement instance IsSVGElement SVGGradientElement instance IsElement SVGGradientElement instance IsNode SVGGradientElement instance IsEventTarget SVGGradientElement instance IsSlotable SVGGradientElement instance IsParentNode SVGGradientElement instance IsNonDocumentTypeChildNode SVGGradientElement instance IsDocumentAndElementEventHandlers SVGGradientElement instance IsChildNode SVGGradientElement instance IsAnimatable SVGGradientElement instance IsGlobalEventHandlers SVGGradientElement instance IsElementCSSInlineStyle SVGGradientElement instance IsSVGURIReference SVGGradientElement instance IsSVGExternalResourcesRequired SVGGradientElement instance IsGObject SVGGradientElement where typeGType _ = gTypeSVGGradientElement {-# INLINE typeGType #-} noSVGGradientElement :: Maybe SVGGradientElement noSVGGradientElement = Nothing {-# INLINE noSVGGradientElement #-} foreign import javascript unsafe "window[\"SVGGradientElement\"]" gTypeSVGGradientElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGGraphicsElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- * "GHCJS.DOM.SVGTests" -- -- newtype SVGGraphicsElement = SVGGraphicsElement { unSVGGraphicsElement :: JSVal } instance Eq (SVGGraphicsElement) where (SVGGraphicsElement a) == (SVGGraphicsElement b) = js_eq a b instance PToJSVal SVGGraphicsElement where pToJSVal = unSVGGraphicsElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGGraphicsElement where pFromJSVal = SVGGraphicsElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGGraphicsElement where toJSVal = return . unSVGGraphicsElement {-# INLINE toJSVal #-} instance FromJSVal SVGGraphicsElement where fromJSVal = return . fmap SVGGraphicsElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsSVGElement o, IsElement o, IsNode o, IsEventTarget o, IsSlotable o, IsParentNode o, IsNonDocumentTypeChildNode o, IsDocumentAndElementEventHandlers o, IsChildNode o, IsAnimatable o, IsGlobalEventHandlers o, IsElementCSSInlineStyle o, IsSVGTests o, IsGObject o) => IsSVGGraphicsElement o toSVGGraphicsElement :: IsSVGGraphicsElement o => o -> SVGGraphicsElement toSVGGraphicsElement = SVGGraphicsElement . coerce instance IsSVGGraphicsElement SVGGraphicsElement instance IsSVGElement SVGGraphicsElement instance IsElement SVGGraphicsElement instance IsNode SVGGraphicsElement instance IsEventTarget SVGGraphicsElement instance IsSlotable SVGGraphicsElement instance IsParentNode SVGGraphicsElement instance IsNonDocumentTypeChildNode SVGGraphicsElement instance IsDocumentAndElementEventHandlers SVGGraphicsElement instance IsChildNode SVGGraphicsElement instance IsAnimatable SVGGraphicsElement instance IsGlobalEventHandlers SVGGraphicsElement instance IsElementCSSInlineStyle SVGGraphicsElement instance IsSVGTests SVGGraphicsElement instance IsGObject SVGGraphicsElement where typeGType _ = gTypeSVGGraphicsElement {-# INLINE typeGType #-} noSVGGraphicsElement :: Maybe SVGGraphicsElement noSVGGraphicsElement = Nothing {-# INLINE noSVGGraphicsElement #-} foreign import javascript unsafe "window[\"SVGGraphicsElement\"]" gTypeSVGGraphicsElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGHKernElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype SVGHKernElement = SVGHKernElement { unSVGHKernElement :: JSVal } instance Eq (SVGHKernElement) where (SVGHKernElement a) == (SVGHKernElement b) = js_eq a b instance PToJSVal SVGHKernElement where pToJSVal = unSVGHKernElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGHKernElement where pFromJSVal = SVGHKernElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGHKernElement where toJSVal = return . unSVGHKernElement {-# INLINE toJSVal #-} instance FromJSVal SVGHKernElement where fromJSVal = return . fmap SVGHKernElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGElement SVGHKernElement instance IsElement SVGHKernElement instance IsNode SVGHKernElement instance IsEventTarget SVGHKernElement instance IsSlotable SVGHKernElement instance IsParentNode SVGHKernElement instance IsNonDocumentTypeChildNode SVGHKernElement instance IsDocumentAndElementEventHandlers SVGHKernElement instance IsChildNode SVGHKernElement instance IsAnimatable SVGHKernElement instance IsGlobalEventHandlers SVGHKernElement instance IsElementCSSInlineStyle SVGHKernElement instance IsGObject SVGHKernElement where typeGType _ = gTypeSVGHKernElement {-# INLINE typeGType #-} noSVGHKernElement :: Maybe SVGHKernElement noSVGHKernElement = Nothing {-# INLINE noSVGHKernElement #-} foreign import javascript unsafe "window[\"SVGHKernElement\"]" gTypeSVGHKernElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGImageElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGGraphicsElement" -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- * "GHCJS.DOM.SVGTests" -- * "GHCJS.DOM.SVGURIReference" -- * "GHCJS.DOM.SVGExternalResourcesRequired" -- -- newtype SVGImageElement = SVGImageElement { unSVGImageElement :: JSVal } instance Eq (SVGImageElement) where (SVGImageElement a) == (SVGImageElement b) = js_eq a b instance PToJSVal SVGImageElement where pToJSVal = unSVGImageElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGImageElement where pFromJSVal = SVGImageElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGImageElement where toJSVal = return . unSVGImageElement {-# INLINE toJSVal #-} instance FromJSVal SVGImageElement where fromJSVal = return . fmap SVGImageElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGGraphicsElement SVGImageElement instance IsSVGElement SVGImageElement instance IsElement SVGImageElement instance IsNode SVGImageElement instance IsEventTarget SVGImageElement instance IsSlotable SVGImageElement instance IsParentNode SVGImageElement instance IsNonDocumentTypeChildNode SVGImageElement instance IsDocumentAndElementEventHandlers SVGImageElement instance IsChildNode SVGImageElement instance IsAnimatable SVGImageElement instance IsGlobalEventHandlers SVGImageElement instance IsElementCSSInlineStyle SVGImageElement instance IsSVGTests SVGImageElement instance IsSVGURIReference SVGImageElement instance IsSVGExternalResourcesRequired SVGImageElement instance IsGObject SVGImageElement where typeGType _ = gTypeSVGImageElement {-# INLINE typeGType #-} noSVGImageElement :: Maybe SVGImageElement noSVGImageElement = Nothing {-# INLINE noSVGImageElement #-} foreign import javascript unsafe "window[\"SVGImageElement\"]" gTypeSVGImageElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGLength". -- -- newtype SVGLength = SVGLength { unSVGLength :: JSVal } instance Eq (SVGLength) where (SVGLength a) == (SVGLength b) = js_eq a b instance PToJSVal SVGLength where pToJSVal = unSVGLength {-# INLINE pToJSVal #-} instance PFromJSVal SVGLength where pFromJSVal = SVGLength {-# INLINE pFromJSVal #-} instance ToJSVal SVGLength where toJSVal = return . unSVGLength {-# INLINE toJSVal #-} instance FromJSVal SVGLength where fromJSVal = return . fmap SVGLength . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject SVGLength where typeGType _ = gTypeSVGLength {-# INLINE typeGType #-} noSVGLength :: Maybe SVGLength noSVGLength = Nothing {-# INLINE noSVGLength #-} foreign import javascript unsafe "window[\"SVGLength\"]" gTypeSVGLength :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGLengthList". -- -- newtype SVGLengthList = SVGLengthList { unSVGLengthList :: JSVal } instance Eq (SVGLengthList) where (SVGLengthList a) == (SVGLengthList b) = js_eq a b instance PToJSVal SVGLengthList where pToJSVal = unSVGLengthList {-# INLINE pToJSVal #-} instance PFromJSVal SVGLengthList where pFromJSVal = SVGLengthList {-# INLINE pFromJSVal #-} instance ToJSVal SVGLengthList where toJSVal = return . unSVGLengthList {-# INLINE toJSVal #-} instance FromJSVal SVGLengthList where fromJSVal = return . fmap SVGLengthList . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject SVGLengthList where typeGType _ = gTypeSVGLengthList {-# INLINE typeGType #-} noSVGLengthList :: Maybe SVGLengthList noSVGLengthList = Nothing {-# INLINE noSVGLengthList #-} foreign import javascript unsafe "window[\"SVGLengthList\"]" gTypeSVGLengthList :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGLineElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGGraphicsElement" -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- * "GHCJS.DOM.SVGTests" -- * "GHCJS.DOM.SVGExternalResourcesRequired" -- -- newtype SVGLineElement = SVGLineElement { unSVGLineElement :: JSVal } instance Eq (SVGLineElement) where (SVGLineElement a) == (SVGLineElement b) = js_eq a b instance PToJSVal SVGLineElement where pToJSVal = unSVGLineElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGLineElement where pFromJSVal = SVGLineElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGLineElement where toJSVal = return . unSVGLineElement {-# INLINE toJSVal #-} instance FromJSVal SVGLineElement where fromJSVal = return . fmap SVGLineElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGGraphicsElement SVGLineElement instance IsSVGElement SVGLineElement instance IsElement SVGLineElement instance IsNode SVGLineElement instance IsEventTarget SVGLineElement instance IsSlotable SVGLineElement instance IsParentNode SVGLineElement instance IsNonDocumentTypeChildNode SVGLineElement instance IsDocumentAndElementEventHandlers SVGLineElement instance IsChildNode SVGLineElement instance IsAnimatable SVGLineElement instance IsGlobalEventHandlers SVGLineElement instance IsElementCSSInlineStyle SVGLineElement instance IsSVGTests SVGLineElement instance IsSVGExternalResourcesRequired SVGLineElement instance IsGObject SVGLineElement where typeGType _ = gTypeSVGLineElement {-# INLINE typeGType #-} noSVGLineElement :: Maybe SVGLineElement noSVGLineElement = Nothing {-# INLINE noSVGLineElement #-} foreign import javascript unsafe "window[\"SVGLineElement\"]" gTypeSVGLineElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGLinearGradientElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGGradientElement" -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- * "GHCJS.DOM.SVGURIReference" -- * "GHCJS.DOM.SVGExternalResourcesRequired" -- -- newtype SVGLinearGradientElement = SVGLinearGradientElement { unSVGLinearGradientElement :: JSVal } instance Eq (SVGLinearGradientElement) where (SVGLinearGradientElement a) == (SVGLinearGradientElement b) = js_eq a b instance PToJSVal SVGLinearGradientElement where pToJSVal = unSVGLinearGradientElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGLinearGradientElement where pFromJSVal = SVGLinearGradientElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGLinearGradientElement where toJSVal = return . unSVGLinearGradientElement {-# INLINE toJSVal #-} instance FromJSVal SVGLinearGradientElement where fromJSVal = return . fmap SVGLinearGradientElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGGradientElement SVGLinearGradientElement instance IsSVGElement SVGLinearGradientElement instance IsElement SVGLinearGradientElement instance IsNode SVGLinearGradientElement instance IsEventTarget SVGLinearGradientElement instance IsSlotable SVGLinearGradientElement instance IsParentNode SVGLinearGradientElement instance IsNonDocumentTypeChildNode SVGLinearGradientElement instance IsDocumentAndElementEventHandlers SVGLinearGradientElement instance IsChildNode SVGLinearGradientElement instance IsAnimatable SVGLinearGradientElement instance IsGlobalEventHandlers SVGLinearGradientElement instance IsElementCSSInlineStyle SVGLinearGradientElement instance IsSVGURIReference SVGLinearGradientElement instance IsSVGExternalResourcesRequired SVGLinearGradientElement instance IsGObject SVGLinearGradientElement where typeGType _ = gTypeSVGLinearGradientElement {-# INLINE typeGType #-} noSVGLinearGradientElement :: Maybe SVGLinearGradientElement noSVGLinearGradientElement = Nothing {-# INLINE noSVGLinearGradientElement #-} foreign import javascript unsafe "window[\"SVGLinearGradientElement\"]" gTypeSVGLinearGradientElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGMPathElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- * "GHCJS.DOM.SVGURIReference" -- * "GHCJS.DOM.SVGExternalResourcesRequired" -- -- newtype SVGMPathElement = SVGMPathElement { unSVGMPathElement :: JSVal } instance Eq (SVGMPathElement) where (SVGMPathElement a) == (SVGMPathElement b) = js_eq a b instance PToJSVal SVGMPathElement where pToJSVal = unSVGMPathElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGMPathElement where pFromJSVal = SVGMPathElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGMPathElement where toJSVal = return . unSVGMPathElement {-# INLINE toJSVal #-} instance FromJSVal SVGMPathElement where fromJSVal = return . fmap SVGMPathElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGElement SVGMPathElement instance IsElement SVGMPathElement instance IsNode SVGMPathElement instance IsEventTarget SVGMPathElement instance IsSlotable SVGMPathElement instance IsParentNode SVGMPathElement instance IsNonDocumentTypeChildNode SVGMPathElement instance IsDocumentAndElementEventHandlers SVGMPathElement instance IsChildNode SVGMPathElement instance IsAnimatable SVGMPathElement instance IsGlobalEventHandlers SVGMPathElement instance IsElementCSSInlineStyle SVGMPathElement instance IsSVGURIReference SVGMPathElement instance IsSVGExternalResourcesRequired SVGMPathElement instance IsGObject SVGMPathElement where typeGType _ = gTypeSVGMPathElement {-# INLINE typeGType #-} noSVGMPathElement :: Maybe SVGMPathElement noSVGMPathElement = Nothing {-# INLINE noSVGMPathElement #-} foreign import javascript unsafe "window[\"SVGMPathElement\"]" gTypeSVGMPathElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGMarkerElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- * "GHCJS.DOM.SVGFitToViewBox" -- * "GHCJS.DOM.SVGExternalResourcesRequired" -- -- newtype SVGMarkerElement = SVGMarkerElement { unSVGMarkerElement :: JSVal } instance Eq (SVGMarkerElement) where (SVGMarkerElement a) == (SVGMarkerElement b) = js_eq a b instance PToJSVal SVGMarkerElement where pToJSVal = unSVGMarkerElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGMarkerElement where pFromJSVal = SVGMarkerElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGMarkerElement where toJSVal = return . unSVGMarkerElement {-# INLINE toJSVal #-} instance FromJSVal SVGMarkerElement where fromJSVal = return . fmap SVGMarkerElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGElement SVGMarkerElement instance IsElement SVGMarkerElement instance IsNode SVGMarkerElement instance IsEventTarget SVGMarkerElement instance IsSlotable SVGMarkerElement instance IsParentNode SVGMarkerElement instance IsNonDocumentTypeChildNode SVGMarkerElement instance IsDocumentAndElementEventHandlers SVGMarkerElement instance IsChildNode SVGMarkerElement instance IsAnimatable SVGMarkerElement instance IsGlobalEventHandlers SVGMarkerElement instance IsElementCSSInlineStyle SVGMarkerElement instance IsSVGFitToViewBox SVGMarkerElement instance IsSVGExternalResourcesRequired SVGMarkerElement instance IsGObject SVGMarkerElement where typeGType _ = gTypeSVGMarkerElement {-# INLINE typeGType #-} noSVGMarkerElement :: Maybe SVGMarkerElement noSVGMarkerElement = Nothing {-# INLINE noSVGMarkerElement #-} foreign import javascript unsafe "window[\"SVGMarkerElement\"]" gTypeSVGMarkerElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGMaskElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- * "GHCJS.DOM.SVGTests" -- * "GHCJS.DOM.SVGExternalResourcesRequired" -- -- newtype SVGMaskElement = SVGMaskElement { unSVGMaskElement :: JSVal } instance Eq (SVGMaskElement) where (SVGMaskElement a) == (SVGMaskElement b) = js_eq a b instance PToJSVal SVGMaskElement where pToJSVal = unSVGMaskElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGMaskElement where pFromJSVal = SVGMaskElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGMaskElement where toJSVal = return . unSVGMaskElement {-# INLINE toJSVal #-} instance FromJSVal SVGMaskElement where fromJSVal = return . fmap SVGMaskElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGElement SVGMaskElement instance IsElement SVGMaskElement instance IsNode SVGMaskElement instance IsEventTarget SVGMaskElement instance IsSlotable SVGMaskElement instance IsParentNode SVGMaskElement instance IsNonDocumentTypeChildNode SVGMaskElement instance IsDocumentAndElementEventHandlers SVGMaskElement instance IsChildNode SVGMaskElement instance IsAnimatable SVGMaskElement instance IsGlobalEventHandlers SVGMaskElement instance IsElementCSSInlineStyle SVGMaskElement instance IsSVGTests SVGMaskElement instance IsSVGExternalResourcesRequired SVGMaskElement instance IsGObject SVGMaskElement where typeGType _ = gTypeSVGMaskElement {-# INLINE typeGType #-} noSVGMaskElement :: Maybe SVGMaskElement noSVGMaskElement = Nothing {-# INLINE noSVGMaskElement #-} foreign import javascript unsafe "window[\"SVGMaskElement\"]" gTypeSVGMaskElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGMatrix". -- -- newtype SVGMatrix = SVGMatrix { unSVGMatrix :: JSVal } instance Eq (SVGMatrix) where (SVGMatrix a) == (SVGMatrix b) = js_eq a b instance PToJSVal SVGMatrix where pToJSVal = unSVGMatrix {-# INLINE pToJSVal #-} instance PFromJSVal SVGMatrix where pFromJSVal = SVGMatrix {-# INLINE pFromJSVal #-} instance ToJSVal SVGMatrix where toJSVal = return . unSVGMatrix {-# INLINE toJSVal #-} instance FromJSVal SVGMatrix where fromJSVal = return . fmap SVGMatrix . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject SVGMatrix where typeGType _ = gTypeSVGMatrix {-# INLINE typeGType #-} noSVGMatrix :: Maybe SVGMatrix noSVGMatrix = Nothing {-# INLINE noSVGMatrix #-} foreign import javascript unsafe "window[\"SVGMatrix\"]" gTypeSVGMatrix :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGMetadataElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype SVGMetadataElement = SVGMetadataElement { unSVGMetadataElement :: JSVal } instance Eq (SVGMetadataElement) where (SVGMetadataElement a) == (SVGMetadataElement b) = js_eq a b instance PToJSVal SVGMetadataElement where pToJSVal = unSVGMetadataElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGMetadataElement where pFromJSVal = SVGMetadataElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGMetadataElement where toJSVal = return . unSVGMetadataElement {-# INLINE toJSVal #-} instance FromJSVal SVGMetadataElement where fromJSVal = return . fmap SVGMetadataElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGElement SVGMetadataElement instance IsElement SVGMetadataElement instance IsNode SVGMetadataElement instance IsEventTarget SVGMetadataElement instance IsSlotable SVGMetadataElement instance IsParentNode SVGMetadataElement instance IsNonDocumentTypeChildNode SVGMetadataElement instance IsDocumentAndElementEventHandlers SVGMetadataElement instance IsChildNode SVGMetadataElement instance IsAnimatable SVGMetadataElement instance IsGlobalEventHandlers SVGMetadataElement instance IsElementCSSInlineStyle SVGMetadataElement instance IsGObject SVGMetadataElement where typeGType _ = gTypeSVGMetadataElement {-# INLINE typeGType #-} noSVGMetadataElement :: Maybe SVGMetadataElement noSVGMetadataElement = Nothing {-# INLINE noSVGMetadataElement #-} foreign import javascript unsafe "window[\"SVGMetadataElement\"]" gTypeSVGMetadataElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGMissingGlyphElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype SVGMissingGlyphElement = SVGMissingGlyphElement { unSVGMissingGlyphElement :: JSVal } instance Eq (SVGMissingGlyphElement) where (SVGMissingGlyphElement a) == (SVGMissingGlyphElement b) = js_eq a b instance PToJSVal SVGMissingGlyphElement where pToJSVal = unSVGMissingGlyphElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGMissingGlyphElement where pFromJSVal = SVGMissingGlyphElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGMissingGlyphElement where toJSVal = return . unSVGMissingGlyphElement {-# INLINE toJSVal #-} instance FromJSVal SVGMissingGlyphElement where fromJSVal = return . fmap SVGMissingGlyphElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGElement SVGMissingGlyphElement instance IsElement SVGMissingGlyphElement instance IsNode SVGMissingGlyphElement instance IsEventTarget SVGMissingGlyphElement instance IsSlotable SVGMissingGlyphElement instance IsParentNode SVGMissingGlyphElement instance IsNonDocumentTypeChildNode SVGMissingGlyphElement instance IsDocumentAndElementEventHandlers SVGMissingGlyphElement instance IsChildNode SVGMissingGlyphElement instance IsAnimatable SVGMissingGlyphElement instance IsGlobalEventHandlers SVGMissingGlyphElement instance IsElementCSSInlineStyle SVGMissingGlyphElement instance IsGObject SVGMissingGlyphElement where typeGType _ = gTypeSVGMissingGlyphElement {-# INLINE typeGType #-} noSVGMissingGlyphElement :: Maybe SVGMissingGlyphElement noSVGMissingGlyphElement = Nothing {-# INLINE noSVGMissingGlyphElement #-} foreign import javascript unsafe "window[\"SVGMissingGlyphElement\"]" gTypeSVGMissingGlyphElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGNumber". -- -- newtype SVGNumber = SVGNumber { unSVGNumber :: JSVal } instance Eq (SVGNumber) where (SVGNumber a) == (SVGNumber b) = js_eq a b instance PToJSVal SVGNumber where pToJSVal = unSVGNumber {-# INLINE pToJSVal #-} instance PFromJSVal SVGNumber where pFromJSVal = SVGNumber {-# INLINE pFromJSVal #-} instance ToJSVal SVGNumber where toJSVal = return . unSVGNumber {-# INLINE toJSVal #-} instance FromJSVal SVGNumber where fromJSVal = return . fmap SVGNumber . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject SVGNumber where typeGType _ = gTypeSVGNumber {-# INLINE typeGType #-} noSVGNumber :: Maybe SVGNumber noSVGNumber = Nothing {-# INLINE noSVGNumber #-} foreign import javascript unsafe "window[\"SVGNumber\"]" gTypeSVGNumber :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGNumberList". -- -- newtype SVGNumberList = SVGNumberList { unSVGNumberList :: JSVal } instance Eq (SVGNumberList) where (SVGNumberList a) == (SVGNumberList b) = js_eq a b instance PToJSVal SVGNumberList where pToJSVal = unSVGNumberList {-# INLINE pToJSVal #-} instance PFromJSVal SVGNumberList where pFromJSVal = SVGNumberList {-# INLINE pFromJSVal #-} instance ToJSVal SVGNumberList where toJSVal = return . unSVGNumberList {-# INLINE toJSVal #-} instance FromJSVal SVGNumberList where fromJSVal = return . fmap SVGNumberList . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject SVGNumberList where typeGType _ = gTypeSVGNumberList {-# INLINE typeGType #-} noSVGNumberList :: Maybe SVGNumberList noSVGNumberList = Nothing {-# INLINE noSVGNumberList #-} foreign import javascript unsafe "window[\"SVGNumberList\"]" gTypeSVGNumberList :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGPathElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGGraphicsElement" -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- * "GHCJS.DOM.SVGTests" -- * "GHCJS.DOM.SVGExternalResourcesRequired" -- -- newtype SVGPathElement = SVGPathElement { unSVGPathElement :: JSVal } instance Eq (SVGPathElement) where (SVGPathElement a) == (SVGPathElement b) = js_eq a b instance PToJSVal SVGPathElement where pToJSVal = unSVGPathElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGPathElement where pFromJSVal = SVGPathElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGPathElement where toJSVal = return . unSVGPathElement {-# INLINE toJSVal #-} instance FromJSVal SVGPathElement where fromJSVal = return . fmap SVGPathElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGGraphicsElement SVGPathElement instance IsSVGElement SVGPathElement instance IsElement SVGPathElement instance IsNode SVGPathElement instance IsEventTarget SVGPathElement instance IsSlotable SVGPathElement instance IsParentNode SVGPathElement instance IsNonDocumentTypeChildNode SVGPathElement instance IsDocumentAndElementEventHandlers SVGPathElement instance IsChildNode SVGPathElement instance IsAnimatable SVGPathElement instance IsGlobalEventHandlers SVGPathElement instance IsElementCSSInlineStyle SVGPathElement instance IsSVGTests SVGPathElement instance IsSVGExternalResourcesRequired SVGPathElement instance IsGObject SVGPathElement where typeGType _ = gTypeSVGPathElement {-# INLINE typeGType #-} noSVGPathElement :: Maybe SVGPathElement noSVGPathElement = Nothing {-# INLINE noSVGPathElement #-} foreign import javascript unsafe "window[\"SVGPathElement\"]" gTypeSVGPathElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGPathSeg". -- -- newtype SVGPathSeg = SVGPathSeg { unSVGPathSeg :: JSVal } instance Eq (SVGPathSeg) where (SVGPathSeg a) == (SVGPathSeg b) = js_eq a b instance PToJSVal SVGPathSeg where pToJSVal = unSVGPathSeg {-# INLINE pToJSVal #-} instance PFromJSVal SVGPathSeg where pFromJSVal = SVGPathSeg {-# INLINE pFromJSVal #-} instance ToJSVal SVGPathSeg where toJSVal = return . unSVGPathSeg {-# INLINE toJSVal #-} instance FromJSVal SVGPathSeg where fromJSVal = return . fmap SVGPathSeg . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsGObject o) => IsSVGPathSeg o toSVGPathSeg :: IsSVGPathSeg o => o -> SVGPathSeg toSVGPathSeg = SVGPathSeg . coerce instance IsSVGPathSeg SVGPathSeg instance IsGObject SVGPathSeg where typeGType _ = gTypeSVGPathSeg {-# INLINE typeGType #-} noSVGPathSeg :: Maybe SVGPathSeg noSVGPathSeg = Nothing {-# INLINE noSVGPathSeg #-} foreign import javascript unsafe "window[\"SVGPathSeg\"]" gTypeSVGPathSeg :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGPathSegArcAbs". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGPathSeg" -- -- newtype SVGPathSegArcAbs = SVGPathSegArcAbs { unSVGPathSegArcAbs :: JSVal } instance Eq (SVGPathSegArcAbs) where (SVGPathSegArcAbs a) == (SVGPathSegArcAbs b) = js_eq a b instance PToJSVal SVGPathSegArcAbs where pToJSVal = unSVGPathSegArcAbs {-# INLINE pToJSVal #-} instance PFromJSVal SVGPathSegArcAbs where pFromJSVal = SVGPathSegArcAbs {-# INLINE pFromJSVal #-} instance ToJSVal SVGPathSegArcAbs where toJSVal = return . unSVGPathSegArcAbs {-# INLINE toJSVal #-} instance FromJSVal SVGPathSegArcAbs where fromJSVal = return . fmap SVGPathSegArcAbs . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGPathSeg SVGPathSegArcAbs instance IsGObject SVGPathSegArcAbs where typeGType _ = gTypeSVGPathSegArcAbs {-# INLINE typeGType #-} noSVGPathSegArcAbs :: Maybe SVGPathSegArcAbs noSVGPathSegArcAbs = Nothing {-# INLINE noSVGPathSegArcAbs #-} foreign import javascript unsafe "window[\"SVGPathSegArcAbs\"]" gTypeSVGPathSegArcAbs :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGPathSegArcRel". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGPathSeg" -- -- newtype SVGPathSegArcRel = SVGPathSegArcRel { unSVGPathSegArcRel :: JSVal } instance Eq (SVGPathSegArcRel) where (SVGPathSegArcRel a) == (SVGPathSegArcRel b) = js_eq a b instance PToJSVal SVGPathSegArcRel where pToJSVal = unSVGPathSegArcRel {-# INLINE pToJSVal #-} instance PFromJSVal SVGPathSegArcRel where pFromJSVal = SVGPathSegArcRel {-# INLINE pFromJSVal #-} instance ToJSVal SVGPathSegArcRel where toJSVal = return . unSVGPathSegArcRel {-# INLINE toJSVal #-} instance FromJSVal SVGPathSegArcRel where fromJSVal = return . fmap SVGPathSegArcRel . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGPathSeg SVGPathSegArcRel instance IsGObject SVGPathSegArcRel where typeGType _ = gTypeSVGPathSegArcRel {-# INLINE typeGType #-} noSVGPathSegArcRel :: Maybe SVGPathSegArcRel noSVGPathSegArcRel = Nothing {-# INLINE noSVGPathSegArcRel #-} foreign import javascript unsafe "window[\"SVGPathSegArcRel\"]" gTypeSVGPathSegArcRel :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGPathSegClosePath". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGPathSeg" -- -- newtype SVGPathSegClosePath = SVGPathSegClosePath { unSVGPathSegClosePath :: JSVal } instance Eq (SVGPathSegClosePath) where (SVGPathSegClosePath a) == (SVGPathSegClosePath b) = js_eq a b instance PToJSVal SVGPathSegClosePath where pToJSVal = unSVGPathSegClosePath {-# INLINE pToJSVal #-} instance PFromJSVal SVGPathSegClosePath where pFromJSVal = SVGPathSegClosePath {-# INLINE pFromJSVal #-} instance ToJSVal SVGPathSegClosePath where toJSVal = return . unSVGPathSegClosePath {-# INLINE toJSVal #-} instance FromJSVal SVGPathSegClosePath where fromJSVal = return . fmap SVGPathSegClosePath . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGPathSeg SVGPathSegClosePath instance IsGObject SVGPathSegClosePath where typeGType _ = gTypeSVGPathSegClosePath {-# INLINE typeGType #-} noSVGPathSegClosePath :: Maybe SVGPathSegClosePath noSVGPathSegClosePath = Nothing {-# INLINE noSVGPathSegClosePath #-} foreign import javascript unsafe "window[\"SVGPathSegClosePath\"]" gTypeSVGPathSegClosePath :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGPathSegCurvetoCubicAbs". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGPathSeg" -- -- newtype SVGPathSegCurvetoCubicAbs = SVGPathSegCurvetoCubicAbs { unSVGPathSegCurvetoCubicAbs :: JSVal } instance Eq (SVGPathSegCurvetoCubicAbs) where (SVGPathSegCurvetoCubicAbs a) == (SVGPathSegCurvetoCubicAbs b) = js_eq a b instance PToJSVal SVGPathSegCurvetoCubicAbs where pToJSVal = unSVGPathSegCurvetoCubicAbs {-# INLINE pToJSVal #-} instance PFromJSVal SVGPathSegCurvetoCubicAbs where pFromJSVal = SVGPathSegCurvetoCubicAbs {-# INLINE pFromJSVal #-} instance ToJSVal SVGPathSegCurvetoCubicAbs where toJSVal = return . unSVGPathSegCurvetoCubicAbs {-# INLINE toJSVal #-} instance FromJSVal SVGPathSegCurvetoCubicAbs where fromJSVal = return . fmap SVGPathSegCurvetoCubicAbs . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGPathSeg SVGPathSegCurvetoCubicAbs instance IsGObject SVGPathSegCurvetoCubicAbs where typeGType _ = gTypeSVGPathSegCurvetoCubicAbs {-# INLINE typeGType #-} noSVGPathSegCurvetoCubicAbs :: Maybe SVGPathSegCurvetoCubicAbs noSVGPathSegCurvetoCubicAbs = Nothing {-# INLINE noSVGPathSegCurvetoCubicAbs #-} foreign import javascript unsafe "window[\"SVGPathSegCurvetoCubicAbs\"]" gTypeSVGPathSegCurvetoCubicAbs :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGPathSegCurvetoCubicRel". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGPathSeg" -- -- newtype SVGPathSegCurvetoCubicRel = SVGPathSegCurvetoCubicRel { unSVGPathSegCurvetoCubicRel :: JSVal } instance Eq (SVGPathSegCurvetoCubicRel) where (SVGPathSegCurvetoCubicRel a) == (SVGPathSegCurvetoCubicRel b) = js_eq a b instance PToJSVal SVGPathSegCurvetoCubicRel where pToJSVal = unSVGPathSegCurvetoCubicRel {-# INLINE pToJSVal #-} instance PFromJSVal SVGPathSegCurvetoCubicRel where pFromJSVal = SVGPathSegCurvetoCubicRel {-# INLINE pFromJSVal #-} instance ToJSVal SVGPathSegCurvetoCubicRel where toJSVal = return . unSVGPathSegCurvetoCubicRel {-# INLINE toJSVal #-} instance FromJSVal SVGPathSegCurvetoCubicRel where fromJSVal = return . fmap SVGPathSegCurvetoCubicRel . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGPathSeg SVGPathSegCurvetoCubicRel instance IsGObject SVGPathSegCurvetoCubicRel where typeGType _ = gTypeSVGPathSegCurvetoCubicRel {-# INLINE typeGType #-} noSVGPathSegCurvetoCubicRel :: Maybe SVGPathSegCurvetoCubicRel noSVGPathSegCurvetoCubicRel = Nothing {-# INLINE noSVGPathSegCurvetoCubicRel #-} foreign import javascript unsafe "window[\"SVGPathSegCurvetoCubicRel\"]" gTypeSVGPathSegCurvetoCubicRel :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGPathSegCurvetoCubicSmoothAbs". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGPathSeg" -- -- newtype SVGPathSegCurvetoCubicSmoothAbs = SVGPathSegCurvetoCubicSmoothAbs { unSVGPathSegCurvetoCubicSmoothAbs :: JSVal } instance Eq (SVGPathSegCurvetoCubicSmoothAbs) where (SVGPathSegCurvetoCubicSmoothAbs a) == (SVGPathSegCurvetoCubicSmoothAbs b) = js_eq a b instance PToJSVal SVGPathSegCurvetoCubicSmoothAbs where pToJSVal = unSVGPathSegCurvetoCubicSmoothAbs {-# INLINE pToJSVal #-} instance PFromJSVal SVGPathSegCurvetoCubicSmoothAbs where pFromJSVal = SVGPathSegCurvetoCubicSmoothAbs {-# INLINE pFromJSVal #-} instance ToJSVal SVGPathSegCurvetoCubicSmoothAbs where toJSVal = return . unSVGPathSegCurvetoCubicSmoothAbs {-# INLINE toJSVal #-} instance FromJSVal SVGPathSegCurvetoCubicSmoothAbs where fromJSVal = return . fmap SVGPathSegCurvetoCubicSmoothAbs . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGPathSeg SVGPathSegCurvetoCubicSmoothAbs instance IsGObject SVGPathSegCurvetoCubicSmoothAbs where typeGType _ = gTypeSVGPathSegCurvetoCubicSmoothAbs {-# INLINE typeGType #-} noSVGPathSegCurvetoCubicSmoothAbs :: Maybe SVGPathSegCurvetoCubicSmoothAbs noSVGPathSegCurvetoCubicSmoothAbs = Nothing {-# INLINE noSVGPathSegCurvetoCubicSmoothAbs #-} foreign import javascript unsafe "window[\"SVGPathSegCurvetoCubicSmoothAbs\"]" gTypeSVGPathSegCurvetoCubicSmoothAbs :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGPathSegCurvetoCubicSmoothRel". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGPathSeg" -- -- newtype SVGPathSegCurvetoCubicSmoothRel = SVGPathSegCurvetoCubicSmoothRel { unSVGPathSegCurvetoCubicSmoothRel :: JSVal } instance Eq (SVGPathSegCurvetoCubicSmoothRel) where (SVGPathSegCurvetoCubicSmoothRel a) == (SVGPathSegCurvetoCubicSmoothRel b) = js_eq a b instance PToJSVal SVGPathSegCurvetoCubicSmoothRel where pToJSVal = unSVGPathSegCurvetoCubicSmoothRel {-# INLINE pToJSVal #-} instance PFromJSVal SVGPathSegCurvetoCubicSmoothRel where pFromJSVal = SVGPathSegCurvetoCubicSmoothRel {-# INLINE pFromJSVal #-} instance ToJSVal SVGPathSegCurvetoCubicSmoothRel where toJSVal = return . unSVGPathSegCurvetoCubicSmoothRel {-# INLINE toJSVal #-} instance FromJSVal SVGPathSegCurvetoCubicSmoothRel where fromJSVal = return . fmap SVGPathSegCurvetoCubicSmoothRel . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGPathSeg SVGPathSegCurvetoCubicSmoothRel instance IsGObject SVGPathSegCurvetoCubicSmoothRel where typeGType _ = gTypeSVGPathSegCurvetoCubicSmoothRel {-# INLINE typeGType #-} noSVGPathSegCurvetoCubicSmoothRel :: Maybe SVGPathSegCurvetoCubicSmoothRel noSVGPathSegCurvetoCubicSmoothRel = Nothing {-# INLINE noSVGPathSegCurvetoCubicSmoothRel #-} foreign import javascript unsafe "window[\"SVGPathSegCurvetoCubicSmoothRel\"]" gTypeSVGPathSegCurvetoCubicSmoothRel :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGPathSegCurvetoQuadraticAbs". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGPathSeg" -- -- newtype SVGPathSegCurvetoQuadraticAbs = SVGPathSegCurvetoQuadraticAbs { unSVGPathSegCurvetoQuadraticAbs :: JSVal } instance Eq (SVGPathSegCurvetoQuadraticAbs) where (SVGPathSegCurvetoQuadraticAbs a) == (SVGPathSegCurvetoQuadraticAbs b) = js_eq a b instance PToJSVal SVGPathSegCurvetoQuadraticAbs where pToJSVal = unSVGPathSegCurvetoQuadraticAbs {-# INLINE pToJSVal #-} instance PFromJSVal SVGPathSegCurvetoQuadraticAbs where pFromJSVal = SVGPathSegCurvetoQuadraticAbs {-# INLINE pFromJSVal #-} instance ToJSVal SVGPathSegCurvetoQuadraticAbs where toJSVal = return . unSVGPathSegCurvetoQuadraticAbs {-# INLINE toJSVal #-} instance FromJSVal SVGPathSegCurvetoQuadraticAbs where fromJSVal = return . fmap SVGPathSegCurvetoQuadraticAbs . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGPathSeg SVGPathSegCurvetoQuadraticAbs instance IsGObject SVGPathSegCurvetoQuadraticAbs where typeGType _ = gTypeSVGPathSegCurvetoQuadraticAbs {-# INLINE typeGType #-} noSVGPathSegCurvetoQuadraticAbs :: Maybe SVGPathSegCurvetoQuadraticAbs noSVGPathSegCurvetoQuadraticAbs = Nothing {-# INLINE noSVGPathSegCurvetoQuadraticAbs #-} foreign import javascript unsafe "window[\"SVGPathSegCurvetoQuadraticAbs\"]" gTypeSVGPathSegCurvetoQuadraticAbs :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGPathSegCurvetoQuadraticRel". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGPathSeg" -- -- newtype SVGPathSegCurvetoQuadraticRel = SVGPathSegCurvetoQuadraticRel { unSVGPathSegCurvetoQuadraticRel :: JSVal } instance Eq (SVGPathSegCurvetoQuadraticRel) where (SVGPathSegCurvetoQuadraticRel a) == (SVGPathSegCurvetoQuadraticRel b) = js_eq a b instance PToJSVal SVGPathSegCurvetoQuadraticRel where pToJSVal = unSVGPathSegCurvetoQuadraticRel {-# INLINE pToJSVal #-} instance PFromJSVal SVGPathSegCurvetoQuadraticRel where pFromJSVal = SVGPathSegCurvetoQuadraticRel {-# INLINE pFromJSVal #-} instance ToJSVal SVGPathSegCurvetoQuadraticRel where toJSVal = return . unSVGPathSegCurvetoQuadraticRel {-# INLINE toJSVal #-} instance FromJSVal SVGPathSegCurvetoQuadraticRel where fromJSVal = return . fmap SVGPathSegCurvetoQuadraticRel . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGPathSeg SVGPathSegCurvetoQuadraticRel instance IsGObject SVGPathSegCurvetoQuadraticRel where typeGType _ = gTypeSVGPathSegCurvetoQuadraticRel {-# INLINE typeGType #-} noSVGPathSegCurvetoQuadraticRel :: Maybe SVGPathSegCurvetoQuadraticRel noSVGPathSegCurvetoQuadraticRel = Nothing {-# INLINE noSVGPathSegCurvetoQuadraticRel #-} foreign import javascript unsafe "window[\"SVGPathSegCurvetoQuadraticRel\"]" gTypeSVGPathSegCurvetoQuadraticRel :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGPathSegCurvetoQuadraticSmoothAbs". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGPathSeg" -- -- newtype SVGPathSegCurvetoQuadraticSmoothAbs = SVGPathSegCurvetoQuadraticSmoothAbs { unSVGPathSegCurvetoQuadraticSmoothAbs :: JSVal } instance Eq (SVGPathSegCurvetoQuadraticSmoothAbs) where (SVGPathSegCurvetoQuadraticSmoothAbs a) == (SVGPathSegCurvetoQuadraticSmoothAbs b) = js_eq a b instance PToJSVal SVGPathSegCurvetoQuadraticSmoothAbs where pToJSVal = unSVGPathSegCurvetoQuadraticSmoothAbs {-# INLINE pToJSVal #-} instance PFromJSVal SVGPathSegCurvetoQuadraticSmoothAbs where pFromJSVal = SVGPathSegCurvetoQuadraticSmoothAbs {-# INLINE pFromJSVal #-} instance ToJSVal SVGPathSegCurvetoQuadraticSmoothAbs where toJSVal = return . unSVGPathSegCurvetoQuadraticSmoothAbs {-# INLINE toJSVal #-} instance FromJSVal SVGPathSegCurvetoQuadraticSmoothAbs where fromJSVal = return . fmap SVGPathSegCurvetoQuadraticSmoothAbs . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGPathSeg SVGPathSegCurvetoQuadraticSmoothAbs instance IsGObject SVGPathSegCurvetoQuadraticSmoothAbs where typeGType _ = gTypeSVGPathSegCurvetoQuadraticSmoothAbs {-# INLINE typeGType #-} noSVGPathSegCurvetoQuadraticSmoothAbs :: Maybe SVGPathSegCurvetoQuadraticSmoothAbs noSVGPathSegCurvetoQuadraticSmoothAbs = Nothing {-# INLINE noSVGPathSegCurvetoQuadraticSmoothAbs #-} foreign import javascript unsafe "window[\"SVGPathSegCurvetoQuadraticSmoothAbs\"]" gTypeSVGPathSegCurvetoQuadraticSmoothAbs :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGPathSegCurvetoQuadraticSmoothRel". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGPathSeg" -- -- newtype SVGPathSegCurvetoQuadraticSmoothRel = SVGPathSegCurvetoQuadraticSmoothRel { unSVGPathSegCurvetoQuadraticSmoothRel :: JSVal } instance Eq (SVGPathSegCurvetoQuadraticSmoothRel) where (SVGPathSegCurvetoQuadraticSmoothRel a) == (SVGPathSegCurvetoQuadraticSmoothRel b) = js_eq a b instance PToJSVal SVGPathSegCurvetoQuadraticSmoothRel where pToJSVal = unSVGPathSegCurvetoQuadraticSmoothRel {-# INLINE pToJSVal #-} instance PFromJSVal SVGPathSegCurvetoQuadraticSmoothRel where pFromJSVal = SVGPathSegCurvetoQuadraticSmoothRel {-# INLINE pFromJSVal #-} instance ToJSVal SVGPathSegCurvetoQuadraticSmoothRel where toJSVal = return . unSVGPathSegCurvetoQuadraticSmoothRel {-# INLINE toJSVal #-} instance FromJSVal SVGPathSegCurvetoQuadraticSmoothRel where fromJSVal = return . fmap SVGPathSegCurvetoQuadraticSmoothRel . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGPathSeg SVGPathSegCurvetoQuadraticSmoothRel instance IsGObject SVGPathSegCurvetoQuadraticSmoothRel where typeGType _ = gTypeSVGPathSegCurvetoQuadraticSmoothRel {-# INLINE typeGType #-} noSVGPathSegCurvetoQuadraticSmoothRel :: Maybe SVGPathSegCurvetoQuadraticSmoothRel noSVGPathSegCurvetoQuadraticSmoothRel = Nothing {-# INLINE noSVGPathSegCurvetoQuadraticSmoothRel #-} foreign import javascript unsafe "window[\"SVGPathSegCurvetoQuadraticSmoothRel\"]" gTypeSVGPathSegCurvetoQuadraticSmoothRel :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGPathSegLinetoAbs". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGPathSeg" -- -- newtype SVGPathSegLinetoAbs = SVGPathSegLinetoAbs { unSVGPathSegLinetoAbs :: JSVal } instance Eq (SVGPathSegLinetoAbs) where (SVGPathSegLinetoAbs a) == (SVGPathSegLinetoAbs b) = js_eq a b instance PToJSVal SVGPathSegLinetoAbs where pToJSVal = unSVGPathSegLinetoAbs {-# INLINE pToJSVal #-} instance PFromJSVal SVGPathSegLinetoAbs where pFromJSVal = SVGPathSegLinetoAbs {-# INLINE pFromJSVal #-} instance ToJSVal SVGPathSegLinetoAbs where toJSVal = return . unSVGPathSegLinetoAbs {-# INLINE toJSVal #-} instance FromJSVal SVGPathSegLinetoAbs where fromJSVal = return . fmap SVGPathSegLinetoAbs . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGPathSeg SVGPathSegLinetoAbs instance IsGObject SVGPathSegLinetoAbs where typeGType _ = gTypeSVGPathSegLinetoAbs {-# INLINE typeGType #-} noSVGPathSegLinetoAbs :: Maybe SVGPathSegLinetoAbs noSVGPathSegLinetoAbs = Nothing {-# INLINE noSVGPathSegLinetoAbs #-} foreign import javascript unsafe "window[\"SVGPathSegLinetoAbs\"]" gTypeSVGPathSegLinetoAbs :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGPathSegLinetoHorizontalAbs". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGPathSeg" -- -- newtype SVGPathSegLinetoHorizontalAbs = SVGPathSegLinetoHorizontalAbs { unSVGPathSegLinetoHorizontalAbs :: JSVal } instance Eq (SVGPathSegLinetoHorizontalAbs) where (SVGPathSegLinetoHorizontalAbs a) == (SVGPathSegLinetoHorizontalAbs b) = js_eq a b instance PToJSVal SVGPathSegLinetoHorizontalAbs where pToJSVal = unSVGPathSegLinetoHorizontalAbs {-# INLINE pToJSVal #-} instance PFromJSVal SVGPathSegLinetoHorizontalAbs where pFromJSVal = SVGPathSegLinetoHorizontalAbs {-# INLINE pFromJSVal #-} instance ToJSVal SVGPathSegLinetoHorizontalAbs where toJSVal = return . unSVGPathSegLinetoHorizontalAbs {-# INLINE toJSVal #-} instance FromJSVal SVGPathSegLinetoHorizontalAbs where fromJSVal = return . fmap SVGPathSegLinetoHorizontalAbs . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGPathSeg SVGPathSegLinetoHorizontalAbs instance IsGObject SVGPathSegLinetoHorizontalAbs where typeGType _ = gTypeSVGPathSegLinetoHorizontalAbs {-# INLINE typeGType #-} noSVGPathSegLinetoHorizontalAbs :: Maybe SVGPathSegLinetoHorizontalAbs noSVGPathSegLinetoHorizontalAbs = Nothing {-# INLINE noSVGPathSegLinetoHorizontalAbs #-} foreign import javascript unsafe "window[\"SVGPathSegLinetoHorizontalAbs\"]" gTypeSVGPathSegLinetoHorizontalAbs :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGPathSegLinetoHorizontalRel". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGPathSeg" -- -- newtype SVGPathSegLinetoHorizontalRel = SVGPathSegLinetoHorizontalRel { unSVGPathSegLinetoHorizontalRel :: JSVal } instance Eq (SVGPathSegLinetoHorizontalRel) where (SVGPathSegLinetoHorizontalRel a) == (SVGPathSegLinetoHorizontalRel b) = js_eq a b instance PToJSVal SVGPathSegLinetoHorizontalRel where pToJSVal = unSVGPathSegLinetoHorizontalRel {-# INLINE pToJSVal #-} instance PFromJSVal SVGPathSegLinetoHorizontalRel where pFromJSVal = SVGPathSegLinetoHorizontalRel {-# INLINE pFromJSVal #-} instance ToJSVal SVGPathSegLinetoHorizontalRel where toJSVal = return . unSVGPathSegLinetoHorizontalRel {-# INLINE toJSVal #-} instance FromJSVal SVGPathSegLinetoHorizontalRel where fromJSVal = return . fmap SVGPathSegLinetoHorizontalRel . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGPathSeg SVGPathSegLinetoHorizontalRel instance IsGObject SVGPathSegLinetoHorizontalRel where typeGType _ = gTypeSVGPathSegLinetoHorizontalRel {-# INLINE typeGType #-} noSVGPathSegLinetoHorizontalRel :: Maybe SVGPathSegLinetoHorizontalRel noSVGPathSegLinetoHorizontalRel = Nothing {-# INLINE noSVGPathSegLinetoHorizontalRel #-} foreign import javascript unsafe "window[\"SVGPathSegLinetoHorizontalRel\"]" gTypeSVGPathSegLinetoHorizontalRel :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGPathSegLinetoRel". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGPathSeg" -- -- newtype SVGPathSegLinetoRel = SVGPathSegLinetoRel { unSVGPathSegLinetoRel :: JSVal } instance Eq (SVGPathSegLinetoRel) where (SVGPathSegLinetoRel a) == (SVGPathSegLinetoRel b) = js_eq a b instance PToJSVal SVGPathSegLinetoRel where pToJSVal = unSVGPathSegLinetoRel {-# INLINE pToJSVal #-} instance PFromJSVal SVGPathSegLinetoRel where pFromJSVal = SVGPathSegLinetoRel {-# INLINE pFromJSVal #-} instance ToJSVal SVGPathSegLinetoRel where toJSVal = return . unSVGPathSegLinetoRel {-# INLINE toJSVal #-} instance FromJSVal SVGPathSegLinetoRel where fromJSVal = return . fmap SVGPathSegLinetoRel . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGPathSeg SVGPathSegLinetoRel instance IsGObject SVGPathSegLinetoRel where typeGType _ = gTypeSVGPathSegLinetoRel {-# INLINE typeGType #-} noSVGPathSegLinetoRel :: Maybe SVGPathSegLinetoRel noSVGPathSegLinetoRel = Nothing {-# INLINE noSVGPathSegLinetoRel #-} foreign import javascript unsafe "window[\"SVGPathSegLinetoRel\"]" gTypeSVGPathSegLinetoRel :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGPathSegLinetoVerticalAbs". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGPathSeg" -- -- newtype SVGPathSegLinetoVerticalAbs = SVGPathSegLinetoVerticalAbs { unSVGPathSegLinetoVerticalAbs :: JSVal } instance Eq (SVGPathSegLinetoVerticalAbs) where (SVGPathSegLinetoVerticalAbs a) == (SVGPathSegLinetoVerticalAbs b) = js_eq a b instance PToJSVal SVGPathSegLinetoVerticalAbs where pToJSVal = unSVGPathSegLinetoVerticalAbs {-# INLINE pToJSVal #-} instance PFromJSVal SVGPathSegLinetoVerticalAbs where pFromJSVal = SVGPathSegLinetoVerticalAbs {-# INLINE pFromJSVal #-} instance ToJSVal SVGPathSegLinetoVerticalAbs where toJSVal = return . unSVGPathSegLinetoVerticalAbs {-# INLINE toJSVal #-} instance FromJSVal SVGPathSegLinetoVerticalAbs where fromJSVal = return . fmap SVGPathSegLinetoVerticalAbs . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGPathSeg SVGPathSegLinetoVerticalAbs instance IsGObject SVGPathSegLinetoVerticalAbs where typeGType _ = gTypeSVGPathSegLinetoVerticalAbs {-# INLINE typeGType #-} noSVGPathSegLinetoVerticalAbs :: Maybe SVGPathSegLinetoVerticalAbs noSVGPathSegLinetoVerticalAbs = Nothing {-# INLINE noSVGPathSegLinetoVerticalAbs #-} foreign import javascript unsafe "window[\"SVGPathSegLinetoVerticalAbs\"]" gTypeSVGPathSegLinetoVerticalAbs :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGPathSegLinetoVerticalRel". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGPathSeg" -- -- newtype SVGPathSegLinetoVerticalRel = SVGPathSegLinetoVerticalRel { unSVGPathSegLinetoVerticalRel :: JSVal } instance Eq (SVGPathSegLinetoVerticalRel) where (SVGPathSegLinetoVerticalRel a) == (SVGPathSegLinetoVerticalRel b) = js_eq a b instance PToJSVal SVGPathSegLinetoVerticalRel where pToJSVal = unSVGPathSegLinetoVerticalRel {-# INLINE pToJSVal #-} instance PFromJSVal SVGPathSegLinetoVerticalRel where pFromJSVal = SVGPathSegLinetoVerticalRel {-# INLINE pFromJSVal #-} instance ToJSVal SVGPathSegLinetoVerticalRel where toJSVal = return . unSVGPathSegLinetoVerticalRel {-# INLINE toJSVal #-} instance FromJSVal SVGPathSegLinetoVerticalRel where fromJSVal = return . fmap SVGPathSegLinetoVerticalRel . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGPathSeg SVGPathSegLinetoVerticalRel instance IsGObject SVGPathSegLinetoVerticalRel where typeGType _ = gTypeSVGPathSegLinetoVerticalRel {-# INLINE typeGType #-} noSVGPathSegLinetoVerticalRel :: Maybe SVGPathSegLinetoVerticalRel noSVGPathSegLinetoVerticalRel = Nothing {-# INLINE noSVGPathSegLinetoVerticalRel #-} foreign import javascript unsafe "window[\"SVGPathSegLinetoVerticalRel\"]" gTypeSVGPathSegLinetoVerticalRel :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGPathSegList". -- -- newtype SVGPathSegList = SVGPathSegList { unSVGPathSegList :: JSVal } instance Eq (SVGPathSegList) where (SVGPathSegList a) == (SVGPathSegList b) = js_eq a b instance PToJSVal SVGPathSegList where pToJSVal = unSVGPathSegList {-# INLINE pToJSVal #-} instance PFromJSVal SVGPathSegList where pFromJSVal = SVGPathSegList {-# INLINE pFromJSVal #-} instance ToJSVal SVGPathSegList where toJSVal = return . unSVGPathSegList {-# INLINE toJSVal #-} instance FromJSVal SVGPathSegList where fromJSVal = return . fmap SVGPathSegList . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject SVGPathSegList where typeGType _ = gTypeSVGPathSegList {-# INLINE typeGType #-} noSVGPathSegList :: Maybe SVGPathSegList noSVGPathSegList = Nothing {-# INLINE noSVGPathSegList #-} foreign import javascript unsafe "window[\"SVGPathSegList\"]" gTypeSVGPathSegList :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGPathSegMovetoAbs". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGPathSeg" -- -- newtype SVGPathSegMovetoAbs = SVGPathSegMovetoAbs { unSVGPathSegMovetoAbs :: JSVal } instance Eq (SVGPathSegMovetoAbs) where (SVGPathSegMovetoAbs a) == (SVGPathSegMovetoAbs b) = js_eq a b instance PToJSVal SVGPathSegMovetoAbs where pToJSVal = unSVGPathSegMovetoAbs {-# INLINE pToJSVal #-} instance PFromJSVal SVGPathSegMovetoAbs where pFromJSVal = SVGPathSegMovetoAbs {-# INLINE pFromJSVal #-} instance ToJSVal SVGPathSegMovetoAbs where toJSVal = return . unSVGPathSegMovetoAbs {-# INLINE toJSVal #-} instance FromJSVal SVGPathSegMovetoAbs where fromJSVal = return . fmap SVGPathSegMovetoAbs . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGPathSeg SVGPathSegMovetoAbs instance IsGObject SVGPathSegMovetoAbs where typeGType _ = gTypeSVGPathSegMovetoAbs {-# INLINE typeGType #-} noSVGPathSegMovetoAbs :: Maybe SVGPathSegMovetoAbs noSVGPathSegMovetoAbs = Nothing {-# INLINE noSVGPathSegMovetoAbs #-} foreign import javascript unsafe "window[\"SVGPathSegMovetoAbs\"]" gTypeSVGPathSegMovetoAbs :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGPathSegMovetoRel". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGPathSeg" -- -- newtype SVGPathSegMovetoRel = SVGPathSegMovetoRel { unSVGPathSegMovetoRel :: JSVal } instance Eq (SVGPathSegMovetoRel) where (SVGPathSegMovetoRel a) == (SVGPathSegMovetoRel b) = js_eq a b instance PToJSVal SVGPathSegMovetoRel where pToJSVal = unSVGPathSegMovetoRel {-# INLINE pToJSVal #-} instance PFromJSVal SVGPathSegMovetoRel where pFromJSVal = SVGPathSegMovetoRel {-# INLINE pFromJSVal #-} instance ToJSVal SVGPathSegMovetoRel where toJSVal = return . unSVGPathSegMovetoRel {-# INLINE toJSVal #-} instance FromJSVal SVGPathSegMovetoRel where fromJSVal = return . fmap SVGPathSegMovetoRel . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGPathSeg SVGPathSegMovetoRel instance IsGObject SVGPathSegMovetoRel where typeGType _ = gTypeSVGPathSegMovetoRel {-# INLINE typeGType #-} noSVGPathSegMovetoRel :: Maybe SVGPathSegMovetoRel noSVGPathSegMovetoRel = Nothing {-# INLINE noSVGPathSegMovetoRel #-} foreign import javascript unsafe "window[\"SVGPathSegMovetoRel\"]" gTypeSVGPathSegMovetoRel :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGPatternElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- * "GHCJS.DOM.SVGURIReference" -- * "GHCJS.DOM.SVGTests" -- * "GHCJS.DOM.SVGFitToViewBox" -- * "GHCJS.DOM.SVGExternalResourcesRequired" -- -- newtype SVGPatternElement = SVGPatternElement { unSVGPatternElement :: JSVal } instance Eq (SVGPatternElement) where (SVGPatternElement a) == (SVGPatternElement b) = js_eq a b instance PToJSVal SVGPatternElement where pToJSVal = unSVGPatternElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGPatternElement where pFromJSVal = SVGPatternElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGPatternElement where toJSVal = return . unSVGPatternElement {-# INLINE toJSVal #-} instance FromJSVal SVGPatternElement where fromJSVal = return . fmap SVGPatternElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGElement SVGPatternElement instance IsElement SVGPatternElement instance IsNode SVGPatternElement instance IsEventTarget SVGPatternElement instance IsSlotable SVGPatternElement instance IsParentNode SVGPatternElement instance IsNonDocumentTypeChildNode SVGPatternElement instance IsDocumentAndElementEventHandlers SVGPatternElement instance IsChildNode SVGPatternElement instance IsAnimatable SVGPatternElement instance IsGlobalEventHandlers SVGPatternElement instance IsElementCSSInlineStyle SVGPatternElement instance IsSVGURIReference SVGPatternElement instance IsSVGTests SVGPatternElement instance IsSVGFitToViewBox SVGPatternElement instance IsSVGExternalResourcesRequired SVGPatternElement instance IsGObject SVGPatternElement where typeGType _ = gTypeSVGPatternElement {-# INLINE typeGType #-} noSVGPatternElement :: Maybe SVGPatternElement noSVGPatternElement = Nothing {-# INLINE noSVGPatternElement #-} foreign import javascript unsafe "window[\"SVGPatternElement\"]" gTypeSVGPatternElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGPoint". -- -- newtype SVGPoint = SVGPoint { unSVGPoint :: JSVal } instance Eq (SVGPoint) where (SVGPoint a) == (SVGPoint b) = js_eq a b instance PToJSVal SVGPoint where pToJSVal = unSVGPoint {-# INLINE pToJSVal #-} instance PFromJSVal SVGPoint where pFromJSVal = SVGPoint {-# INLINE pFromJSVal #-} instance ToJSVal SVGPoint where toJSVal = return . unSVGPoint {-# INLINE toJSVal #-} instance FromJSVal SVGPoint where fromJSVal = return . fmap SVGPoint . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject SVGPoint where typeGType _ = gTypeSVGPoint {-# INLINE typeGType #-} noSVGPoint :: Maybe SVGPoint noSVGPoint = Nothing {-# INLINE noSVGPoint #-} foreign import javascript unsafe "window[\"SVGPoint\"]" gTypeSVGPoint :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGPointList". -- -- newtype SVGPointList = SVGPointList { unSVGPointList :: JSVal } instance Eq (SVGPointList) where (SVGPointList a) == (SVGPointList b) = js_eq a b instance PToJSVal SVGPointList where pToJSVal = unSVGPointList {-# INLINE pToJSVal #-} instance PFromJSVal SVGPointList where pFromJSVal = SVGPointList {-# INLINE pFromJSVal #-} instance ToJSVal SVGPointList where toJSVal = return . unSVGPointList {-# INLINE toJSVal #-} instance FromJSVal SVGPointList where fromJSVal = return . fmap SVGPointList . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject SVGPointList where typeGType _ = gTypeSVGPointList {-# INLINE typeGType #-} noSVGPointList :: Maybe SVGPointList noSVGPointList = Nothing {-# INLINE noSVGPointList #-} foreign import javascript unsafe "window[\"SVGPointList\"]" gTypeSVGPointList :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGPolygonElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGGraphicsElement" -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- * "GHCJS.DOM.SVGTests" -- * "GHCJS.DOM.SVGExternalResourcesRequired" -- -- newtype SVGPolygonElement = SVGPolygonElement { unSVGPolygonElement :: JSVal } instance Eq (SVGPolygonElement) where (SVGPolygonElement a) == (SVGPolygonElement b) = js_eq a b instance PToJSVal SVGPolygonElement where pToJSVal = unSVGPolygonElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGPolygonElement where pFromJSVal = SVGPolygonElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGPolygonElement where toJSVal = return . unSVGPolygonElement {-# INLINE toJSVal #-} instance FromJSVal SVGPolygonElement where fromJSVal = return . fmap SVGPolygonElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGGraphicsElement SVGPolygonElement instance IsSVGElement SVGPolygonElement instance IsElement SVGPolygonElement instance IsNode SVGPolygonElement instance IsEventTarget SVGPolygonElement instance IsSlotable SVGPolygonElement instance IsParentNode SVGPolygonElement instance IsNonDocumentTypeChildNode SVGPolygonElement instance IsDocumentAndElementEventHandlers SVGPolygonElement instance IsChildNode SVGPolygonElement instance IsAnimatable SVGPolygonElement instance IsGlobalEventHandlers SVGPolygonElement instance IsElementCSSInlineStyle SVGPolygonElement instance IsSVGTests SVGPolygonElement instance IsSVGExternalResourcesRequired SVGPolygonElement instance IsGObject SVGPolygonElement where typeGType _ = gTypeSVGPolygonElement {-# INLINE typeGType #-} noSVGPolygonElement :: Maybe SVGPolygonElement noSVGPolygonElement = Nothing {-# INLINE noSVGPolygonElement #-} foreign import javascript unsafe "window[\"SVGPolygonElement\"]" gTypeSVGPolygonElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGPolylineElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGGraphicsElement" -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- * "GHCJS.DOM.SVGTests" -- * "GHCJS.DOM.SVGExternalResourcesRequired" -- -- newtype SVGPolylineElement = SVGPolylineElement { unSVGPolylineElement :: JSVal } instance Eq (SVGPolylineElement) where (SVGPolylineElement a) == (SVGPolylineElement b) = js_eq a b instance PToJSVal SVGPolylineElement where pToJSVal = unSVGPolylineElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGPolylineElement where pFromJSVal = SVGPolylineElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGPolylineElement where toJSVal = return . unSVGPolylineElement {-# INLINE toJSVal #-} instance FromJSVal SVGPolylineElement where fromJSVal = return . fmap SVGPolylineElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGGraphicsElement SVGPolylineElement instance IsSVGElement SVGPolylineElement instance IsElement SVGPolylineElement instance IsNode SVGPolylineElement instance IsEventTarget SVGPolylineElement instance IsSlotable SVGPolylineElement instance IsParentNode SVGPolylineElement instance IsNonDocumentTypeChildNode SVGPolylineElement instance IsDocumentAndElementEventHandlers SVGPolylineElement instance IsChildNode SVGPolylineElement instance IsAnimatable SVGPolylineElement instance IsGlobalEventHandlers SVGPolylineElement instance IsElementCSSInlineStyle SVGPolylineElement instance IsSVGTests SVGPolylineElement instance IsSVGExternalResourcesRequired SVGPolylineElement instance IsGObject SVGPolylineElement where typeGType _ = gTypeSVGPolylineElement {-# INLINE typeGType #-} noSVGPolylineElement :: Maybe SVGPolylineElement noSVGPolylineElement = Nothing {-# INLINE noSVGPolylineElement #-} foreign import javascript unsafe "window[\"SVGPolylineElement\"]" gTypeSVGPolylineElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGPreserveAspectRatio". -- -- newtype SVGPreserveAspectRatio = SVGPreserveAspectRatio { unSVGPreserveAspectRatio :: JSVal } instance Eq (SVGPreserveAspectRatio) where (SVGPreserveAspectRatio a) == (SVGPreserveAspectRatio b) = js_eq a b instance PToJSVal SVGPreserveAspectRatio where pToJSVal = unSVGPreserveAspectRatio {-# INLINE pToJSVal #-} instance PFromJSVal SVGPreserveAspectRatio where pFromJSVal = SVGPreserveAspectRatio {-# INLINE pFromJSVal #-} instance ToJSVal SVGPreserveAspectRatio where toJSVal = return . unSVGPreserveAspectRatio {-# INLINE toJSVal #-} instance FromJSVal SVGPreserveAspectRatio where fromJSVal = return . fmap SVGPreserveAspectRatio . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject SVGPreserveAspectRatio where typeGType _ = gTypeSVGPreserveAspectRatio {-# INLINE typeGType #-} noSVGPreserveAspectRatio :: Maybe SVGPreserveAspectRatio noSVGPreserveAspectRatio = Nothing {-# INLINE noSVGPreserveAspectRatio #-} foreign import javascript unsafe "window[\"SVGPreserveAspectRatio\"]" gTypeSVGPreserveAspectRatio :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGRadialGradientElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGGradientElement" -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- * "GHCJS.DOM.SVGURIReference" -- * "GHCJS.DOM.SVGExternalResourcesRequired" -- -- newtype SVGRadialGradientElement = SVGRadialGradientElement { unSVGRadialGradientElement :: JSVal } instance Eq (SVGRadialGradientElement) where (SVGRadialGradientElement a) == (SVGRadialGradientElement b) = js_eq a b instance PToJSVal SVGRadialGradientElement where pToJSVal = unSVGRadialGradientElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGRadialGradientElement where pFromJSVal = SVGRadialGradientElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGRadialGradientElement where toJSVal = return . unSVGRadialGradientElement {-# INLINE toJSVal #-} instance FromJSVal SVGRadialGradientElement where fromJSVal = return . fmap SVGRadialGradientElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGGradientElement SVGRadialGradientElement instance IsSVGElement SVGRadialGradientElement instance IsElement SVGRadialGradientElement instance IsNode SVGRadialGradientElement instance IsEventTarget SVGRadialGradientElement instance IsSlotable SVGRadialGradientElement instance IsParentNode SVGRadialGradientElement instance IsNonDocumentTypeChildNode SVGRadialGradientElement instance IsDocumentAndElementEventHandlers SVGRadialGradientElement instance IsChildNode SVGRadialGradientElement instance IsAnimatable SVGRadialGradientElement instance IsGlobalEventHandlers SVGRadialGradientElement instance IsElementCSSInlineStyle SVGRadialGradientElement instance IsSVGURIReference SVGRadialGradientElement instance IsSVGExternalResourcesRequired SVGRadialGradientElement instance IsGObject SVGRadialGradientElement where typeGType _ = gTypeSVGRadialGradientElement {-# INLINE typeGType #-} noSVGRadialGradientElement :: Maybe SVGRadialGradientElement noSVGRadialGradientElement = Nothing {-# INLINE noSVGRadialGradientElement #-} foreign import javascript unsafe "window[\"SVGRadialGradientElement\"]" gTypeSVGRadialGradientElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGRect". -- -- newtype SVGRect = SVGRect { unSVGRect :: JSVal } instance Eq (SVGRect) where (SVGRect a) == (SVGRect b) = js_eq a b instance PToJSVal SVGRect where pToJSVal = unSVGRect {-# INLINE pToJSVal #-} instance PFromJSVal SVGRect where pFromJSVal = SVGRect {-# INLINE pFromJSVal #-} instance ToJSVal SVGRect where toJSVal = return . unSVGRect {-# INLINE toJSVal #-} instance FromJSVal SVGRect where fromJSVal = return . fmap SVGRect . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject SVGRect where typeGType _ = gTypeSVGRect {-# INLINE typeGType #-} noSVGRect :: Maybe SVGRect noSVGRect = Nothing {-# INLINE noSVGRect #-} foreign import javascript unsafe "window[\"SVGRect\"]" gTypeSVGRect :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGRectElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGGraphicsElement" -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- * "GHCJS.DOM.SVGTests" -- * "GHCJS.DOM.SVGExternalResourcesRequired" -- -- newtype SVGRectElement = SVGRectElement { unSVGRectElement :: JSVal } instance Eq (SVGRectElement) where (SVGRectElement a) == (SVGRectElement b) = js_eq a b instance PToJSVal SVGRectElement where pToJSVal = unSVGRectElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGRectElement where pFromJSVal = SVGRectElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGRectElement where toJSVal = return . unSVGRectElement {-# INLINE toJSVal #-} instance FromJSVal SVGRectElement where fromJSVal = return . fmap SVGRectElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGGraphicsElement SVGRectElement instance IsSVGElement SVGRectElement instance IsElement SVGRectElement instance IsNode SVGRectElement instance IsEventTarget SVGRectElement instance IsSlotable SVGRectElement instance IsParentNode SVGRectElement instance IsNonDocumentTypeChildNode SVGRectElement instance IsDocumentAndElementEventHandlers SVGRectElement instance IsChildNode SVGRectElement instance IsAnimatable SVGRectElement instance IsGlobalEventHandlers SVGRectElement instance IsElementCSSInlineStyle SVGRectElement instance IsSVGTests SVGRectElement instance IsSVGExternalResourcesRequired SVGRectElement instance IsGObject SVGRectElement where typeGType _ = gTypeSVGRectElement {-# INLINE typeGType #-} noSVGRectElement :: Maybe SVGRectElement noSVGRectElement = Nothing {-# INLINE noSVGRectElement #-} foreign import javascript unsafe "window[\"SVGRectElement\"]" gTypeSVGRectElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGRenderingIntent". -- -- newtype SVGRenderingIntent = SVGRenderingIntent { unSVGRenderingIntent :: JSVal } instance Eq (SVGRenderingIntent) where (SVGRenderingIntent a) == (SVGRenderingIntent b) = js_eq a b instance PToJSVal SVGRenderingIntent where pToJSVal = unSVGRenderingIntent {-# INLINE pToJSVal #-} instance PFromJSVal SVGRenderingIntent where pFromJSVal = SVGRenderingIntent {-# INLINE pFromJSVal #-} instance ToJSVal SVGRenderingIntent where toJSVal = return . unSVGRenderingIntent {-# INLINE toJSVal #-} instance FromJSVal SVGRenderingIntent where fromJSVal = return . fmap SVGRenderingIntent . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject SVGRenderingIntent where typeGType _ = gTypeSVGRenderingIntent {-# INLINE typeGType #-} noSVGRenderingIntent :: Maybe SVGRenderingIntent noSVGRenderingIntent = Nothing {-# INLINE noSVGRenderingIntent #-} foreign import javascript unsafe "window[\"SVGRenderingIntent\"]" gTypeSVGRenderingIntent :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGSVGElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGGraphicsElement" -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- * "GHCJS.DOM.SVGTests" -- * "GHCJS.DOM.SVGZoomAndPan" -- * "GHCJS.DOM.SVGFitToViewBox" -- * "GHCJS.DOM.SVGExternalResourcesRequired" -- -- newtype SVGSVGElement = SVGSVGElement { unSVGSVGElement :: JSVal } instance Eq (SVGSVGElement) where (SVGSVGElement a) == (SVGSVGElement b) = js_eq a b instance PToJSVal SVGSVGElement where pToJSVal = unSVGSVGElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGSVGElement where pFromJSVal = SVGSVGElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGSVGElement where toJSVal = return . unSVGSVGElement {-# INLINE toJSVal #-} instance FromJSVal SVGSVGElement where fromJSVal = return . fmap SVGSVGElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGGraphicsElement SVGSVGElement instance IsSVGElement SVGSVGElement instance IsElement SVGSVGElement instance IsNode SVGSVGElement instance IsEventTarget SVGSVGElement instance IsSlotable SVGSVGElement instance IsParentNode SVGSVGElement instance IsNonDocumentTypeChildNode SVGSVGElement instance IsDocumentAndElementEventHandlers SVGSVGElement instance IsChildNode SVGSVGElement instance IsAnimatable SVGSVGElement instance IsGlobalEventHandlers SVGSVGElement instance IsElementCSSInlineStyle SVGSVGElement instance IsSVGTests SVGSVGElement instance IsSVGZoomAndPan SVGSVGElement instance IsSVGFitToViewBox SVGSVGElement instance IsSVGExternalResourcesRequired SVGSVGElement instance IsGObject SVGSVGElement where typeGType _ = gTypeSVGSVGElement {-# INLINE typeGType #-} noSVGSVGElement :: Maybe SVGSVGElement noSVGSVGElement = Nothing {-# INLINE noSVGSVGElement #-} foreign import javascript unsafe "window[\"SVGSVGElement\"]" gTypeSVGSVGElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGScriptElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- * "GHCJS.DOM.SVGURIReference" -- * "GHCJS.DOM.SVGExternalResourcesRequired" -- -- newtype SVGScriptElement = SVGScriptElement { unSVGScriptElement :: JSVal } instance Eq (SVGScriptElement) where (SVGScriptElement a) == (SVGScriptElement b) = js_eq a b instance PToJSVal SVGScriptElement where pToJSVal = unSVGScriptElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGScriptElement where pFromJSVal = SVGScriptElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGScriptElement where toJSVal = return . unSVGScriptElement {-# INLINE toJSVal #-} instance FromJSVal SVGScriptElement where fromJSVal = return . fmap SVGScriptElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGElement SVGScriptElement instance IsElement SVGScriptElement instance IsNode SVGScriptElement instance IsEventTarget SVGScriptElement instance IsSlotable SVGScriptElement instance IsParentNode SVGScriptElement instance IsNonDocumentTypeChildNode SVGScriptElement instance IsDocumentAndElementEventHandlers SVGScriptElement instance IsChildNode SVGScriptElement instance IsAnimatable SVGScriptElement instance IsGlobalEventHandlers SVGScriptElement instance IsElementCSSInlineStyle SVGScriptElement instance IsSVGURIReference SVGScriptElement instance IsSVGExternalResourcesRequired SVGScriptElement instance IsGObject SVGScriptElement where typeGType _ = gTypeSVGScriptElement {-# INLINE typeGType #-} noSVGScriptElement :: Maybe SVGScriptElement noSVGScriptElement = Nothing {-# INLINE noSVGScriptElement #-} foreign import javascript unsafe "window[\"SVGScriptElement\"]" gTypeSVGScriptElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGSetElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGAnimationElement" -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- * "GHCJS.DOM.SVGTests" -- * "GHCJS.DOM.SVGExternalResourcesRequired" -- -- newtype SVGSetElement = SVGSetElement { unSVGSetElement :: JSVal } instance Eq (SVGSetElement) where (SVGSetElement a) == (SVGSetElement b) = js_eq a b instance PToJSVal SVGSetElement where pToJSVal = unSVGSetElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGSetElement where pFromJSVal = SVGSetElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGSetElement where toJSVal = return . unSVGSetElement {-# INLINE toJSVal #-} instance FromJSVal SVGSetElement where fromJSVal = return . fmap SVGSetElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGAnimationElement SVGSetElement instance IsSVGElement SVGSetElement instance IsElement SVGSetElement instance IsNode SVGSetElement instance IsEventTarget SVGSetElement instance IsSlotable SVGSetElement instance IsParentNode SVGSetElement instance IsNonDocumentTypeChildNode SVGSetElement instance IsDocumentAndElementEventHandlers SVGSetElement instance IsChildNode SVGSetElement instance IsAnimatable SVGSetElement instance IsGlobalEventHandlers SVGSetElement instance IsElementCSSInlineStyle SVGSetElement instance IsSVGTests SVGSetElement instance IsSVGExternalResourcesRequired SVGSetElement instance IsGObject SVGSetElement where typeGType _ = gTypeSVGSetElement {-# INLINE typeGType #-} noSVGSetElement :: Maybe SVGSetElement noSVGSetElement = Nothing {-# INLINE noSVGSetElement #-} foreign import javascript unsafe "window[\"SVGSetElement\"]" gTypeSVGSetElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGStopElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype SVGStopElement = SVGStopElement { unSVGStopElement :: JSVal } instance Eq (SVGStopElement) where (SVGStopElement a) == (SVGStopElement b) = js_eq a b instance PToJSVal SVGStopElement where pToJSVal = unSVGStopElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGStopElement where pFromJSVal = SVGStopElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGStopElement where toJSVal = return . unSVGStopElement {-# INLINE toJSVal #-} instance FromJSVal SVGStopElement where fromJSVal = return . fmap SVGStopElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGElement SVGStopElement instance IsElement SVGStopElement instance IsNode SVGStopElement instance IsEventTarget SVGStopElement instance IsSlotable SVGStopElement instance IsParentNode SVGStopElement instance IsNonDocumentTypeChildNode SVGStopElement instance IsDocumentAndElementEventHandlers SVGStopElement instance IsChildNode SVGStopElement instance IsAnimatable SVGStopElement instance IsGlobalEventHandlers SVGStopElement instance IsElementCSSInlineStyle SVGStopElement instance IsGObject SVGStopElement where typeGType _ = gTypeSVGStopElement {-# INLINE typeGType #-} noSVGStopElement :: Maybe SVGStopElement noSVGStopElement = Nothing {-# INLINE noSVGStopElement #-} foreign import javascript unsafe "window[\"SVGStopElement\"]" gTypeSVGStopElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGStringList". -- -- newtype SVGStringList = SVGStringList { unSVGStringList :: JSVal } instance Eq (SVGStringList) where (SVGStringList a) == (SVGStringList b) = js_eq a b instance PToJSVal SVGStringList where pToJSVal = unSVGStringList {-# INLINE pToJSVal #-} instance PFromJSVal SVGStringList where pFromJSVal = SVGStringList {-# INLINE pFromJSVal #-} instance ToJSVal SVGStringList where toJSVal = return . unSVGStringList {-# INLINE toJSVal #-} instance FromJSVal SVGStringList where fromJSVal = return . fmap SVGStringList . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject SVGStringList where typeGType _ = gTypeSVGStringList {-# INLINE typeGType #-} noSVGStringList :: Maybe SVGStringList noSVGStringList = Nothing {-# INLINE noSVGStringList #-} foreign import javascript unsafe "window[\"SVGStringList\"]" gTypeSVGStringList :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGStyleElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype SVGStyleElement = SVGStyleElement { unSVGStyleElement :: JSVal } instance Eq (SVGStyleElement) where (SVGStyleElement a) == (SVGStyleElement b) = js_eq a b instance PToJSVal SVGStyleElement where pToJSVal = unSVGStyleElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGStyleElement where pFromJSVal = SVGStyleElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGStyleElement where toJSVal = return . unSVGStyleElement {-# INLINE toJSVal #-} instance FromJSVal SVGStyleElement where fromJSVal = return . fmap SVGStyleElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGElement SVGStyleElement instance IsElement SVGStyleElement instance IsNode SVGStyleElement instance IsEventTarget SVGStyleElement instance IsSlotable SVGStyleElement instance IsParentNode SVGStyleElement instance IsNonDocumentTypeChildNode SVGStyleElement instance IsDocumentAndElementEventHandlers SVGStyleElement instance IsChildNode SVGStyleElement instance IsAnimatable SVGStyleElement instance IsGlobalEventHandlers SVGStyleElement instance IsElementCSSInlineStyle SVGStyleElement instance IsGObject SVGStyleElement where typeGType _ = gTypeSVGStyleElement {-# INLINE typeGType #-} noSVGStyleElement :: Maybe SVGStyleElement noSVGStyleElement = Nothing {-# INLINE noSVGStyleElement #-} foreign import javascript unsafe "window[\"SVGStyleElement\"]" gTypeSVGStyleElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGSwitchElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGGraphicsElement" -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- * "GHCJS.DOM.SVGTests" -- * "GHCJS.DOM.SVGExternalResourcesRequired" -- -- newtype SVGSwitchElement = SVGSwitchElement { unSVGSwitchElement :: JSVal } instance Eq (SVGSwitchElement) where (SVGSwitchElement a) == (SVGSwitchElement b) = js_eq a b instance PToJSVal SVGSwitchElement where pToJSVal = unSVGSwitchElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGSwitchElement where pFromJSVal = SVGSwitchElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGSwitchElement where toJSVal = return . unSVGSwitchElement {-# INLINE toJSVal #-} instance FromJSVal SVGSwitchElement where fromJSVal = return . fmap SVGSwitchElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGGraphicsElement SVGSwitchElement instance IsSVGElement SVGSwitchElement instance IsElement SVGSwitchElement instance IsNode SVGSwitchElement instance IsEventTarget SVGSwitchElement instance IsSlotable SVGSwitchElement instance IsParentNode SVGSwitchElement instance IsNonDocumentTypeChildNode SVGSwitchElement instance IsDocumentAndElementEventHandlers SVGSwitchElement instance IsChildNode SVGSwitchElement instance IsAnimatable SVGSwitchElement instance IsGlobalEventHandlers SVGSwitchElement instance IsElementCSSInlineStyle SVGSwitchElement instance IsSVGTests SVGSwitchElement instance IsSVGExternalResourcesRequired SVGSwitchElement instance IsGObject SVGSwitchElement where typeGType _ = gTypeSVGSwitchElement {-# INLINE typeGType #-} noSVGSwitchElement :: Maybe SVGSwitchElement noSVGSwitchElement = Nothing {-# INLINE noSVGSwitchElement #-} foreign import javascript unsafe "window[\"SVGSwitchElement\"]" gTypeSVGSwitchElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGSymbolElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- * "GHCJS.DOM.SVGFitToViewBox" -- * "GHCJS.DOM.SVGExternalResourcesRequired" -- -- newtype SVGSymbolElement = SVGSymbolElement { unSVGSymbolElement :: JSVal } instance Eq (SVGSymbolElement) where (SVGSymbolElement a) == (SVGSymbolElement b) = js_eq a b instance PToJSVal SVGSymbolElement where pToJSVal = unSVGSymbolElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGSymbolElement where pFromJSVal = SVGSymbolElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGSymbolElement where toJSVal = return . unSVGSymbolElement {-# INLINE toJSVal #-} instance FromJSVal SVGSymbolElement where fromJSVal = return . fmap SVGSymbolElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGElement SVGSymbolElement instance IsElement SVGSymbolElement instance IsNode SVGSymbolElement instance IsEventTarget SVGSymbolElement instance IsSlotable SVGSymbolElement instance IsParentNode SVGSymbolElement instance IsNonDocumentTypeChildNode SVGSymbolElement instance IsDocumentAndElementEventHandlers SVGSymbolElement instance IsChildNode SVGSymbolElement instance IsAnimatable SVGSymbolElement instance IsGlobalEventHandlers SVGSymbolElement instance IsElementCSSInlineStyle SVGSymbolElement instance IsSVGFitToViewBox SVGSymbolElement instance IsSVGExternalResourcesRequired SVGSymbolElement instance IsGObject SVGSymbolElement where typeGType _ = gTypeSVGSymbolElement {-# INLINE typeGType #-} noSVGSymbolElement :: Maybe SVGSymbolElement noSVGSymbolElement = Nothing {-# INLINE noSVGSymbolElement #-} foreign import javascript unsafe "window[\"SVGSymbolElement\"]" gTypeSVGSymbolElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGTRefElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGTextPositioningElement" -- * "GHCJS.DOM.SVGTextContentElement" -- * "GHCJS.DOM.SVGGraphicsElement" -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- * "GHCJS.DOM.SVGTests" -- * "GHCJS.DOM.SVGExternalResourcesRequired" -- * "GHCJS.DOM.SVGURIReference" -- -- newtype SVGTRefElement = SVGTRefElement { unSVGTRefElement :: JSVal } instance Eq (SVGTRefElement) where (SVGTRefElement a) == (SVGTRefElement b) = js_eq a b instance PToJSVal SVGTRefElement where pToJSVal = unSVGTRefElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGTRefElement where pFromJSVal = SVGTRefElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGTRefElement where toJSVal = return . unSVGTRefElement {-# INLINE toJSVal #-} instance FromJSVal SVGTRefElement where fromJSVal = return . fmap SVGTRefElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGTextPositioningElement SVGTRefElement instance IsSVGTextContentElement SVGTRefElement instance IsSVGGraphicsElement SVGTRefElement instance IsSVGElement SVGTRefElement instance IsElement SVGTRefElement instance IsNode SVGTRefElement instance IsEventTarget SVGTRefElement instance IsSlotable SVGTRefElement instance IsParentNode SVGTRefElement instance IsNonDocumentTypeChildNode SVGTRefElement instance IsDocumentAndElementEventHandlers SVGTRefElement instance IsChildNode SVGTRefElement instance IsAnimatable SVGTRefElement instance IsGlobalEventHandlers SVGTRefElement instance IsElementCSSInlineStyle SVGTRefElement instance IsSVGTests SVGTRefElement instance IsSVGExternalResourcesRequired SVGTRefElement instance IsSVGURIReference SVGTRefElement instance IsGObject SVGTRefElement where typeGType _ = gTypeSVGTRefElement {-# INLINE typeGType #-} noSVGTRefElement :: Maybe SVGTRefElement noSVGTRefElement = Nothing {-# INLINE noSVGTRefElement #-} foreign import javascript unsafe "window[\"SVGTRefElement\"]" gTypeSVGTRefElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGTSpanElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGTextPositioningElement" -- * "GHCJS.DOM.SVGTextContentElement" -- * "GHCJS.DOM.SVGGraphicsElement" -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- * "GHCJS.DOM.SVGTests" -- * "GHCJS.DOM.SVGExternalResourcesRequired" -- -- newtype SVGTSpanElement = SVGTSpanElement { unSVGTSpanElement :: JSVal } instance Eq (SVGTSpanElement) where (SVGTSpanElement a) == (SVGTSpanElement b) = js_eq a b instance PToJSVal SVGTSpanElement where pToJSVal = unSVGTSpanElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGTSpanElement where pFromJSVal = SVGTSpanElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGTSpanElement where toJSVal = return . unSVGTSpanElement {-# INLINE toJSVal #-} instance FromJSVal SVGTSpanElement where fromJSVal = return . fmap SVGTSpanElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGTextPositioningElement SVGTSpanElement instance IsSVGTextContentElement SVGTSpanElement instance IsSVGGraphicsElement SVGTSpanElement instance IsSVGElement SVGTSpanElement instance IsElement SVGTSpanElement instance IsNode SVGTSpanElement instance IsEventTarget SVGTSpanElement instance IsSlotable SVGTSpanElement instance IsParentNode SVGTSpanElement instance IsNonDocumentTypeChildNode SVGTSpanElement instance IsDocumentAndElementEventHandlers SVGTSpanElement instance IsChildNode SVGTSpanElement instance IsAnimatable SVGTSpanElement instance IsGlobalEventHandlers SVGTSpanElement instance IsElementCSSInlineStyle SVGTSpanElement instance IsSVGTests SVGTSpanElement instance IsSVGExternalResourcesRequired SVGTSpanElement instance IsGObject SVGTSpanElement where typeGType _ = gTypeSVGTSpanElement {-# INLINE typeGType #-} noSVGTSpanElement :: Maybe SVGTSpanElement noSVGTSpanElement = Nothing {-# INLINE noSVGTSpanElement #-} foreign import javascript unsafe "window[\"SVGTSpanElement\"]" gTypeSVGTSpanElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGTests". -- -- newtype SVGTests = SVGTests { unSVGTests :: JSVal } instance Eq (SVGTests) where (SVGTests a) == (SVGTests b) = js_eq a b instance PToJSVal SVGTests where pToJSVal = unSVGTests {-# INLINE pToJSVal #-} instance PFromJSVal SVGTests where pFromJSVal = SVGTests {-# INLINE pFromJSVal #-} instance ToJSVal SVGTests where toJSVal = return . unSVGTests {-# INLINE toJSVal #-} instance FromJSVal SVGTests where fromJSVal = return . fmap SVGTests . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsGObject o) => IsSVGTests o toSVGTests :: IsSVGTests o => o -> SVGTests toSVGTests = SVGTests . coerce instance IsSVGTests SVGTests instance IsGObject SVGTests where typeGType _ = gTypeSVGTests {-# INLINE typeGType #-} noSVGTests :: Maybe SVGTests noSVGTests = Nothing {-# INLINE noSVGTests #-} foreign import javascript unsafe "window[\"SVGTests\"]" gTypeSVGTests :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGTextContentElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGGraphicsElement" -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- * "GHCJS.DOM.SVGTests" -- * "GHCJS.DOM.SVGExternalResourcesRequired" -- -- newtype SVGTextContentElement = SVGTextContentElement { unSVGTextContentElement :: JSVal } instance Eq (SVGTextContentElement) where (SVGTextContentElement a) == (SVGTextContentElement b) = js_eq a b instance PToJSVal SVGTextContentElement where pToJSVal = unSVGTextContentElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGTextContentElement where pFromJSVal = SVGTextContentElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGTextContentElement where toJSVal = return . unSVGTextContentElement {-# INLINE toJSVal #-} instance FromJSVal SVGTextContentElement where fromJSVal = return . fmap SVGTextContentElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsSVGGraphicsElement o, IsSVGElement o, IsElement o, IsNode o, IsEventTarget o, IsSlotable o, IsParentNode o, IsNonDocumentTypeChildNode o, IsDocumentAndElementEventHandlers o, IsChildNode o, IsAnimatable o, IsGlobalEventHandlers o, IsElementCSSInlineStyle o, IsSVGTests o, IsSVGExternalResourcesRequired o, IsGObject o) => IsSVGTextContentElement o toSVGTextContentElement :: IsSVGTextContentElement o => o -> SVGTextContentElement toSVGTextContentElement = SVGTextContentElement . coerce instance IsSVGTextContentElement SVGTextContentElement instance IsSVGGraphicsElement SVGTextContentElement instance IsSVGElement SVGTextContentElement instance IsElement SVGTextContentElement instance IsNode SVGTextContentElement instance IsEventTarget SVGTextContentElement instance IsSlotable SVGTextContentElement instance IsParentNode SVGTextContentElement instance IsNonDocumentTypeChildNode SVGTextContentElement instance IsDocumentAndElementEventHandlers SVGTextContentElement instance IsChildNode SVGTextContentElement instance IsAnimatable SVGTextContentElement instance IsGlobalEventHandlers SVGTextContentElement instance IsElementCSSInlineStyle SVGTextContentElement instance IsSVGTests SVGTextContentElement instance IsSVGExternalResourcesRequired SVGTextContentElement instance IsGObject SVGTextContentElement where typeGType _ = gTypeSVGTextContentElement {-# INLINE typeGType #-} noSVGTextContentElement :: Maybe SVGTextContentElement noSVGTextContentElement = Nothing {-# INLINE noSVGTextContentElement #-} foreign import javascript unsafe "window[\"SVGTextContentElement\"]" gTypeSVGTextContentElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGTextElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGTextPositioningElement" -- * "GHCJS.DOM.SVGTextContentElement" -- * "GHCJS.DOM.SVGGraphicsElement" -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- * "GHCJS.DOM.SVGTests" -- * "GHCJS.DOM.SVGExternalResourcesRequired" -- -- newtype SVGTextElement = SVGTextElement { unSVGTextElement :: JSVal } instance Eq (SVGTextElement) where (SVGTextElement a) == (SVGTextElement b) = js_eq a b instance PToJSVal SVGTextElement where pToJSVal = unSVGTextElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGTextElement where pFromJSVal = SVGTextElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGTextElement where toJSVal = return . unSVGTextElement {-# INLINE toJSVal #-} instance FromJSVal SVGTextElement where fromJSVal = return . fmap SVGTextElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGTextPositioningElement SVGTextElement instance IsSVGTextContentElement SVGTextElement instance IsSVGGraphicsElement SVGTextElement instance IsSVGElement SVGTextElement instance IsElement SVGTextElement instance IsNode SVGTextElement instance IsEventTarget SVGTextElement instance IsSlotable SVGTextElement instance IsParentNode SVGTextElement instance IsNonDocumentTypeChildNode SVGTextElement instance IsDocumentAndElementEventHandlers SVGTextElement instance IsChildNode SVGTextElement instance IsAnimatable SVGTextElement instance IsGlobalEventHandlers SVGTextElement instance IsElementCSSInlineStyle SVGTextElement instance IsSVGTests SVGTextElement instance IsSVGExternalResourcesRequired SVGTextElement instance IsGObject SVGTextElement where typeGType _ = gTypeSVGTextElement {-# INLINE typeGType #-} noSVGTextElement :: Maybe SVGTextElement noSVGTextElement = Nothing {-# INLINE noSVGTextElement #-} foreign import javascript unsafe "window[\"SVGTextElement\"]" gTypeSVGTextElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGTextPathElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGTextContentElement" -- * "GHCJS.DOM.SVGGraphicsElement" -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- * "GHCJS.DOM.SVGTests" -- * "GHCJS.DOM.SVGExternalResourcesRequired" -- * "GHCJS.DOM.SVGURIReference" -- -- newtype SVGTextPathElement = SVGTextPathElement { unSVGTextPathElement :: JSVal } instance Eq (SVGTextPathElement) where (SVGTextPathElement a) == (SVGTextPathElement b) = js_eq a b instance PToJSVal SVGTextPathElement where pToJSVal = unSVGTextPathElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGTextPathElement where pFromJSVal = SVGTextPathElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGTextPathElement where toJSVal = return . unSVGTextPathElement {-# INLINE toJSVal #-} instance FromJSVal SVGTextPathElement where fromJSVal = return . fmap SVGTextPathElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGTextContentElement SVGTextPathElement instance IsSVGGraphicsElement SVGTextPathElement instance IsSVGElement SVGTextPathElement instance IsElement SVGTextPathElement instance IsNode SVGTextPathElement instance IsEventTarget SVGTextPathElement instance IsSlotable SVGTextPathElement instance IsParentNode SVGTextPathElement instance IsNonDocumentTypeChildNode SVGTextPathElement instance IsDocumentAndElementEventHandlers SVGTextPathElement instance IsChildNode SVGTextPathElement instance IsAnimatable SVGTextPathElement instance IsGlobalEventHandlers SVGTextPathElement instance IsElementCSSInlineStyle SVGTextPathElement instance IsSVGTests SVGTextPathElement instance IsSVGExternalResourcesRequired SVGTextPathElement instance IsSVGURIReference SVGTextPathElement instance IsGObject SVGTextPathElement where typeGType _ = gTypeSVGTextPathElement {-# INLINE typeGType #-} noSVGTextPathElement :: Maybe SVGTextPathElement noSVGTextPathElement = Nothing {-# INLINE noSVGTextPathElement #-} foreign import javascript unsafe "window[\"SVGTextPathElement\"]" gTypeSVGTextPathElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGTextPositioningElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGTextContentElement" -- * "GHCJS.DOM.SVGGraphicsElement" -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- * "GHCJS.DOM.SVGTests" -- * "GHCJS.DOM.SVGExternalResourcesRequired" -- -- newtype SVGTextPositioningElement = SVGTextPositioningElement { unSVGTextPositioningElement :: JSVal } instance Eq (SVGTextPositioningElement) where (SVGTextPositioningElement a) == (SVGTextPositioningElement b) = js_eq a b instance PToJSVal SVGTextPositioningElement where pToJSVal = unSVGTextPositioningElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGTextPositioningElement where pFromJSVal = SVGTextPositioningElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGTextPositioningElement where toJSVal = return . unSVGTextPositioningElement {-# INLINE toJSVal #-} instance FromJSVal SVGTextPositioningElement where fromJSVal = return . fmap SVGTextPositioningElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsSVGTextContentElement o, IsSVGGraphicsElement o, IsSVGElement o, IsElement o, IsNode o, IsEventTarget o, IsSlotable o, IsParentNode o, IsNonDocumentTypeChildNode o, IsDocumentAndElementEventHandlers o, IsChildNode o, IsAnimatable o, IsGlobalEventHandlers o, IsElementCSSInlineStyle o, IsSVGTests o, IsSVGExternalResourcesRequired o, IsGObject o) => IsSVGTextPositioningElement o toSVGTextPositioningElement :: IsSVGTextPositioningElement o => o -> SVGTextPositioningElement toSVGTextPositioningElement = SVGTextPositioningElement . coerce instance IsSVGTextPositioningElement SVGTextPositioningElement instance IsSVGTextContentElement SVGTextPositioningElement instance IsSVGGraphicsElement SVGTextPositioningElement instance IsSVGElement SVGTextPositioningElement instance IsElement SVGTextPositioningElement instance IsNode SVGTextPositioningElement instance IsEventTarget SVGTextPositioningElement instance IsSlotable SVGTextPositioningElement instance IsParentNode SVGTextPositioningElement instance IsNonDocumentTypeChildNode SVGTextPositioningElement instance IsDocumentAndElementEventHandlers SVGTextPositioningElement instance IsChildNode SVGTextPositioningElement instance IsAnimatable SVGTextPositioningElement instance IsGlobalEventHandlers SVGTextPositioningElement instance IsElementCSSInlineStyle SVGTextPositioningElement instance IsSVGTests SVGTextPositioningElement instance IsSVGExternalResourcesRequired SVGTextPositioningElement instance IsGObject SVGTextPositioningElement where typeGType _ = gTypeSVGTextPositioningElement {-# INLINE typeGType #-} noSVGTextPositioningElement :: Maybe SVGTextPositioningElement noSVGTextPositioningElement = Nothing {-# INLINE noSVGTextPositioningElement #-} foreign import javascript unsafe "window[\"SVGTextPositioningElement\"]" gTypeSVGTextPositioningElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGTitleElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype SVGTitleElement = SVGTitleElement { unSVGTitleElement :: JSVal } instance Eq (SVGTitleElement) where (SVGTitleElement a) == (SVGTitleElement b) = js_eq a b instance PToJSVal SVGTitleElement where pToJSVal = unSVGTitleElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGTitleElement where pFromJSVal = SVGTitleElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGTitleElement where toJSVal = return . unSVGTitleElement {-# INLINE toJSVal #-} instance FromJSVal SVGTitleElement where fromJSVal = return . fmap SVGTitleElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGElement SVGTitleElement instance IsElement SVGTitleElement instance IsNode SVGTitleElement instance IsEventTarget SVGTitleElement instance IsSlotable SVGTitleElement instance IsParentNode SVGTitleElement instance IsNonDocumentTypeChildNode SVGTitleElement instance IsDocumentAndElementEventHandlers SVGTitleElement instance IsChildNode SVGTitleElement instance IsAnimatable SVGTitleElement instance IsGlobalEventHandlers SVGTitleElement instance IsElementCSSInlineStyle SVGTitleElement instance IsGObject SVGTitleElement where typeGType _ = gTypeSVGTitleElement {-# INLINE typeGType #-} noSVGTitleElement :: Maybe SVGTitleElement noSVGTitleElement = Nothing {-# INLINE noSVGTitleElement #-} foreign import javascript unsafe "window[\"SVGTitleElement\"]" gTypeSVGTitleElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGTransform". -- -- newtype SVGTransform = SVGTransform { unSVGTransform :: JSVal } instance Eq (SVGTransform) where (SVGTransform a) == (SVGTransform b) = js_eq a b instance PToJSVal SVGTransform where pToJSVal = unSVGTransform {-# INLINE pToJSVal #-} instance PFromJSVal SVGTransform where pFromJSVal = SVGTransform {-# INLINE pFromJSVal #-} instance ToJSVal SVGTransform where toJSVal = return . unSVGTransform {-# INLINE toJSVal #-} instance FromJSVal SVGTransform where fromJSVal = return . fmap SVGTransform . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject SVGTransform where typeGType _ = gTypeSVGTransform {-# INLINE typeGType #-} noSVGTransform :: Maybe SVGTransform noSVGTransform = Nothing {-# INLINE noSVGTransform #-} foreign import javascript unsafe "window[\"SVGTransform\"]" gTypeSVGTransform :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGTransformList". -- -- newtype SVGTransformList = SVGTransformList { unSVGTransformList :: JSVal } instance Eq (SVGTransformList) where (SVGTransformList a) == (SVGTransformList b) = js_eq a b instance PToJSVal SVGTransformList where pToJSVal = unSVGTransformList {-# INLINE pToJSVal #-} instance PFromJSVal SVGTransformList where pFromJSVal = SVGTransformList {-# INLINE pFromJSVal #-} instance ToJSVal SVGTransformList where toJSVal = return . unSVGTransformList {-# INLINE toJSVal #-} instance FromJSVal SVGTransformList where fromJSVal = return . fmap SVGTransformList . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject SVGTransformList where typeGType _ = gTypeSVGTransformList {-# INLINE typeGType #-} noSVGTransformList :: Maybe SVGTransformList noSVGTransformList = Nothing {-# INLINE noSVGTransformList #-} foreign import javascript unsafe "window[\"SVGTransformList\"]" gTypeSVGTransformList :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGURIReference". -- -- newtype SVGURIReference = SVGURIReference { unSVGURIReference :: JSVal } instance Eq (SVGURIReference) where (SVGURIReference a) == (SVGURIReference b) = js_eq a b instance PToJSVal SVGURIReference where pToJSVal = unSVGURIReference {-# INLINE pToJSVal #-} instance PFromJSVal SVGURIReference where pFromJSVal = SVGURIReference {-# INLINE pFromJSVal #-} instance ToJSVal SVGURIReference where toJSVal = return . unSVGURIReference {-# INLINE toJSVal #-} instance FromJSVal SVGURIReference where fromJSVal = return . fmap SVGURIReference . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsGObject o) => IsSVGURIReference o toSVGURIReference :: IsSVGURIReference o => o -> SVGURIReference toSVGURIReference = SVGURIReference . coerce instance IsSVGURIReference SVGURIReference instance IsGObject SVGURIReference where typeGType _ = gTypeSVGURIReference {-# INLINE typeGType #-} noSVGURIReference :: Maybe SVGURIReference noSVGURIReference = Nothing {-# INLINE noSVGURIReference #-} foreign import javascript unsafe "window[\"SVGURIReference\"]" gTypeSVGURIReference :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGUnitTypes". -- -- newtype SVGUnitTypes = SVGUnitTypes { unSVGUnitTypes :: JSVal } instance Eq (SVGUnitTypes) where (SVGUnitTypes a) == (SVGUnitTypes b) = js_eq a b instance PToJSVal SVGUnitTypes where pToJSVal = unSVGUnitTypes {-# INLINE pToJSVal #-} instance PFromJSVal SVGUnitTypes where pFromJSVal = SVGUnitTypes {-# INLINE pFromJSVal #-} instance ToJSVal SVGUnitTypes where toJSVal = return . unSVGUnitTypes {-# INLINE toJSVal #-} instance FromJSVal SVGUnitTypes where fromJSVal = return . fmap SVGUnitTypes . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject SVGUnitTypes where typeGType _ = gTypeSVGUnitTypes {-# INLINE typeGType #-} noSVGUnitTypes :: Maybe SVGUnitTypes noSVGUnitTypes = Nothing {-# INLINE noSVGUnitTypes #-} foreign import javascript unsafe "window[\"SVGUnitTypes\"]" gTypeSVGUnitTypes :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGUseElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGGraphicsElement" -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- * "GHCJS.DOM.SVGTests" -- * "GHCJS.DOM.SVGURIReference" -- * "GHCJS.DOM.SVGExternalResourcesRequired" -- -- newtype SVGUseElement = SVGUseElement { unSVGUseElement :: JSVal } instance Eq (SVGUseElement) where (SVGUseElement a) == (SVGUseElement b) = js_eq a b instance PToJSVal SVGUseElement where pToJSVal = unSVGUseElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGUseElement where pFromJSVal = SVGUseElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGUseElement where toJSVal = return . unSVGUseElement {-# INLINE toJSVal #-} instance FromJSVal SVGUseElement where fromJSVal = return . fmap SVGUseElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGGraphicsElement SVGUseElement instance IsSVGElement SVGUseElement instance IsElement SVGUseElement instance IsNode SVGUseElement instance IsEventTarget SVGUseElement instance IsSlotable SVGUseElement instance IsParentNode SVGUseElement instance IsNonDocumentTypeChildNode SVGUseElement instance IsDocumentAndElementEventHandlers SVGUseElement instance IsChildNode SVGUseElement instance IsAnimatable SVGUseElement instance IsGlobalEventHandlers SVGUseElement instance IsElementCSSInlineStyle SVGUseElement instance IsSVGTests SVGUseElement instance IsSVGURIReference SVGUseElement instance IsSVGExternalResourcesRequired SVGUseElement instance IsGObject SVGUseElement where typeGType _ = gTypeSVGUseElement {-# INLINE typeGType #-} noSVGUseElement :: Maybe SVGUseElement noSVGUseElement = Nothing {-# INLINE noSVGUseElement #-} foreign import javascript unsafe "window[\"SVGUseElement\"]" gTypeSVGUseElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGVKernElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- -- newtype SVGVKernElement = SVGVKernElement { unSVGVKernElement :: JSVal } instance Eq (SVGVKernElement) where (SVGVKernElement a) == (SVGVKernElement b) = js_eq a b instance PToJSVal SVGVKernElement where pToJSVal = unSVGVKernElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGVKernElement where pFromJSVal = SVGVKernElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGVKernElement where toJSVal = return . unSVGVKernElement {-# INLINE toJSVal #-} instance FromJSVal SVGVKernElement where fromJSVal = return . fmap SVGVKernElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGElement SVGVKernElement instance IsElement SVGVKernElement instance IsNode SVGVKernElement instance IsEventTarget SVGVKernElement instance IsSlotable SVGVKernElement instance IsParentNode SVGVKernElement instance IsNonDocumentTypeChildNode SVGVKernElement instance IsDocumentAndElementEventHandlers SVGVKernElement instance IsChildNode SVGVKernElement instance IsAnimatable SVGVKernElement instance IsGlobalEventHandlers SVGVKernElement instance IsElementCSSInlineStyle SVGVKernElement instance IsGObject SVGVKernElement where typeGType _ = gTypeSVGVKernElement {-# INLINE typeGType #-} noSVGVKernElement :: Maybe SVGVKernElement noSVGVKernElement = Nothing {-# INLINE noSVGVKernElement #-} foreign import javascript unsafe "window[\"SVGVKernElement\"]" gTypeSVGVKernElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGViewElement". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGElement" -- * "GHCJS.DOM.Element" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.Slotable" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Animatable" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.ElementCSSInlineStyle" -- * "GHCJS.DOM.SVGZoomAndPan" -- * "GHCJS.DOM.SVGFitToViewBox" -- * "GHCJS.DOM.SVGExternalResourcesRequired" -- -- newtype SVGViewElement = SVGViewElement { unSVGViewElement :: JSVal } instance Eq (SVGViewElement) where (SVGViewElement a) == (SVGViewElement b) = js_eq a b instance PToJSVal SVGViewElement where pToJSVal = unSVGViewElement {-# INLINE pToJSVal #-} instance PFromJSVal SVGViewElement where pFromJSVal = SVGViewElement {-# INLINE pFromJSVal #-} instance ToJSVal SVGViewElement where toJSVal = return . unSVGViewElement {-# INLINE toJSVal #-} instance FromJSVal SVGViewElement where fromJSVal = return . fmap SVGViewElement . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGElement SVGViewElement instance IsElement SVGViewElement instance IsNode SVGViewElement instance IsEventTarget SVGViewElement instance IsSlotable SVGViewElement instance IsParentNode SVGViewElement instance IsNonDocumentTypeChildNode SVGViewElement instance IsDocumentAndElementEventHandlers SVGViewElement instance IsChildNode SVGViewElement instance IsAnimatable SVGViewElement instance IsGlobalEventHandlers SVGViewElement instance IsElementCSSInlineStyle SVGViewElement instance IsSVGZoomAndPan SVGViewElement instance IsSVGFitToViewBox SVGViewElement instance IsSVGExternalResourcesRequired SVGViewElement instance IsGObject SVGViewElement where typeGType _ = gTypeSVGViewElement {-# INLINE typeGType #-} noSVGViewElement :: Maybe SVGViewElement noSVGViewElement = Nothing {-# INLINE noSVGViewElement #-} foreign import javascript unsafe "window[\"SVGViewElement\"]" gTypeSVGViewElement :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGViewSpec". -- Base interface functions are in: -- -- * "GHCJS.DOM.SVGFitToViewBox" -- -- newtype SVGViewSpec = SVGViewSpec { unSVGViewSpec :: JSVal } instance Eq (SVGViewSpec) where (SVGViewSpec a) == (SVGViewSpec b) = js_eq a b instance PToJSVal SVGViewSpec where pToJSVal = unSVGViewSpec {-# INLINE pToJSVal #-} instance PFromJSVal SVGViewSpec where pFromJSVal = SVGViewSpec {-# INLINE pFromJSVal #-} instance ToJSVal SVGViewSpec where toJSVal = return . unSVGViewSpec {-# INLINE toJSVal #-} instance FromJSVal SVGViewSpec where fromJSVal = return . fmap SVGViewSpec . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsSVGFitToViewBox SVGViewSpec instance IsGObject SVGViewSpec where typeGType _ = gTypeSVGViewSpec {-# INLINE typeGType #-} noSVGViewSpec :: Maybe SVGViewSpec noSVGViewSpec = Nothing {-# INLINE noSVGViewSpec #-} foreign import javascript unsafe "window[\"SVGViewSpec\"]" gTypeSVGViewSpec :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGZoomAndPan". -- -- newtype SVGZoomAndPan = SVGZoomAndPan { unSVGZoomAndPan :: JSVal } instance Eq (SVGZoomAndPan) where (SVGZoomAndPan a) == (SVGZoomAndPan b) = js_eq a b instance PToJSVal SVGZoomAndPan where pToJSVal = unSVGZoomAndPan {-# INLINE pToJSVal #-} instance PFromJSVal SVGZoomAndPan where pFromJSVal = SVGZoomAndPan {-# INLINE pFromJSVal #-} instance ToJSVal SVGZoomAndPan where toJSVal = return . unSVGZoomAndPan {-# INLINE toJSVal #-} instance FromJSVal SVGZoomAndPan where fromJSVal = return . fmap SVGZoomAndPan . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsGObject o) => IsSVGZoomAndPan o toSVGZoomAndPan :: IsSVGZoomAndPan o => o -> SVGZoomAndPan toSVGZoomAndPan = SVGZoomAndPan . coerce instance IsSVGZoomAndPan SVGZoomAndPan instance IsGObject SVGZoomAndPan where typeGType _ = gTypeSVGZoomAndPan {-# INLINE typeGType #-} noSVGZoomAndPan :: Maybe SVGZoomAndPan noSVGZoomAndPan = Nothing {-# INLINE noSVGZoomAndPan #-} foreign import javascript unsafe "window[\"SVGZoomAndPan\"]" gTypeSVGZoomAndPan :: GType -- | Functions for this inteface are in "GHCJS.DOM.SVGZoomEvent". -- Base interface functions are in: -- -- * "GHCJS.DOM.UIEvent" -- * "GHCJS.DOM.Event" -- -- newtype SVGZoomEvent = SVGZoomEvent { unSVGZoomEvent :: JSVal } instance Eq (SVGZoomEvent) where (SVGZoomEvent a) == (SVGZoomEvent b) = js_eq a b instance PToJSVal SVGZoomEvent where pToJSVal = unSVGZoomEvent {-# INLINE pToJSVal #-} instance PFromJSVal SVGZoomEvent where pFromJSVal = SVGZoomEvent {-# INLINE pFromJSVal #-} instance ToJSVal SVGZoomEvent where toJSVal = return . unSVGZoomEvent {-# INLINE toJSVal #-} instance FromJSVal SVGZoomEvent where fromJSVal = return . fmap SVGZoomEvent . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsUIEvent SVGZoomEvent instance IsEvent SVGZoomEvent instance IsGObject SVGZoomEvent where typeGType _ = gTypeSVGZoomEvent {-# INLINE typeGType #-} noSVGZoomEvent :: Maybe SVGZoomEvent noSVGZoomEvent = Nothing {-# INLINE noSVGZoomEvent #-} foreign import javascript unsafe "window[\"SVGZoomEvent\"]" gTypeSVGZoomEvent :: GType -- | Functions for this inteface are in "GHCJS.DOM.Screen". -- -- newtype Screen = Screen { unScreen :: JSVal } instance Eq (Screen) where (Screen a) == (Screen b) = js_eq a b instance PToJSVal Screen where pToJSVal = unScreen {-# INLINE pToJSVal #-} instance PFromJSVal Screen where pFromJSVal = Screen {-# INLINE pFromJSVal #-} instance ToJSVal Screen where toJSVal = return . unScreen {-# INLINE toJSVal #-} instance FromJSVal Screen where fromJSVal = return . fmap Screen . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject Screen where typeGType _ = gTypeScreen {-# INLINE typeGType #-} noScreen :: Maybe Screen noScreen = Nothing {-# INLINE noScreen #-} foreign import javascript unsafe "window[\"Screen\"]" gTypeScreen :: GType -- | Functions for this inteface are in "GHCJS.DOM.ScriptProcessorNode". -- Base interface functions are in: -- -- * "GHCJS.DOM.AudioNode" -- * "GHCJS.DOM.EventTarget" -- -- newtype ScriptProcessorNode = ScriptProcessorNode { unScriptProcessorNode :: JSVal } instance Eq (ScriptProcessorNode) where (ScriptProcessorNode a) == (ScriptProcessorNode b) = js_eq a b instance PToJSVal ScriptProcessorNode where pToJSVal = unScriptProcessorNode {-# INLINE pToJSVal #-} instance PFromJSVal ScriptProcessorNode where pFromJSVal = ScriptProcessorNode {-# INLINE pFromJSVal #-} instance ToJSVal ScriptProcessorNode where toJSVal = return . unScriptProcessorNode {-# INLINE toJSVal #-} instance FromJSVal ScriptProcessorNode where fromJSVal = return . fmap ScriptProcessorNode . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsAudioNode ScriptProcessorNode instance IsEventTarget ScriptProcessorNode instance IsGObject ScriptProcessorNode where typeGType _ = gTypeScriptProcessorNode {-# INLINE typeGType #-} noScriptProcessorNode :: Maybe ScriptProcessorNode noScriptProcessorNode = Nothing {-# INLINE noScriptProcessorNode #-} foreign import javascript unsafe "window[\"ScriptProcessorNode\"]" gTypeScriptProcessorNode :: GType -- | Functions for this inteface are in "GHCJS.DOM.ScrollToOptions". -- -- newtype ScrollToOptions = ScrollToOptions { unScrollToOptions :: JSVal } instance Eq (ScrollToOptions) where (ScrollToOptions a) == (ScrollToOptions b) = js_eq a b instance PToJSVal ScrollToOptions where pToJSVal = unScrollToOptions {-# INLINE pToJSVal #-} instance PFromJSVal ScrollToOptions where pFromJSVal = ScrollToOptions {-# INLINE pFromJSVal #-} instance ToJSVal ScrollToOptions where toJSVal = return . unScrollToOptions {-# INLINE toJSVal #-} instance FromJSVal ScrollToOptions where fromJSVal = return . fmap ScrollToOptions . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject ScrollToOptions where typeGType _ = gTypeScrollToOptions {-# INLINE typeGType #-} noScrollToOptions :: Maybe ScrollToOptions noScrollToOptions = Nothing {-# INLINE noScrollToOptions #-} foreign import javascript unsafe "window[\"ScrollToOptions\"]" gTypeScrollToOptions :: GType -- | Functions for this inteface are in "GHCJS.DOM.SecurityPolicyViolationEvent". -- Base interface functions are in: -- -- * "GHCJS.DOM.Event" -- -- newtype SecurityPolicyViolationEvent = SecurityPolicyViolationEvent { unSecurityPolicyViolationEvent :: JSVal } instance Eq (SecurityPolicyViolationEvent) where (SecurityPolicyViolationEvent a) == (SecurityPolicyViolationEvent b) = js_eq a b instance PToJSVal SecurityPolicyViolationEvent where pToJSVal = unSecurityPolicyViolationEvent {-# INLINE pToJSVal #-} instance PFromJSVal SecurityPolicyViolationEvent where pFromJSVal = SecurityPolicyViolationEvent {-# INLINE pFromJSVal #-} instance ToJSVal SecurityPolicyViolationEvent where toJSVal = return . unSecurityPolicyViolationEvent {-# INLINE toJSVal #-} instance FromJSVal SecurityPolicyViolationEvent where fromJSVal = return . fmap SecurityPolicyViolationEvent . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEvent SecurityPolicyViolationEvent instance IsGObject SecurityPolicyViolationEvent where typeGType _ = gTypeSecurityPolicyViolationEvent {-# INLINE typeGType #-} noSecurityPolicyViolationEvent :: Maybe SecurityPolicyViolationEvent noSecurityPolicyViolationEvent = Nothing {-# INLINE noSecurityPolicyViolationEvent #-} foreign import javascript unsafe "window[\"SecurityPolicyViolationEvent\"]" gTypeSecurityPolicyViolationEvent :: GType -- | Functions for this inteface are in "GHCJS.DOM.SecurityPolicyViolationEventInit". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventInit" -- -- newtype SecurityPolicyViolationEventInit = SecurityPolicyViolationEventInit { unSecurityPolicyViolationEventInit :: JSVal } instance Eq (SecurityPolicyViolationEventInit) where (SecurityPolicyViolationEventInit a) == (SecurityPolicyViolationEventInit b) = js_eq a b instance PToJSVal SecurityPolicyViolationEventInit where pToJSVal = unSecurityPolicyViolationEventInit {-# INLINE pToJSVal #-} instance PFromJSVal SecurityPolicyViolationEventInit where pFromJSVal = SecurityPolicyViolationEventInit {-# INLINE pFromJSVal #-} instance ToJSVal SecurityPolicyViolationEventInit where toJSVal = return . unSecurityPolicyViolationEventInit {-# INLINE toJSVal #-} instance FromJSVal SecurityPolicyViolationEventInit where fromJSVal = return . fmap SecurityPolicyViolationEventInit . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventInit SecurityPolicyViolationEventInit instance IsGObject SecurityPolicyViolationEventInit where typeGType _ = gTypeSecurityPolicyViolationEventInit {-# INLINE typeGType #-} noSecurityPolicyViolationEventInit :: Maybe SecurityPolicyViolationEventInit noSecurityPolicyViolationEventInit = Nothing {-# INLINE noSecurityPolicyViolationEventInit #-} foreign import javascript unsafe "window[\"SecurityPolicyViolationEventInit\"]" gTypeSecurityPolicyViolationEventInit :: GType -- | Functions for this inteface are in "GHCJS.DOM.Selection". -- -- newtype Selection = Selection { unSelection :: JSVal } instance Eq (Selection) where (Selection a) == (Selection b) = js_eq a b instance PToJSVal Selection where pToJSVal = unSelection {-# INLINE pToJSVal #-} instance PFromJSVal Selection where pFromJSVal = Selection {-# INLINE pFromJSVal #-} instance ToJSVal Selection where toJSVal = return . unSelection {-# INLINE toJSVal #-} instance FromJSVal Selection where fromJSVal = return . fmap Selection . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject Selection where typeGType _ = gTypeSelection {-# INLINE typeGType #-} noSelection :: Maybe Selection noSelection = Nothing {-# INLINE noSelection #-} foreign import javascript unsafe "window[\"Selection\"]" gTypeSelection :: GType -- | Functions for this inteface are in "GHCJS.DOM.ShadowRoot". -- Base interface functions are in: -- -- * "GHCJS.DOM.DocumentFragment" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.NonElementParentNode" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.DocumentOrShadowRoot" -- -- newtype ShadowRoot = ShadowRoot { unShadowRoot :: JSVal } instance Eq (ShadowRoot) where (ShadowRoot a) == (ShadowRoot b) = js_eq a b instance PToJSVal ShadowRoot where pToJSVal = unShadowRoot {-# INLINE pToJSVal #-} instance PFromJSVal ShadowRoot where pFromJSVal = ShadowRoot {-# INLINE pFromJSVal #-} instance ToJSVal ShadowRoot where toJSVal = return . unShadowRoot {-# INLINE toJSVal #-} instance FromJSVal ShadowRoot where fromJSVal = return . fmap ShadowRoot . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsDocumentFragment ShadowRoot instance IsNode ShadowRoot instance IsEventTarget ShadowRoot instance IsNonElementParentNode ShadowRoot instance IsParentNode ShadowRoot instance IsDocumentOrShadowRoot ShadowRoot instance IsGObject ShadowRoot where typeGType _ = gTypeShadowRoot {-# INLINE typeGType #-} noShadowRoot :: Maybe ShadowRoot noShadowRoot = Nothing {-# INLINE noShadowRoot #-} foreign import javascript unsafe "window[\"ShadowRoot\"]" gTypeShadowRoot :: GType -- | Functions for this inteface are in "GHCJS.DOM.ShadowRootInit". -- -- newtype ShadowRootInit = ShadowRootInit { unShadowRootInit :: JSVal } instance Eq (ShadowRootInit) where (ShadowRootInit a) == (ShadowRootInit b) = js_eq a b instance PToJSVal ShadowRootInit where pToJSVal = unShadowRootInit {-# INLINE pToJSVal #-} instance PFromJSVal ShadowRootInit where pFromJSVal = ShadowRootInit {-# INLINE pFromJSVal #-} instance ToJSVal ShadowRootInit where toJSVal = return . unShadowRootInit {-# INLINE toJSVal #-} instance FromJSVal ShadowRootInit where fromJSVal = return . fmap ShadowRootInit . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject ShadowRootInit where typeGType _ = gTypeShadowRootInit {-# INLINE typeGType #-} noShadowRootInit :: Maybe ShadowRootInit noShadowRootInit = Nothing {-# INLINE noShadowRootInit #-} foreign import javascript unsafe "window[\"ShadowRootInit\"]" gTypeShadowRootInit :: GType -- | Functions for this inteface are in "GHCJS.DOM.SiteBoundCredential". -- Base interface functions are in: -- -- * "GHCJS.DOM.BasicCredential" -- -- newtype SiteBoundCredential = SiteBoundCredential { unSiteBoundCredential :: JSVal } instance Eq (SiteBoundCredential) where (SiteBoundCredential a) == (SiteBoundCredential b) = js_eq a b instance PToJSVal SiteBoundCredential where pToJSVal = unSiteBoundCredential {-# INLINE pToJSVal #-} instance PFromJSVal SiteBoundCredential where pFromJSVal = SiteBoundCredential {-# INLINE pFromJSVal #-} instance ToJSVal SiteBoundCredential where toJSVal = return . unSiteBoundCredential {-# INLINE toJSVal #-} instance FromJSVal SiteBoundCredential where fromJSVal = return . fmap SiteBoundCredential . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsBasicCredential o, IsGObject o) => IsSiteBoundCredential o toSiteBoundCredential :: IsSiteBoundCredential o => o -> SiteBoundCredential toSiteBoundCredential = SiteBoundCredential . coerce instance IsSiteBoundCredential SiteBoundCredential instance IsBasicCredential SiteBoundCredential instance IsGObject SiteBoundCredential where typeGType _ = gTypeSiteBoundCredential {-# INLINE typeGType #-} noSiteBoundCredential :: Maybe SiteBoundCredential noSiteBoundCredential = Nothing {-# INLINE noSiteBoundCredential #-} foreign import javascript unsafe "window[\"SiteBoundCredential\"]" gTypeSiteBoundCredential :: GType -- | Functions for this inteface are in "GHCJS.DOM.SiteBoundCredentialData". -- Base interface functions are in: -- -- * "GHCJS.DOM.CredentialData" -- -- newtype SiteBoundCredentialData = SiteBoundCredentialData { unSiteBoundCredentialData :: JSVal } instance Eq (SiteBoundCredentialData) where (SiteBoundCredentialData a) == (SiteBoundCredentialData b) = js_eq a b instance PToJSVal SiteBoundCredentialData where pToJSVal = unSiteBoundCredentialData {-# INLINE pToJSVal #-} instance PFromJSVal SiteBoundCredentialData where pFromJSVal = SiteBoundCredentialData {-# INLINE pFromJSVal #-} instance ToJSVal SiteBoundCredentialData where toJSVal = return . unSiteBoundCredentialData {-# INLINE toJSVal #-} instance FromJSVal SiteBoundCredentialData where fromJSVal = return . fmap SiteBoundCredentialData . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsCredentialData o, IsGObject o) => IsSiteBoundCredentialData o toSiteBoundCredentialData :: IsSiteBoundCredentialData o => o -> SiteBoundCredentialData toSiteBoundCredentialData = SiteBoundCredentialData . coerce instance IsSiteBoundCredentialData SiteBoundCredentialData instance IsCredentialData SiteBoundCredentialData instance IsGObject SiteBoundCredentialData where typeGType _ = gTypeSiteBoundCredentialData {-# INLINE typeGType #-} noSiteBoundCredentialData :: Maybe SiteBoundCredentialData noSiteBoundCredentialData = Nothing {-# INLINE noSiteBoundCredentialData #-} foreign import javascript unsafe "window[\"SiteBoundCredentialData\"]" gTypeSiteBoundCredentialData :: GType -- | Functions for this inteface are in "GHCJS.DOM.Slotable". -- -- newtype Slotable = Slotable { unSlotable :: JSVal } instance Eq (Slotable) where (Slotable a) == (Slotable b) = js_eq a b instance PToJSVal Slotable where pToJSVal = unSlotable {-# INLINE pToJSVal #-} instance PFromJSVal Slotable where pFromJSVal = Slotable {-# INLINE pFromJSVal #-} instance ToJSVal Slotable where toJSVal = return . unSlotable {-# INLINE toJSVal #-} instance FromJSVal Slotable where fromJSVal = return . fmap Slotable . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsGObject o) => IsSlotable o toSlotable :: IsSlotable o => o -> Slotable toSlotable = Slotable . coerce instance IsSlotable Slotable instance IsGObject Slotable where typeGType _ = gTypeSlotable {-# INLINE typeGType #-} noSlotable :: Maybe Slotable noSlotable = Nothing {-# INLINE noSlotable #-} foreign import javascript unsafe "window[\"Slotable\"]" gTypeSlotable :: GType -- | Functions for this inteface are in "GHCJS.DOM.SourceBuffer". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventTarget" -- -- newtype SourceBuffer = SourceBuffer { unSourceBuffer :: JSVal } instance Eq (SourceBuffer) where (SourceBuffer a) == (SourceBuffer b) = js_eq a b instance PToJSVal SourceBuffer where pToJSVal = unSourceBuffer {-# INLINE pToJSVal #-} instance PFromJSVal SourceBuffer where pFromJSVal = SourceBuffer {-# INLINE pFromJSVal #-} instance ToJSVal SourceBuffer where toJSVal = return . unSourceBuffer {-# INLINE toJSVal #-} instance FromJSVal SourceBuffer where fromJSVal = return . fmap SourceBuffer . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventTarget SourceBuffer instance IsGObject SourceBuffer where typeGType _ = gTypeSourceBuffer {-# INLINE typeGType #-} noSourceBuffer :: Maybe SourceBuffer noSourceBuffer = Nothing {-# INLINE noSourceBuffer #-} foreign import javascript unsafe "window[\"SourceBuffer\"]" gTypeSourceBuffer :: GType -- | Functions for this inteface are in "GHCJS.DOM.SourceBufferList". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventTarget" -- -- newtype SourceBufferList = SourceBufferList { unSourceBufferList :: JSVal } instance Eq (SourceBufferList) where (SourceBufferList a) == (SourceBufferList b) = js_eq a b instance PToJSVal SourceBufferList where pToJSVal = unSourceBufferList {-# INLINE pToJSVal #-} instance PFromJSVal SourceBufferList where pFromJSVal = SourceBufferList {-# INLINE pFromJSVal #-} instance ToJSVal SourceBufferList where toJSVal = return . unSourceBufferList {-# INLINE toJSVal #-} instance FromJSVal SourceBufferList where fromJSVal = return . fmap SourceBufferList . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventTarget SourceBufferList instance IsGObject SourceBufferList where typeGType _ = gTypeSourceBufferList {-# INLINE typeGType #-} noSourceBufferList :: Maybe SourceBufferList noSourceBufferList = Nothing {-# INLINE noSourceBufferList #-} foreign import javascript unsafe "window[\"SourceBufferList\"]" gTypeSourceBufferList :: GType -- | Functions for this inteface are in "GHCJS.DOM.SpeechSynthesis". -- -- newtype SpeechSynthesis = SpeechSynthesis { unSpeechSynthesis :: JSVal } instance Eq (SpeechSynthesis) where (SpeechSynthesis a) == (SpeechSynthesis b) = js_eq a b instance PToJSVal SpeechSynthesis where pToJSVal = unSpeechSynthesis {-# INLINE pToJSVal #-} instance PFromJSVal SpeechSynthesis where pFromJSVal = SpeechSynthesis {-# INLINE pFromJSVal #-} instance ToJSVal SpeechSynthesis where toJSVal = return . unSpeechSynthesis {-# INLINE toJSVal #-} instance FromJSVal SpeechSynthesis where fromJSVal = return . fmap SpeechSynthesis . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject SpeechSynthesis where typeGType _ = gTypeSpeechSynthesis {-# INLINE typeGType #-} noSpeechSynthesis :: Maybe SpeechSynthesis noSpeechSynthesis = Nothing {-# INLINE noSpeechSynthesis #-} foreign import javascript unsafe "window[\"SpeechSynthesis\"]" gTypeSpeechSynthesis :: GType -- | Functions for this inteface are in "GHCJS.DOM.SpeechSynthesisEvent". -- Base interface functions are in: -- -- * "GHCJS.DOM.Event" -- -- newtype SpeechSynthesisEvent = SpeechSynthesisEvent { unSpeechSynthesisEvent :: JSVal } instance Eq (SpeechSynthesisEvent) where (SpeechSynthesisEvent a) == (SpeechSynthesisEvent b) = js_eq a b instance PToJSVal SpeechSynthesisEvent where pToJSVal = unSpeechSynthesisEvent {-# INLINE pToJSVal #-} instance PFromJSVal SpeechSynthesisEvent where pFromJSVal = SpeechSynthesisEvent {-# INLINE pFromJSVal #-} instance ToJSVal SpeechSynthesisEvent where toJSVal = return . unSpeechSynthesisEvent {-# INLINE toJSVal #-} instance FromJSVal SpeechSynthesisEvent where fromJSVal = return . fmap SpeechSynthesisEvent . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEvent SpeechSynthesisEvent instance IsGObject SpeechSynthesisEvent where typeGType _ = gTypeSpeechSynthesisEvent {-# INLINE typeGType #-} noSpeechSynthesisEvent :: Maybe SpeechSynthesisEvent noSpeechSynthesisEvent = Nothing {-# INLINE noSpeechSynthesisEvent #-} foreign import javascript unsafe "window[\"SpeechSynthesisEvent\"]" gTypeSpeechSynthesisEvent :: GType -- | Functions for this inteface are in "GHCJS.DOM.SpeechSynthesisUtterance". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventTarget" -- -- newtype SpeechSynthesisUtterance = SpeechSynthesisUtterance { unSpeechSynthesisUtterance :: JSVal } instance Eq (SpeechSynthesisUtterance) where (SpeechSynthesisUtterance a) == (SpeechSynthesisUtterance b) = js_eq a b instance PToJSVal SpeechSynthesisUtterance where pToJSVal = unSpeechSynthesisUtterance {-# INLINE pToJSVal #-} instance PFromJSVal SpeechSynthesisUtterance where pFromJSVal = SpeechSynthesisUtterance {-# INLINE pFromJSVal #-} instance ToJSVal SpeechSynthesisUtterance where toJSVal = return . unSpeechSynthesisUtterance {-# INLINE toJSVal #-} instance FromJSVal SpeechSynthesisUtterance where fromJSVal = return . fmap SpeechSynthesisUtterance . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventTarget SpeechSynthesisUtterance instance IsGObject SpeechSynthesisUtterance where typeGType _ = gTypeSpeechSynthesisUtterance {-# INLINE typeGType #-} noSpeechSynthesisUtterance :: Maybe SpeechSynthesisUtterance noSpeechSynthesisUtterance = Nothing {-# INLINE noSpeechSynthesisUtterance #-} foreign import javascript unsafe "window[\"SpeechSynthesisUtterance\"]" gTypeSpeechSynthesisUtterance :: GType -- | Functions for this inteface are in "GHCJS.DOM.SpeechSynthesisVoice". -- -- newtype SpeechSynthesisVoice = SpeechSynthesisVoice { unSpeechSynthesisVoice :: JSVal } instance Eq (SpeechSynthesisVoice) where (SpeechSynthesisVoice a) == (SpeechSynthesisVoice b) = js_eq a b instance PToJSVal SpeechSynthesisVoice where pToJSVal = unSpeechSynthesisVoice {-# INLINE pToJSVal #-} instance PFromJSVal SpeechSynthesisVoice where pFromJSVal = SpeechSynthesisVoice {-# INLINE pFromJSVal #-} instance ToJSVal SpeechSynthesisVoice where toJSVal = return . unSpeechSynthesisVoice {-# INLINE toJSVal #-} instance FromJSVal SpeechSynthesisVoice where fromJSVal = return . fmap SpeechSynthesisVoice . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject SpeechSynthesisVoice where typeGType _ = gTypeSpeechSynthesisVoice {-# INLINE typeGType #-} noSpeechSynthesisVoice :: Maybe SpeechSynthesisVoice noSpeechSynthesisVoice = Nothing {-# INLINE noSpeechSynthesisVoice #-} foreign import javascript unsafe "window[\"SpeechSynthesisVoice\"]" gTypeSpeechSynthesisVoice :: GType -- | Functions for this inteface are in "GHCJS.DOM.StaticRange". -- -- newtype StaticRange = StaticRange { unStaticRange :: JSVal } instance Eq (StaticRange) where (StaticRange a) == (StaticRange b) = js_eq a b instance PToJSVal StaticRange where pToJSVal = unStaticRange {-# INLINE pToJSVal #-} instance PFromJSVal StaticRange where pFromJSVal = StaticRange {-# INLINE pFromJSVal #-} instance ToJSVal StaticRange where toJSVal = return . unStaticRange {-# INLINE toJSVal #-} instance FromJSVal StaticRange where fromJSVal = return . fmap StaticRange . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject StaticRange where typeGType _ = gTypeStaticRange {-# INLINE typeGType #-} noStaticRange :: Maybe StaticRange noStaticRange = Nothing {-# INLINE noStaticRange #-} foreign import javascript unsafe "window[\"StaticRange\"]" gTypeStaticRange :: GType -- | Functions for this inteface are in "GHCJS.DOM.Storage". -- -- newtype Storage = Storage { unStorage :: JSVal } instance Eq (Storage) where (Storage a) == (Storage b) = js_eq a b instance PToJSVal Storage where pToJSVal = unStorage {-# INLINE pToJSVal #-} instance PFromJSVal Storage where pFromJSVal = Storage {-# INLINE pFromJSVal #-} instance ToJSVal Storage where toJSVal = return . unStorage {-# INLINE toJSVal #-} instance FromJSVal Storage where fromJSVal = return . fmap Storage . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject Storage where typeGType _ = gTypeStorage {-# INLINE typeGType #-} noStorage :: Maybe Storage noStorage = Nothing {-# INLINE noStorage #-} foreign import javascript unsafe "window[\"Storage\"]" gTypeStorage :: GType -- | Functions for this inteface are in "GHCJS.DOM.StorageEvent". -- Base interface functions are in: -- -- * "GHCJS.DOM.Event" -- -- newtype StorageEvent = StorageEvent { unStorageEvent :: JSVal } instance Eq (StorageEvent) where (StorageEvent a) == (StorageEvent b) = js_eq a b instance PToJSVal StorageEvent where pToJSVal = unStorageEvent {-# INLINE pToJSVal #-} instance PFromJSVal StorageEvent where pFromJSVal = StorageEvent {-# INLINE pFromJSVal #-} instance ToJSVal StorageEvent where toJSVal = return . unStorageEvent {-# INLINE toJSVal #-} instance FromJSVal StorageEvent where fromJSVal = return . fmap StorageEvent . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEvent StorageEvent instance IsGObject StorageEvent where typeGType _ = gTypeStorageEvent {-# INLINE typeGType #-} noStorageEvent :: Maybe StorageEvent noStorageEvent = Nothing {-# INLINE noStorageEvent #-} foreign import javascript unsafe "window[\"StorageEvent\"]" gTypeStorageEvent :: GType -- | Functions for this inteface are in "GHCJS.DOM.StorageEventInit". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventInit" -- -- newtype StorageEventInit = StorageEventInit { unStorageEventInit :: JSVal } instance Eq (StorageEventInit) where (StorageEventInit a) == (StorageEventInit b) = js_eq a b instance PToJSVal StorageEventInit where pToJSVal = unStorageEventInit {-# INLINE pToJSVal #-} instance PFromJSVal StorageEventInit where pFromJSVal = StorageEventInit {-# INLINE pFromJSVal #-} instance ToJSVal StorageEventInit where toJSVal = return . unStorageEventInit {-# INLINE toJSVal #-} instance FromJSVal StorageEventInit where fromJSVal = return . fmap StorageEventInit . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventInit StorageEventInit instance IsGObject StorageEventInit where typeGType _ = gTypeStorageEventInit {-# INLINE typeGType #-} noStorageEventInit :: Maybe StorageEventInit noStorageEventInit = Nothing {-# INLINE noStorageEventInit #-} foreign import javascript unsafe "window[\"StorageEventInit\"]" gTypeStorageEventInit :: GType -- | Functions for this inteface are in "GHCJS.DOM.StorageInfo". -- -- newtype StorageInfo = StorageInfo { unStorageInfo :: JSVal } instance Eq (StorageInfo) where (StorageInfo a) == (StorageInfo b) = js_eq a b instance PToJSVal StorageInfo where pToJSVal = unStorageInfo {-# INLINE pToJSVal #-} instance PFromJSVal StorageInfo where pFromJSVal = StorageInfo {-# INLINE pFromJSVal #-} instance ToJSVal StorageInfo where toJSVal = return . unStorageInfo {-# INLINE toJSVal #-} instance FromJSVal StorageInfo where fromJSVal = return . fmap StorageInfo . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject StorageInfo where typeGType _ = gTypeStorageInfo {-# INLINE typeGType #-} noStorageInfo :: Maybe StorageInfo noStorageInfo = Nothing {-# INLINE noStorageInfo #-} foreign import javascript unsafe "window[\"StorageInfo\"]" gTypeStorageInfo :: GType -- | Functions for this inteface are in "GHCJS.DOM.StorageQuota". -- -- newtype StorageQuota = StorageQuota { unStorageQuota :: JSVal } instance Eq (StorageQuota) where (StorageQuota a) == (StorageQuota b) = js_eq a b instance PToJSVal StorageQuota where pToJSVal = unStorageQuota {-# INLINE pToJSVal #-} instance PFromJSVal StorageQuota where pFromJSVal = StorageQuota {-# INLINE pFromJSVal #-} instance ToJSVal StorageQuota where toJSVal = return . unStorageQuota {-# INLINE toJSVal #-} instance FromJSVal StorageQuota where fromJSVal = return . fmap StorageQuota . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject StorageQuota where typeGType _ = gTypeStorageQuota {-# INLINE typeGType #-} noStorageQuota :: Maybe StorageQuota noStorageQuota = Nothing {-# INLINE noStorageQuota #-} foreign import javascript unsafe "window[\"StorageQuota\"]" gTypeStorageQuota :: GType -- | Functions for this inteface are in "GHCJS.DOM.StyleMedia". -- -- newtype StyleMedia = StyleMedia { unStyleMedia :: JSVal } instance Eq (StyleMedia) where (StyleMedia a) == (StyleMedia b) = js_eq a b instance PToJSVal StyleMedia where pToJSVal = unStyleMedia {-# INLINE pToJSVal #-} instance PFromJSVal StyleMedia where pFromJSVal = StyleMedia {-# INLINE pFromJSVal #-} instance ToJSVal StyleMedia where toJSVal = return . unStyleMedia {-# INLINE toJSVal #-} instance FromJSVal StyleMedia where fromJSVal = return . fmap StyleMedia . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject StyleMedia where typeGType _ = gTypeStyleMedia {-# INLINE typeGType #-} noStyleMedia :: Maybe StyleMedia noStyleMedia = Nothing {-# INLINE noStyleMedia #-} foreign import javascript unsafe "window[\"StyleMedia\"]" gTypeStyleMedia :: GType -- | Functions for this inteface are in "GHCJS.DOM.StyleSheet". -- -- newtype StyleSheet = StyleSheet { unStyleSheet :: JSVal } instance Eq (StyleSheet) where (StyleSheet a) == (StyleSheet b) = js_eq a b instance PToJSVal StyleSheet where pToJSVal = unStyleSheet {-# INLINE pToJSVal #-} instance PFromJSVal StyleSheet where pFromJSVal = StyleSheet {-# INLINE pFromJSVal #-} instance ToJSVal StyleSheet where toJSVal = return . unStyleSheet {-# INLINE toJSVal #-} instance FromJSVal StyleSheet where fromJSVal = return . fmap StyleSheet . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsGObject o) => IsStyleSheet o toStyleSheet :: IsStyleSheet o => o -> StyleSheet toStyleSheet = StyleSheet . coerce instance IsStyleSheet StyleSheet instance IsGObject StyleSheet where typeGType _ = gTypeStyleSheet {-# INLINE typeGType #-} noStyleSheet :: Maybe StyleSheet noStyleSheet = Nothing {-# INLINE noStyleSheet #-} foreign import javascript unsafe "window[\"StyleSheet\"]" gTypeStyleSheet :: GType -- | Functions for this inteface are in "GHCJS.DOM.StyleSheetList". -- -- newtype StyleSheetList = StyleSheetList { unStyleSheetList :: JSVal } instance Eq (StyleSheetList) where (StyleSheetList a) == (StyleSheetList b) = js_eq a b instance PToJSVal StyleSheetList where pToJSVal = unStyleSheetList {-# INLINE pToJSVal #-} instance PFromJSVal StyleSheetList where pFromJSVal = StyleSheetList {-# INLINE pFromJSVal #-} instance ToJSVal StyleSheetList where toJSVal = return . unStyleSheetList {-# INLINE toJSVal #-} instance FromJSVal StyleSheetList where fromJSVal = return . fmap StyleSheetList . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject StyleSheetList where typeGType _ = gTypeStyleSheetList {-# INLINE typeGType #-} noStyleSheetList :: Maybe StyleSheetList noStyleSheetList = Nothing {-# INLINE noStyleSheetList #-} foreign import javascript unsafe "window[\"StyleSheetList\"]" gTypeStyleSheetList :: GType -- | Functions for this inteface are in "GHCJS.DOM.SubtleCrypto". -- -- newtype SubtleCrypto = SubtleCrypto { unSubtleCrypto :: JSVal } instance Eq (SubtleCrypto) where (SubtleCrypto a) == (SubtleCrypto b) = js_eq a b instance PToJSVal SubtleCrypto where pToJSVal = unSubtleCrypto {-# INLINE pToJSVal #-} instance PFromJSVal SubtleCrypto where pFromJSVal = SubtleCrypto {-# INLINE pFromJSVal #-} instance ToJSVal SubtleCrypto where toJSVal = return . unSubtleCrypto {-# INLINE toJSVal #-} instance FromJSVal SubtleCrypto where fromJSVal = return . fmap SubtleCrypto . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject SubtleCrypto where typeGType _ = gTypeSubtleCrypto {-# INLINE typeGType #-} noSubtleCrypto :: Maybe SubtleCrypto noSubtleCrypto = Nothing {-# INLINE noSubtleCrypto #-} foreign import javascript unsafe "window[\"WebKitSubtleCrypto\"]" gTypeSubtleCrypto :: GType -- | Functions for this inteface are in "GHCJS.DOM.Text". -- Base interface functions are in: -- -- * "GHCJS.DOM.CharacterData" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.NonDocumentTypeChildNode" -- * "GHCJS.DOM.ChildNode" -- * "GHCJS.DOM.Slotable" -- -- newtype Text = Text { unText :: JSVal } instance Eq (Text) where (Text a) == (Text b) = js_eq a b instance PToJSVal Text where pToJSVal = unText {-# INLINE pToJSVal #-} instance PFromJSVal Text where pFromJSVal = Text {-# INLINE pFromJSVal #-} instance ToJSVal Text where toJSVal = return . unText {-# INLINE toJSVal #-} instance FromJSVal Text where fromJSVal = return . fmap Text . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsCharacterData o, IsNode o, IsEventTarget o, IsNonDocumentTypeChildNode o, IsChildNode o, IsSlotable o, IsGObject o) => IsText o toText :: IsText o => o -> Text toText = Text . coerce instance IsText Text instance IsCharacterData Text instance IsNode Text instance IsEventTarget Text instance IsNonDocumentTypeChildNode Text instance IsChildNode Text instance IsSlotable Text instance IsGObject Text where typeGType _ = gTypeText {-# INLINE typeGType #-} noText :: Maybe Text noText = Nothing {-# INLINE noText #-} foreign import javascript unsafe "window[\"Text\"]" gTypeText :: GType -- | Functions for this inteface are in "GHCJS.DOM.TextDecodeOptions". -- -- newtype TextDecodeOptions = TextDecodeOptions { unTextDecodeOptions :: JSVal } instance Eq (TextDecodeOptions) where (TextDecodeOptions a) == (TextDecodeOptions b) = js_eq a b instance PToJSVal TextDecodeOptions where pToJSVal = unTextDecodeOptions {-# INLINE pToJSVal #-} instance PFromJSVal TextDecodeOptions where pFromJSVal = TextDecodeOptions {-# INLINE pFromJSVal #-} instance ToJSVal TextDecodeOptions where toJSVal = return . unTextDecodeOptions {-# INLINE toJSVal #-} instance FromJSVal TextDecodeOptions where fromJSVal = return . fmap TextDecodeOptions . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject TextDecodeOptions where typeGType _ = gTypeTextDecodeOptions {-# INLINE typeGType #-} noTextDecodeOptions :: Maybe TextDecodeOptions noTextDecodeOptions = Nothing {-# INLINE noTextDecodeOptions #-} foreign import javascript unsafe "window[\"TextDecodeOptions\"]" gTypeTextDecodeOptions :: GType -- | Functions for this inteface are in "GHCJS.DOM.TextDecoder". -- -- newtype TextDecoder = TextDecoder { unTextDecoder :: JSVal } instance Eq (TextDecoder) where (TextDecoder a) == (TextDecoder b) = js_eq a b instance PToJSVal TextDecoder where pToJSVal = unTextDecoder {-# INLINE pToJSVal #-} instance PFromJSVal TextDecoder where pFromJSVal = TextDecoder {-# INLINE pFromJSVal #-} instance ToJSVal TextDecoder where toJSVal = return . unTextDecoder {-# INLINE toJSVal #-} instance FromJSVal TextDecoder where fromJSVal = return . fmap TextDecoder . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject TextDecoder where typeGType _ = gTypeTextDecoder {-# INLINE typeGType #-} noTextDecoder :: Maybe TextDecoder noTextDecoder = Nothing {-# INLINE noTextDecoder #-} foreign import javascript unsafe "window[\"TextDecoder\"]" gTypeTextDecoder :: GType -- | Functions for this inteface are in "GHCJS.DOM.TextDecoderOptions". -- -- newtype TextDecoderOptions = TextDecoderOptions { unTextDecoderOptions :: JSVal } instance Eq (TextDecoderOptions) where (TextDecoderOptions a) == (TextDecoderOptions b) = js_eq a b instance PToJSVal TextDecoderOptions where pToJSVal = unTextDecoderOptions {-# INLINE pToJSVal #-} instance PFromJSVal TextDecoderOptions where pFromJSVal = TextDecoderOptions {-# INLINE pFromJSVal #-} instance ToJSVal TextDecoderOptions where toJSVal = return . unTextDecoderOptions {-# INLINE toJSVal #-} instance FromJSVal TextDecoderOptions where fromJSVal = return . fmap TextDecoderOptions . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject TextDecoderOptions where typeGType _ = gTypeTextDecoderOptions {-# INLINE typeGType #-} noTextDecoderOptions :: Maybe TextDecoderOptions noTextDecoderOptions = Nothing {-# INLINE noTextDecoderOptions #-} foreign import javascript unsafe "window[\"TextDecoderOptions\"]" gTypeTextDecoderOptions :: GType -- | Functions for this inteface are in "GHCJS.DOM.TextEncoder". -- -- newtype TextEncoder = TextEncoder { unTextEncoder :: JSVal } instance Eq (TextEncoder) where (TextEncoder a) == (TextEncoder b) = js_eq a b instance PToJSVal TextEncoder where pToJSVal = unTextEncoder {-# INLINE pToJSVal #-} instance PFromJSVal TextEncoder where pFromJSVal = TextEncoder {-# INLINE pFromJSVal #-} instance ToJSVal TextEncoder where toJSVal = return . unTextEncoder {-# INLINE toJSVal #-} instance FromJSVal TextEncoder where fromJSVal = return . fmap TextEncoder . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject TextEncoder where typeGType _ = gTypeTextEncoder {-# INLINE typeGType #-} noTextEncoder :: Maybe TextEncoder noTextEncoder = Nothing {-# INLINE noTextEncoder #-} foreign import javascript unsafe "window[\"TextEncoder\"]" gTypeTextEncoder :: GType -- | Functions for this inteface are in "GHCJS.DOM.TextEvent". -- Base interface functions are in: -- -- * "GHCJS.DOM.UIEvent" -- * "GHCJS.DOM.Event" -- -- newtype TextEvent = TextEvent { unTextEvent :: JSVal } instance Eq (TextEvent) where (TextEvent a) == (TextEvent b) = js_eq a b instance PToJSVal TextEvent where pToJSVal = unTextEvent {-# INLINE pToJSVal #-} instance PFromJSVal TextEvent where pFromJSVal = TextEvent {-# INLINE pFromJSVal #-} instance ToJSVal TextEvent where toJSVal = return . unTextEvent {-# INLINE toJSVal #-} instance FromJSVal TextEvent where fromJSVal = return . fmap TextEvent . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsUIEvent TextEvent instance IsEvent TextEvent instance IsGObject TextEvent where typeGType _ = gTypeTextEvent {-# INLINE typeGType #-} noTextEvent :: Maybe TextEvent noTextEvent = Nothing {-# INLINE noTextEvent #-} foreign import javascript unsafe "window[\"TextEvent\"]" gTypeTextEvent :: GType -- | Functions for this inteface are in "GHCJS.DOM.TextMetrics". -- -- newtype TextMetrics = TextMetrics { unTextMetrics :: JSVal } instance Eq (TextMetrics) where (TextMetrics a) == (TextMetrics b) = js_eq a b instance PToJSVal TextMetrics where pToJSVal = unTextMetrics {-# INLINE pToJSVal #-} instance PFromJSVal TextMetrics where pFromJSVal = TextMetrics {-# INLINE pFromJSVal #-} instance ToJSVal TextMetrics where toJSVal = return . unTextMetrics {-# INLINE toJSVal #-} instance FromJSVal TextMetrics where fromJSVal = return . fmap TextMetrics . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject TextMetrics where typeGType _ = gTypeTextMetrics {-# INLINE typeGType #-} noTextMetrics :: Maybe TextMetrics noTextMetrics = Nothing {-# INLINE noTextMetrics #-} foreign import javascript unsafe "window[\"TextMetrics\"]" gTypeTextMetrics :: GType -- | Functions for this inteface are in "GHCJS.DOM.TextTrack". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventTarget" -- -- newtype TextTrack = TextTrack { unTextTrack :: JSVal } instance Eq (TextTrack) where (TextTrack a) == (TextTrack b) = js_eq a b instance PToJSVal TextTrack where pToJSVal = unTextTrack {-# INLINE pToJSVal #-} instance PFromJSVal TextTrack where pFromJSVal = TextTrack {-# INLINE pFromJSVal #-} instance ToJSVal TextTrack where toJSVal = return . unTextTrack {-# INLINE toJSVal #-} instance FromJSVal TextTrack where fromJSVal = return . fmap TextTrack . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventTarget TextTrack instance IsGObject TextTrack where typeGType _ = gTypeTextTrack {-# INLINE typeGType #-} noTextTrack :: Maybe TextTrack noTextTrack = Nothing {-# INLINE noTextTrack #-} foreign import javascript unsafe "window[\"TextTrack\"]" gTypeTextTrack :: GType -- | Functions for this inteface are in "GHCJS.DOM.TextTrackCue". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventTarget" -- -- newtype TextTrackCue = TextTrackCue { unTextTrackCue :: JSVal } instance Eq (TextTrackCue) where (TextTrackCue a) == (TextTrackCue b) = js_eq a b instance PToJSVal TextTrackCue where pToJSVal = unTextTrackCue {-# INLINE pToJSVal #-} instance PFromJSVal TextTrackCue where pFromJSVal = TextTrackCue {-# INLINE pFromJSVal #-} instance ToJSVal TextTrackCue where toJSVal = return . unTextTrackCue {-# INLINE toJSVal #-} instance FromJSVal TextTrackCue where fromJSVal = return . fmap TextTrackCue . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsEventTarget o, IsGObject o) => IsTextTrackCue o toTextTrackCue :: IsTextTrackCue o => o -> TextTrackCue toTextTrackCue = TextTrackCue . coerce instance IsTextTrackCue TextTrackCue instance IsEventTarget TextTrackCue instance IsGObject TextTrackCue where typeGType _ = gTypeTextTrackCue {-# INLINE typeGType #-} noTextTrackCue :: Maybe TextTrackCue noTextTrackCue = Nothing {-# INLINE noTextTrackCue #-} foreign import javascript unsafe "window[\"TextTrackCue\"]" gTypeTextTrackCue :: GType -- | Functions for this inteface are in "GHCJS.DOM.TextTrackCueList". -- -- newtype TextTrackCueList = TextTrackCueList { unTextTrackCueList :: JSVal } instance Eq (TextTrackCueList) where (TextTrackCueList a) == (TextTrackCueList b) = js_eq a b instance PToJSVal TextTrackCueList where pToJSVal = unTextTrackCueList {-# INLINE pToJSVal #-} instance PFromJSVal TextTrackCueList where pFromJSVal = TextTrackCueList {-# INLINE pFromJSVal #-} instance ToJSVal TextTrackCueList where toJSVal = return . unTextTrackCueList {-# INLINE toJSVal #-} instance FromJSVal TextTrackCueList where fromJSVal = return . fmap TextTrackCueList . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject TextTrackCueList where typeGType _ = gTypeTextTrackCueList {-# INLINE typeGType #-} noTextTrackCueList :: Maybe TextTrackCueList noTextTrackCueList = Nothing {-# INLINE noTextTrackCueList #-} foreign import javascript unsafe "window[\"TextTrackCueList\"]" gTypeTextTrackCueList :: GType -- | Functions for this inteface are in "GHCJS.DOM.TextTrackList". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventTarget" -- -- newtype TextTrackList = TextTrackList { unTextTrackList :: JSVal } instance Eq (TextTrackList) where (TextTrackList a) == (TextTrackList b) = js_eq a b instance PToJSVal TextTrackList where pToJSVal = unTextTrackList {-# INLINE pToJSVal #-} instance PFromJSVal TextTrackList where pFromJSVal = TextTrackList {-# INLINE pFromJSVal #-} instance ToJSVal TextTrackList where toJSVal = return . unTextTrackList {-# INLINE toJSVal #-} instance FromJSVal TextTrackList where fromJSVal = return . fmap TextTrackList . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventTarget TextTrackList instance IsGObject TextTrackList where typeGType _ = gTypeTextTrackList {-# INLINE typeGType #-} noTextTrackList :: Maybe TextTrackList noTextTrackList = Nothing {-# INLINE noTextTrackList #-} foreign import javascript unsafe "window[\"TextTrackList\"]" gTypeTextTrackList :: GType -- | Functions for this inteface are in "GHCJS.DOM.TimeRanges". -- -- newtype TimeRanges = TimeRanges { unTimeRanges :: JSVal } instance Eq (TimeRanges) where (TimeRanges a) == (TimeRanges b) = js_eq a b instance PToJSVal TimeRanges where pToJSVal = unTimeRanges {-# INLINE pToJSVal #-} instance PFromJSVal TimeRanges where pFromJSVal = TimeRanges {-# INLINE pFromJSVal #-} instance ToJSVal TimeRanges where toJSVal = return . unTimeRanges {-# INLINE toJSVal #-} instance FromJSVal TimeRanges where fromJSVal = return . fmap TimeRanges . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject TimeRanges where typeGType _ = gTypeTimeRanges {-# INLINE typeGType #-} noTimeRanges :: Maybe TimeRanges noTimeRanges = Nothing {-# INLINE noTimeRanges #-} foreign import javascript unsafe "window[\"TimeRanges\"]" gTypeTimeRanges :: GType -- | Functions for this inteface are in "GHCJS.DOM.Touch". -- -- newtype Touch = Touch { unTouch :: JSVal } instance Eq (Touch) where (Touch a) == (Touch b) = js_eq a b instance PToJSVal Touch where pToJSVal = unTouch {-# INLINE pToJSVal #-} instance PFromJSVal Touch where pFromJSVal = Touch {-# INLINE pFromJSVal #-} instance ToJSVal Touch where toJSVal = return . unTouch {-# INLINE toJSVal #-} instance FromJSVal Touch where fromJSVal = return . fmap Touch . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject Touch where typeGType _ = gTypeTouch {-# INLINE typeGType #-} noTouch :: Maybe Touch noTouch = Nothing {-# INLINE noTouch #-} foreign import javascript unsafe "window[\"Touch\"]" gTypeTouch :: GType -- | Functions for this inteface are in "GHCJS.DOM.TouchEvent". -- Base interface functions are in: -- -- * "GHCJS.DOM.UIEvent" -- * "GHCJS.DOM.Event" -- -- newtype TouchEvent = TouchEvent { unTouchEvent :: JSVal } instance Eq (TouchEvent) where (TouchEvent a) == (TouchEvent b) = js_eq a b instance PToJSVal TouchEvent where pToJSVal = unTouchEvent {-# INLINE pToJSVal #-} instance PFromJSVal TouchEvent where pFromJSVal = TouchEvent {-# INLINE pFromJSVal #-} instance ToJSVal TouchEvent where toJSVal = return . unTouchEvent {-# INLINE toJSVal #-} instance FromJSVal TouchEvent where fromJSVal = return . fmap TouchEvent . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsUIEvent TouchEvent instance IsEvent TouchEvent instance IsGObject TouchEvent where typeGType _ = gTypeTouchEvent {-# INLINE typeGType #-} noTouchEvent :: Maybe TouchEvent noTouchEvent = Nothing {-# INLINE noTouchEvent #-} foreign import javascript unsafe "window[\"TouchEvent\"]" gTypeTouchEvent :: GType -- | Functions for this inteface are in "GHCJS.DOM.TouchEventInit". -- Base interface functions are in: -- -- * "GHCJS.DOM.UIEventInit" -- * "GHCJS.DOM.EventInit" -- -- newtype TouchEventInit = TouchEventInit { unTouchEventInit :: JSVal } instance Eq (TouchEventInit) where (TouchEventInit a) == (TouchEventInit b) = js_eq a b instance PToJSVal TouchEventInit where pToJSVal = unTouchEventInit {-# INLINE pToJSVal #-} instance PFromJSVal TouchEventInit where pFromJSVal = TouchEventInit {-# INLINE pFromJSVal #-} instance ToJSVal TouchEventInit where toJSVal = return . unTouchEventInit {-# INLINE toJSVal #-} instance FromJSVal TouchEventInit where fromJSVal = return . fmap TouchEventInit . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsUIEventInit TouchEventInit instance IsEventInit TouchEventInit instance IsGObject TouchEventInit where typeGType _ = gTypeTouchEventInit {-# INLINE typeGType #-} noTouchEventInit :: Maybe TouchEventInit noTouchEventInit = Nothing {-# INLINE noTouchEventInit #-} foreign import javascript unsafe "window[\"TouchEventInit\"]" gTypeTouchEventInit :: GType -- | Functions for this inteface are in "GHCJS.DOM.TouchList". -- -- newtype TouchList = TouchList { unTouchList :: JSVal } instance Eq (TouchList) where (TouchList a) == (TouchList b) = js_eq a b instance PToJSVal TouchList where pToJSVal = unTouchList {-# INLINE pToJSVal #-} instance PFromJSVal TouchList where pFromJSVal = TouchList {-# INLINE pFromJSVal #-} instance ToJSVal TouchList where toJSVal = return . unTouchList {-# INLINE toJSVal #-} instance FromJSVal TouchList where fromJSVal = return . fmap TouchList . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject TouchList where typeGType _ = gTypeTouchList {-# INLINE typeGType #-} noTouchList :: Maybe TouchList noTouchList = Nothing {-# INLINE noTouchList #-} foreign import javascript unsafe "window[\"TouchList\"]" gTypeTouchList :: GType -- | Functions for this inteface are in "GHCJS.DOM.TrackEvent". -- Base interface functions are in: -- -- * "GHCJS.DOM.Event" -- -- newtype TrackEvent = TrackEvent { unTrackEvent :: JSVal } instance Eq (TrackEvent) where (TrackEvent a) == (TrackEvent b) = js_eq a b instance PToJSVal TrackEvent where pToJSVal = unTrackEvent {-# INLINE pToJSVal #-} instance PFromJSVal TrackEvent where pFromJSVal = TrackEvent {-# INLINE pFromJSVal #-} instance ToJSVal TrackEvent where toJSVal = return . unTrackEvent {-# INLINE toJSVal #-} instance FromJSVal TrackEvent where fromJSVal = return . fmap TrackEvent . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEvent TrackEvent instance IsGObject TrackEvent where typeGType _ = gTypeTrackEvent {-# INLINE typeGType #-} noTrackEvent :: Maybe TrackEvent noTrackEvent = Nothing {-# INLINE noTrackEvent #-} foreign import javascript unsafe "window[\"TrackEvent\"]" gTypeTrackEvent :: GType -- | Functions for this inteface are in "GHCJS.DOM.TrackEventInit". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventInit" -- -- newtype TrackEventInit = TrackEventInit { unTrackEventInit :: JSVal } instance Eq (TrackEventInit) where (TrackEventInit a) == (TrackEventInit b) = js_eq a b instance PToJSVal TrackEventInit where pToJSVal = unTrackEventInit {-# INLINE pToJSVal #-} instance PFromJSVal TrackEventInit where pFromJSVal = TrackEventInit {-# INLINE pFromJSVal #-} instance ToJSVal TrackEventInit where toJSVal = return . unTrackEventInit {-# INLINE toJSVal #-} instance FromJSVal TrackEventInit where fromJSVal = return . fmap TrackEventInit . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventInit TrackEventInit instance IsGObject TrackEventInit where typeGType _ = gTypeTrackEventInit {-# INLINE typeGType #-} noTrackEventInit :: Maybe TrackEventInit noTrackEventInit = Nothing {-# INLINE noTrackEventInit #-} foreign import javascript unsafe "window[\"TrackEventInit\"]" gTypeTrackEventInit :: GType -- | Functions for this inteface are in "GHCJS.DOM.TransitionEvent". -- Base interface functions are in: -- -- * "GHCJS.DOM.Event" -- -- newtype TransitionEvent = TransitionEvent { unTransitionEvent :: JSVal } instance Eq (TransitionEvent) where (TransitionEvent a) == (TransitionEvent b) = js_eq a b instance PToJSVal TransitionEvent where pToJSVal = unTransitionEvent {-# INLINE pToJSVal #-} instance PFromJSVal TransitionEvent where pFromJSVal = TransitionEvent {-# INLINE pFromJSVal #-} instance ToJSVal TransitionEvent where toJSVal = return . unTransitionEvent {-# INLINE toJSVal #-} instance FromJSVal TransitionEvent where fromJSVal = return . fmap TransitionEvent . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEvent TransitionEvent instance IsGObject TransitionEvent where typeGType _ = gTypeTransitionEvent {-# INLINE typeGType #-} noTransitionEvent :: Maybe TransitionEvent noTransitionEvent = Nothing {-# INLINE noTransitionEvent #-} foreign import javascript unsafe "window[\"TransitionEvent\"]" gTypeTransitionEvent :: GType -- | Functions for this inteface are in "GHCJS.DOM.TransitionEventInit". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventInit" -- -- newtype TransitionEventInit = TransitionEventInit { unTransitionEventInit :: JSVal } instance Eq (TransitionEventInit) where (TransitionEventInit a) == (TransitionEventInit b) = js_eq a b instance PToJSVal TransitionEventInit where pToJSVal = unTransitionEventInit {-# INLINE pToJSVal #-} instance PFromJSVal TransitionEventInit where pFromJSVal = TransitionEventInit {-# INLINE pFromJSVal #-} instance ToJSVal TransitionEventInit where toJSVal = return . unTransitionEventInit {-# INLINE toJSVal #-} instance FromJSVal TransitionEventInit where fromJSVal = return . fmap TransitionEventInit . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventInit TransitionEventInit instance IsGObject TransitionEventInit where typeGType _ = gTypeTransitionEventInit {-# INLINE typeGType #-} noTransitionEventInit :: Maybe TransitionEventInit noTransitionEventInit = Nothing {-# INLINE noTransitionEventInit #-} foreign import javascript unsafe "window[\"TransitionEventInit\"]" gTypeTransitionEventInit :: GType -- | Functions for this inteface are in "GHCJS.DOM.TreeWalker". -- -- newtype TreeWalker = TreeWalker { unTreeWalker :: JSVal } instance Eq (TreeWalker) where (TreeWalker a) == (TreeWalker b) = js_eq a b instance PToJSVal TreeWalker where pToJSVal = unTreeWalker {-# INLINE pToJSVal #-} instance PFromJSVal TreeWalker where pFromJSVal = TreeWalker {-# INLINE pFromJSVal #-} instance ToJSVal TreeWalker where toJSVal = return . unTreeWalker {-# INLINE toJSVal #-} instance FromJSVal TreeWalker where fromJSVal = return . fmap TreeWalker . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject TreeWalker where typeGType _ = gTypeTreeWalker {-# INLINE typeGType #-} noTreeWalker :: Maybe TreeWalker noTreeWalker = Nothing {-# INLINE noTreeWalker #-} foreign import javascript unsafe "window[\"TreeWalker\"]" gTypeTreeWalker :: GType -- | Functions for this inteface are in "GHCJS.DOM.UIEvent". -- Base interface functions are in: -- -- * "GHCJS.DOM.Event" -- -- newtype UIEvent = UIEvent { unUIEvent :: JSVal } instance Eq (UIEvent) where (UIEvent a) == (UIEvent b) = js_eq a b instance PToJSVal UIEvent where pToJSVal = unUIEvent {-# INLINE pToJSVal #-} instance PFromJSVal UIEvent where pFromJSVal = UIEvent {-# INLINE pFromJSVal #-} instance ToJSVal UIEvent where toJSVal = return . unUIEvent {-# INLINE toJSVal #-} instance FromJSVal UIEvent where fromJSVal = return . fmap UIEvent . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsEvent o, IsGObject o) => IsUIEvent o toUIEvent :: IsUIEvent o => o -> UIEvent toUIEvent = UIEvent . coerce instance IsUIEvent UIEvent instance IsEvent UIEvent instance IsGObject UIEvent where typeGType _ = gTypeUIEvent {-# INLINE typeGType #-} noUIEvent :: Maybe UIEvent noUIEvent = Nothing {-# INLINE noUIEvent #-} foreign import javascript unsafe "window[\"UIEvent\"]" gTypeUIEvent :: GType -- | Functions for this inteface are in "GHCJS.DOM.UIEventInit". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventInit" -- -- newtype UIEventInit = UIEventInit { unUIEventInit :: JSVal } instance Eq (UIEventInit) where (UIEventInit a) == (UIEventInit b) = js_eq a b instance PToJSVal UIEventInit where pToJSVal = unUIEventInit {-# INLINE pToJSVal #-} instance PFromJSVal UIEventInit where pFromJSVal = UIEventInit {-# INLINE pFromJSVal #-} instance ToJSVal UIEventInit where toJSVal = return . unUIEventInit {-# INLINE toJSVal #-} instance FromJSVal UIEventInit where fromJSVal = return . fmap UIEventInit . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsEventInit o, IsGObject o) => IsUIEventInit o toUIEventInit :: IsUIEventInit o => o -> UIEventInit toUIEventInit = UIEventInit . coerce instance IsUIEventInit UIEventInit instance IsEventInit UIEventInit instance IsGObject UIEventInit where typeGType _ = gTypeUIEventInit {-# INLINE typeGType #-} noUIEventInit :: Maybe UIEventInit noUIEventInit = Nothing {-# INLINE noUIEventInit #-} foreign import javascript unsafe "window[\"UIEventInit\"]" gTypeUIEventInit :: GType -- | Functions for this inteface are in "GHCJS.DOM.URL". -- -- newtype URL = URL { unURL :: JSVal } instance Eq (URL) where (URL a) == (URL b) = js_eq a b instance PToJSVal URL where pToJSVal = unURL {-# INLINE pToJSVal #-} instance PFromJSVal URL where pFromJSVal = URL {-# INLINE pFromJSVal #-} instance ToJSVal URL where toJSVal = return . unURL {-# INLINE toJSVal #-} instance FromJSVal URL where fromJSVal = return . fmap URL . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject URL where typeGType _ = gTypeURL {-# INLINE typeGType #-} noURL :: Maybe URL noURL = Nothing {-# INLINE noURL #-} foreign import javascript unsafe "window[\"URL\"]" gTypeURL :: GType -- | Functions for this inteface are in "GHCJS.DOM.URLSearchParams". -- -- newtype URLSearchParams = URLSearchParams { unURLSearchParams :: JSVal } instance Eq (URLSearchParams) where (URLSearchParams a) == (URLSearchParams b) = js_eq a b instance PToJSVal URLSearchParams where pToJSVal = unURLSearchParams {-# INLINE pToJSVal #-} instance PFromJSVal URLSearchParams where pFromJSVal = URLSearchParams {-# INLINE pFromJSVal #-} instance ToJSVal URLSearchParams where toJSVal = return . unURLSearchParams {-# INLINE toJSVal #-} instance FromJSVal URLSearchParams where fromJSVal = return . fmap URLSearchParams . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject URLSearchParams where typeGType _ = gTypeURLSearchParams {-# INLINE typeGType #-} noURLSearchParams :: Maybe URLSearchParams noURLSearchParams = Nothing {-# INLINE noURLSearchParams #-} foreign import javascript unsafe "window[\"URLSearchParams\"]" gTypeURLSearchParams :: GType -- | Functions for this inteface are in "GHCJS.DOM.UserMessageHandler". -- -- newtype UserMessageHandler = UserMessageHandler { unUserMessageHandler :: JSVal } instance Eq (UserMessageHandler) where (UserMessageHandler a) == (UserMessageHandler b) = js_eq a b instance PToJSVal UserMessageHandler where pToJSVal = unUserMessageHandler {-# INLINE pToJSVal #-} instance PFromJSVal UserMessageHandler where pFromJSVal = UserMessageHandler {-# INLINE pFromJSVal #-} instance ToJSVal UserMessageHandler where toJSVal = return . unUserMessageHandler {-# INLINE toJSVal #-} instance FromJSVal UserMessageHandler where fromJSVal = return . fmap UserMessageHandler . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject UserMessageHandler where typeGType _ = gTypeUserMessageHandler {-# INLINE typeGType #-} noUserMessageHandler :: Maybe UserMessageHandler noUserMessageHandler = Nothing {-# INLINE noUserMessageHandler #-} foreign import javascript unsafe "window[\"UserMessageHandler\"]" gTypeUserMessageHandler :: GType -- | Functions for this inteface are in "GHCJS.DOM.UserMessageHandlersNamespace". -- -- newtype UserMessageHandlersNamespace = UserMessageHandlersNamespace { unUserMessageHandlersNamespace :: JSVal } instance Eq (UserMessageHandlersNamespace) where (UserMessageHandlersNamespace a) == (UserMessageHandlersNamespace b) = js_eq a b instance PToJSVal UserMessageHandlersNamespace where pToJSVal = unUserMessageHandlersNamespace {-# INLINE pToJSVal #-} instance PFromJSVal UserMessageHandlersNamespace where pFromJSVal = UserMessageHandlersNamespace {-# INLINE pFromJSVal #-} instance ToJSVal UserMessageHandlersNamespace where toJSVal = return . unUserMessageHandlersNamespace {-# INLINE toJSVal #-} instance FromJSVal UserMessageHandlersNamespace where fromJSVal = return . fmap UserMessageHandlersNamespace . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject UserMessageHandlersNamespace where typeGType _ = gTypeUserMessageHandlersNamespace {-# INLINE typeGType #-} noUserMessageHandlersNamespace :: Maybe UserMessageHandlersNamespace noUserMessageHandlersNamespace = Nothing {-# INLINE noUserMessageHandlersNamespace #-} foreign import javascript unsafe "window[\"UserMessageHandlersNamespace\"]" gTypeUserMessageHandlersNamespace :: GType -- | Functions for this inteface are in "GHCJS.DOM.VTTCue". -- Base interface functions are in: -- -- * "GHCJS.DOM.TextTrackCue" -- * "GHCJS.DOM.EventTarget" -- -- newtype VTTCue = VTTCue { unVTTCue :: JSVal } instance Eq (VTTCue) where (VTTCue a) == (VTTCue b) = js_eq a b instance PToJSVal VTTCue where pToJSVal = unVTTCue {-# INLINE pToJSVal #-} instance PFromJSVal VTTCue where pFromJSVal = VTTCue {-# INLINE pFromJSVal #-} instance ToJSVal VTTCue where toJSVal = return . unVTTCue {-# INLINE toJSVal #-} instance FromJSVal VTTCue where fromJSVal = return . fmap VTTCue . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsTextTrackCue VTTCue instance IsEventTarget VTTCue instance IsGObject VTTCue where typeGType _ = gTypeVTTCue {-# INLINE typeGType #-} noVTTCue :: Maybe VTTCue noVTTCue = Nothing {-# INLINE noVTTCue #-} foreign import javascript unsafe "window[\"VTTCue\"]" gTypeVTTCue :: GType -- | Functions for this inteface are in "GHCJS.DOM.VTTRegion". -- -- newtype VTTRegion = VTTRegion { unVTTRegion :: JSVal } instance Eq (VTTRegion) where (VTTRegion a) == (VTTRegion b) = js_eq a b instance PToJSVal VTTRegion where pToJSVal = unVTTRegion {-# INLINE pToJSVal #-} instance PFromJSVal VTTRegion where pFromJSVal = VTTRegion {-# INLINE pFromJSVal #-} instance ToJSVal VTTRegion where toJSVal = return . unVTTRegion {-# INLINE toJSVal #-} instance FromJSVal VTTRegion where fromJSVal = return . fmap VTTRegion . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject VTTRegion where typeGType _ = gTypeVTTRegion {-# INLINE typeGType #-} noVTTRegion :: Maybe VTTRegion noVTTRegion = Nothing {-# INLINE noVTTRegion #-} foreign import javascript unsafe "window[\"VTTRegion\"]" gTypeVTTRegion :: GType -- | Functions for this inteface are in "GHCJS.DOM.VTTRegionList". -- -- newtype VTTRegionList = VTTRegionList { unVTTRegionList :: JSVal } instance Eq (VTTRegionList) where (VTTRegionList a) == (VTTRegionList b) = js_eq a b instance PToJSVal VTTRegionList where pToJSVal = unVTTRegionList {-# INLINE pToJSVal #-} instance PFromJSVal VTTRegionList where pFromJSVal = VTTRegionList {-# INLINE pFromJSVal #-} instance ToJSVal VTTRegionList where toJSVal = return . unVTTRegionList {-# INLINE toJSVal #-} instance FromJSVal VTTRegionList where fromJSVal = return . fmap VTTRegionList . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject VTTRegionList where typeGType _ = gTypeVTTRegionList {-# INLINE typeGType #-} noVTTRegionList :: Maybe VTTRegionList noVTTRegionList = Nothing {-# INLINE noVTTRegionList #-} foreign import javascript unsafe "window[\"VTTRegionList\"]" gTypeVTTRegionList :: GType -- | Functions for this inteface are in "GHCJS.DOM.ValidityState". -- -- newtype ValidityState = ValidityState { unValidityState :: JSVal } instance Eq (ValidityState) where (ValidityState a) == (ValidityState b) = js_eq a b instance PToJSVal ValidityState where pToJSVal = unValidityState {-# INLINE pToJSVal #-} instance PFromJSVal ValidityState where pFromJSVal = ValidityState {-# INLINE pFromJSVal #-} instance ToJSVal ValidityState where toJSVal = return . unValidityState {-# INLINE toJSVal #-} instance FromJSVal ValidityState where fromJSVal = return . fmap ValidityState . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject ValidityState where typeGType _ = gTypeValidityState {-# INLINE typeGType #-} noValidityState :: Maybe ValidityState noValidityState = Nothing {-# INLINE noValidityState #-} foreign import javascript unsafe "window[\"ValidityState\"]" gTypeValidityState :: GType -- | Functions for this inteface are in "GHCJS.DOM.VideoPlaybackQuality". -- -- newtype VideoPlaybackQuality = VideoPlaybackQuality { unVideoPlaybackQuality :: JSVal } instance Eq (VideoPlaybackQuality) where (VideoPlaybackQuality a) == (VideoPlaybackQuality b) = js_eq a b instance PToJSVal VideoPlaybackQuality where pToJSVal = unVideoPlaybackQuality {-# INLINE pToJSVal #-} instance PFromJSVal VideoPlaybackQuality where pFromJSVal = VideoPlaybackQuality {-# INLINE pFromJSVal #-} instance ToJSVal VideoPlaybackQuality where toJSVal = return . unVideoPlaybackQuality {-# INLINE toJSVal #-} instance FromJSVal VideoPlaybackQuality where fromJSVal = return . fmap VideoPlaybackQuality . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject VideoPlaybackQuality where typeGType _ = gTypeVideoPlaybackQuality {-# INLINE typeGType #-} noVideoPlaybackQuality :: Maybe VideoPlaybackQuality noVideoPlaybackQuality = Nothing {-# INLINE noVideoPlaybackQuality #-} foreign import javascript unsafe "window[\"VideoPlaybackQuality\"]" gTypeVideoPlaybackQuality :: GType -- | Functions for this inteface are in "GHCJS.DOM.VideoTrack". -- -- newtype VideoTrack = VideoTrack { unVideoTrack :: JSVal } instance Eq (VideoTrack) where (VideoTrack a) == (VideoTrack b) = js_eq a b instance PToJSVal VideoTrack where pToJSVal = unVideoTrack {-# INLINE pToJSVal #-} instance PFromJSVal VideoTrack where pFromJSVal = VideoTrack {-# INLINE pFromJSVal #-} instance ToJSVal VideoTrack where toJSVal = return . unVideoTrack {-# INLINE toJSVal #-} instance FromJSVal VideoTrack where fromJSVal = return . fmap VideoTrack . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject VideoTrack where typeGType _ = gTypeVideoTrack {-# INLINE typeGType #-} noVideoTrack :: Maybe VideoTrack noVideoTrack = Nothing {-# INLINE noVideoTrack #-} foreign import javascript unsafe "window[\"VideoTrack\"]" gTypeVideoTrack :: GType -- | Functions for this inteface are in "GHCJS.DOM.VideoTrackList". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventTarget" -- -- newtype VideoTrackList = VideoTrackList { unVideoTrackList :: JSVal } instance Eq (VideoTrackList) where (VideoTrackList a) == (VideoTrackList b) = js_eq a b instance PToJSVal VideoTrackList where pToJSVal = unVideoTrackList {-# INLINE pToJSVal #-} instance PFromJSVal VideoTrackList where pFromJSVal = VideoTrackList {-# INLINE pFromJSVal #-} instance ToJSVal VideoTrackList where toJSVal = return . unVideoTrackList {-# INLINE toJSVal #-} instance FromJSVal VideoTrackList where fromJSVal = return . fmap VideoTrackList . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventTarget VideoTrackList instance IsGObject VideoTrackList where typeGType _ = gTypeVideoTrackList {-# INLINE typeGType #-} noVideoTrackList :: Maybe VideoTrackList noVideoTrackList = Nothing {-# INLINE noVideoTrackList #-} foreign import javascript unsafe "window[\"VideoTrackList\"]" gTypeVideoTrackList :: GType -- | Functions for this inteface are in "GHCJS.DOM.WaveShaperNode". -- Base interface functions are in: -- -- * "GHCJS.DOM.AudioNode" -- * "GHCJS.DOM.EventTarget" -- -- newtype WaveShaperNode = WaveShaperNode { unWaveShaperNode :: JSVal } instance Eq (WaveShaperNode) where (WaveShaperNode a) == (WaveShaperNode b) = js_eq a b instance PToJSVal WaveShaperNode where pToJSVal = unWaveShaperNode {-# INLINE pToJSVal #-} instance PFromJSVal WaveShaperNode where pFromJSVal = WaveShaperNode {-# INLINE pFromJSVal #-} instance ToJSVal WaveShaperNode where toJSVal = return . unWaveShaperNode {-# INLINE toJSVal #-} instance FromJSVal WaveShaperNode where fromJSVal = return . fmap WaveShaperNode . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsAudioNode WaveShaperNode instance IsEventTarget WaveShaperNode instance IsGObject WaveShaperNode where typeGType _ = gTypeWaveShaperNode {-# INLINE typeGType #-} noWaveShaperNode :: Maybe WaveShaperNode noWaveShaperNode = Nothing {-# INLINE noWaveShaperNode #-} foreign import javascript unsafe "window[\"WaveShaperNode\"]" gTypeWaveShaperNode :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebGL2RenderingContext". -- Base interface functions are in: -- -- * "GHCJS.DOM.WebGLRenderingContextBase" -- -- newtype WebGL2RenderingContext = WebGL2RenderingContext { unWebGL2RenderingContext :: JSVal } instance Eq (WebGL2RenderingContext) where (WebGL2RenderingContext a) == (WebGL2RenderingContext b) = js_eq a b instance PToJSVal WebGL2RenderingContext where pToJSVal = unWebGL2RenderingContext {-# INLINE pToJSVal #-} instance PFromJSVal WebGL2RenderingContext where pFromJSVal = WebGL2RenderingContext {-# INLINE pFromJSVal #-} instance ToJSVal WebGL2RenderingContext where toJSVal = return . unWebGL2RenderingContext {-# INLINE toJSVal #-} instance FromJSVal WebGL2RenderingContext where fromJSVal = return . fmap WebGL2RenderingContext . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsWebGLRenderingContextBase WebGL2RenderingContext instance IsGObject WebGL2RenderingContext where typeGType _ = gTypeWebGL2RenderingContext {-# INLINE typeGType #-} noWebGL2RenderingContext :: Maybe WebGL2RenderingContext noWebGL2RenderingContext = Nothing {-# INLINE noWebGL2RenderingContext #-} foreign import javascript unsafe "window[\"WebGL2RenderingContext\"]" gTypeWebGL2RenderingContext :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebGLActiveInfo". -- -- newtype WebGLActiveInfo = WebGLActiveInfo { unWebGLActiveInfo :: JSVal } instance Eq (WebGLActiveInfo) where (WebGLActiveInfo a) == (WebGLActiveInfo b) = js_eq a b instance PToJSVal WebGLActiveInfo where pToJSVal = unWebGLActiveInfo {-# INLINE pToJSVal #-} instance PFromJSVal WebGLActiveInfo where pFromJSVal = WebGLActiveInfo {-# INLINE pFromJSVal #-} instance ToJSVal WebGLActiveInfo where toJSVal = return . unWebGLActiveInfo {-# INLINE toJSVal #-} instance FromJSVal WebGLActiveInfo where fromJSVal = return . fmap WebGLActiveInfo . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject WebGLActiveInfo where typeGType _ = gTypeWebGLActiveInfo {-# INLINE typeGType #-} noWebGLActiveInfo :: Maybe WebGLActiveInfo noWebGLActiveInfo = Nothing {-# INLINE noWebGLActiveInfo #-} foreign import javascript unsafe "window[\"WebGLActiveInfo\"]" gTypeWebGLActiveInfo :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebGLBuffer". -- -- newtype WebGLBuffer = WebGLBuffer { unWebGLBuffer :: JSVal } instance Eq (WebGLBuffer) where (WebGLBuffer a) == (WebGLBuffer b) = js_eq a b instance PToJSVal WebGLBuffer where pToJSVal = unWebGLBuffer {-# INLINE pToJSVal #-} instance PFromJSVal WebGLBuffer where pFromJSVal = WebGLBuffer {-# INLINE pFromJSVal #-} instance ToJSVal WebGLBuffer where toJSVal = return . unWebGLBuffer {-# INLINE toJSVal #-} instance FromJSVal WebGLBuffer where fromJSVal = return . fmap WebGLBuffer . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject WebGLBuffer where typeGType _ = gTypeWebGLBuffer {-# INLINE typeGType #-} noWebGLBuffer :: Maybe WebGLBuffer noWebGLBuffer = Nothing {-# INLINE noWebGLBuffer #-} foreign import javascript unsafe "window[\"WebGLBuffer\"]" gTypeWebGLBuffer :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebGLCompressedTextureATC". -- -- newtype WebGLCompressedTextureATC = WebGLCompressedTextureATC { unWebGLCompressedTextureATC :: JSVal } instance Eq (WebGLCompressedTextureATC) where (WebGLCompressedTextureATC a) == (WebGLCompressedTextureATC b) = js_eq a b instance PToJSVal WebGLCompressedTextureATC where pToJSVal = unWebGLCompressedTextureATC {-# INLINE pToJSVal #-} instance PFromJSVal WebGLCompressedTextureATC where pFromJSVal = WebGLCompressedTextureATC {-# INLINE pFromJSVal #-} instance ToJSVal WebGLCompressedTextureATC where toJSVal = return . unWebGLCompressedTextureATC {-# INLINE toJSVal #-} instance FromJSVal WebGLCompressedTextureATC where fromJSVal = return . fmap WebGLCompressedTextureATC . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject WebGLCompressedTextureATC where typeGType _ = gTypeWebGLCompressedTextureATC {-# INLINE typeGType #-} noWebGLCompressedTextureATC :: Maybe WebGLCompressedTextureATC noWebGLCompressedTextureATC = Nothing {-# INLINE noWebGLCompressedTextureATC #-} foreign import javascript unsafe "window[\"WebGLCompressedTextureATC\"]" gTypeWebGLCompressedTextureATC :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebGLCompressedTexturePVRTC". -- -- newtype WebGLCompressedTexturePVRTC = WebGLCompressedTexturePVRTC { unWebGLCompressedTexturePVRTC :: JSVal } instance Eq (WebGLCompressedTexturePVRTC) where (WebGLCompressedTexturePVRTC a) == (WebGLCompressedTexturePVRTC b) = js_eq a b instance PToJSVal WebGLCompressedTexturePVRTC where pToJSVal = unWebGLCompressedTexturePVRTC {-# INLINE pToJSVal #-} instance PFromJSVal WebGLCompressedTexturePVRTC where pFromJSVal = WebGLCompressedTexturePVRTC {-# INLINE pFromJSVal #-} instance ToJSVal WebGLCompressedTexturePVRTC where toJSVal = return . unWebGLCompressedTexturePVRTC {-# INLINE toJSVal #-} instance FromJSVal WebGLCompressedTexturePVRTC where fromJSVal = return . fmap WebGLCompressedTexturePVRTC . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject WebGLCompressedTexturePVRTC where typeGType _ = gTypeWebGLCompressedTexturePVRTC {-# INLINE typeGType #-} noWebGLCompressedTexturePVRTC :: Maybe WebGLCompressedTexturePVRTC noWebGLCompressedTexturePVRTC = Nothing {-# INLINE noWebGLCompressedTexturePVRTC #-} foreign import javascript unsafe "window[\"WebGLCompressedTexturePVRTC\"]" gTypeWebGLCompressedTexturePVRTC :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebGLCompressedTextureS3TC". -- -- newtype WebGLCompressedTextureS3TC = WebGLCompressedTextureS3TC { unWebGLCompressedTextureS3TC :: JSVal } instance Eq (WebGLCompressedTextureS3TC) where (WebGLCompressedTextureS3TC a) == (WebGLCompressedTextureS3TC b) = js_eq a b instance PToJSVal WebGLCompressedTextureS3TC where pToJSVal = unWebGLCompressedTextureS3TC {-# INLINE pToJSVal #-} instance PFromJSVal WebGLCompressedTextureS3TC where pFromJSVal = WebGLCompressedTextureS3TC {-# INLINE pFromJSVal #-} instance ToJSVal WebGLCompressedTextureS3TC where toJSVal = return . unWebGLCompressedTextureS3TC {-# INLINE toJSVal #-} instance FromJSVal WebGLCompressedTextureS3TC where fromJSVal = return . fmap WebGLCompressedTextureS3TC . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject WebGLCompressedTextureS3TC where typeGType _ = gTypeWebGLCompressedTextureS3TC {-# INLINE typeGType #-} noWebGLCompressedTextureS3TC :: Maybe WebGLCompressedTextureS3TC noWebGLCompressedTextureS3TC = Nothing {-# INLINE noWebGLCompressedTextureS3TC #-} foreign import javascript unsafe "window[\"WebGLCompressedTextureS3TC\"]" gTypeWebGLCompressedTextureS3TC :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebGLContextAttributes". -- -- newtype WebGLContextAttributes = WebGLContextAttributes { unWebGLContextAttributes :: JSVal } instance Eq (WebGLContextAttributes) where (WebGLContextAttributes a) == (WebGLContextAttributes b) = js_eq a b instance PToJSVal WebGLContextAttributes where pToJSVal = unWebGLContextAttributes {-# INLINE pToJSVal #-} instance PFromJSVal WebGLContextAttributes where pFromJSVal = WebGLContextAttributes {-# INLINE pFromJSVal #-} instance ToJSVal WebGLContextAttributes where toJSVal = return . unWebGLContextAttributes {-# INLINE toJSVal #-} instance FromJSVal WebGLContextAttributes where fromJSVal = return . fmap WebGLContextAttributes . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject WebGLContextAttributes where typeGType _ = gTypeWebGLContextAttributes {-# INLINE typeGType #-} noWebGLContextAttributes :: Maybe WebGLContextAttributes noWebGLContextAttributes = Nothing {-# INLINE noWebGLContextAttributes #-} foreign import javascript unsafe "window[\"WebGLContextAttributes\"]" gTypeWebGLContextAttributes :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebGLContextEvent". -- Base interface functions are in: -- -- * "GHCJS.DOM.Event" -- -- newtype WebGLContextEvent = WebGLContextEvent { unWebGLContextEvent :: JSVal } instance Eq (WebGLContextEvent) where (WebGLContextEvent a) == (WebGLContextEvent b) = js_eq a b instance PToJSVal WebGLContextEvent where pToJSVal = unWebGLContextEvent {-# INLINE pToJSVal #-} instance PFromJSVal WebGLContextEvent where pFromJSVal = WebGLContextEvent {-# INLINE pFromJSVal #-} instance ToJSVal WebGLContextEvent where toJSVal = return . unWebGLContextEvent {-# INLINE toJSVal #-} instance FromJSVal WebGLContextEvent where fromJSVal = return . fmap WebGLContextEvent . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEvent WebGLContextEvent instance IsGObject WebGLContextEvent where typeGType _ = gTypeWebGLContextEvent {-# INLINE typeGType #-} noWebGLContextEvent :: Maybe WebGLContextEvent noWebGLContextEvent = Nothing {-# INLINE noWebGLContextEvent #-} foreign import javascript unsafe "window[\"WebGLContextEvent\"]" gTypeWebGLContextEvent :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebGLContextEventInit". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventInit" -- -- newtype WebGLContextEventInit = WebGLContextEventInit { unWebGLContextEventInit :: JSVal } instance Eq (WebGLContextEventInit) where (WebGLContextEventInit a) == (WebGLContextEventInit b) = js_eq a b instance PToJSVal WebGLContextEventInit where pToJSVal = unWebGLContextEventInit {-# INLINE pToJSVal #-} instance PFromJSVal WebGLContextEventInit where pFromJSVal = WebGLContextEventInit {-# INLINE pFromJSVal #-} instance ToJSVal WebGLContextEventInit where toJSVal = return . unWebGLContextEventInit {-# INLINE toJSVal #-} instance FromJSVal WebGLContextEventInit where fromJSVal = return . fmap WebGLContextEventInit . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventInit WebGLContextEventInit instance IsGObject WebGLContextEventInit where typeGType _ = gTypeWebGLContextEventInit {-# INLINE typeGType #-} noWebGLContextEventInit :: Maybe WebGLContextEventInit noWebGLContextEventInit = Nothing {-# INLINE noWebGLContextEventInit #-} foreign import javascript unsafe "window[\"WebGLContextEventInit\"]" gTypeWebGLContextEventInit :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebGLDebugRendererInfo". -- -- newtype WebGLDebugRendererInfo = WebGLDebugRendererInfo { unWebGLDebugRendererInfo :: JSVal } instance Eq (WebGLDebugRendererInfo) where (WebGLDebugRendererInfo a) == (WebGLDebugRendererInfo b) = js_eq a b instance PToJSVal WebGLDebugRendererInfo where pToJSVal = unWebGLDebugRendererInfo {-# INLINE pToJSVal #-} instance PFromJSVal WebGLDebugRendererInfo where pFromJSVal = WebGLDebugRendererInfo {-# INLINE pFromJSVal #-} instance ToJSVal WebGLDebugRendererInfo where toJSVal = return . unWebGLDebugRendererInfo {-# INLINE toJSVal #-} instance FromJSVal WebGLDebugRendererInfo where fromJSVal = return . fmap WebGLDebugRendererInfo . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject WebGLDebugRendererInfo where typeGType _ = gTypeWebGLDebugRendererInfo {-# INLINE typeGType #-} noWebGLDebugRendererInfo :: Maybe WebGLDebugRendererInfo noWebGLDebugRendererInfo = Nothing {-# INLINE noWebGLDebugRendererInfo #-} foreign import javascript unsafe "window[\"WebGLDebugRendererInfo\"]" gTypeWebGLDebugRendererInfo :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebGLDebugShaders". -- -- newtype WebGLDebugShaders = WebGLDebugShaders { unWebGLDebugShaders :: JSVal } instance Eq (WebGLDebugShaders) where (WebGLDebugShaders a) == (WebGLDebugShaders b) = js_eq a b instance PToJSVal WebGLDebugShaders where pToJSVal = unWebGLDebugShaders {-# INLINE pToJSVal #-} instance PFromJSVal WebGLDebugShaders where pFromJSVal = WebGLDebugShaders {-# INLINE pFromJSVal #-} instance ToJSVal WebGLDebugShaders where toJSVal = return . unWebGLDebugShaders {-# INLINE toJSVal #-} instance FromJSVal WebGLDebugShaders where fromJSVal = return . fmap WebGLDebugShaders . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject WebGLDebugShaders where typeGType _ = gTypeWebGLDebugShaders {-# INLINE typeGType #-} noWebGLDebugShaders :: Maybe WebGLDebugShaders noWebGLDebugShaders = Nothing {-# INLINE noWebGLDebugShaders #-} foreign import javascript unsafe "window[\"WebGLDebugShaders\"]" gTypeWebGLDebugShaders :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebGLDepthTexture". -- -- newtype WebGLDepthTexture = WebGLDepthTexture { unWebGLDepthTexture :: JSVal } instance Eq (WebGLDepthTexture) where (WebGLDepthTexture a) == (WebGLDepthTexture b) = js_eq a b instance PToJSVal WebGLDepthTexture where pToJSVal = unWebGLDepthTexture {-# INLINE pToJSVal #-} instance PFromJSVal WebGLDepthTexture where pFromJSVal = WebGLDepthTexture {-# INLINE pFromJSVal #-} instance ToJSVal WebGLDepthTexture where toJSVal = return . unWebGLDepthTexture {-# INLINE toJSVal #-} instance FromJSVal WebGLDepthTexture where fromJSVal = return . fmap WebGLDepthTexture . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject WebGLDepthTexture where typeGType _ = gTypeWebGLDepthTexture {-# INLINE typeGType #-} noWebGLDepthTexture :: Maybe WebGLDepthTexture noWebGLDepthTexture = Nothing {-# INLINE noWebGLDepthTexture #-} foreign import javascript unsafe "window[\"WebGLDepthTexture\"]" gTypeWebGLDepthTexture :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebGLDrawBuffers". -- -- newtype WebGLDrawBuffers = WebGLDrawBuffers { unWebGLDrawBuffers :: JSVal } instance Eq (WebGLDrawBuffers) where (WebGLDrawBuffers a) == (WebGLDrawBuffers b) = js_eq a b instance PToJSVal WebGLDrawBuffers where pToJSVal = unWebGLDrawBuffers {-# INLINE pToJSVal #-} instance PFromJSVal WebGLDrawBuffers where pFromJSVal = WebGLDrawBuffers {-# INLINE pFromJSVal #-} instance ToJSVal WebGLDrawBuffers where toJSVal = return . unWebGLDrawBuffers {-# INLINE toJSVal #-} instance FromJSVal WebGLDrawBuffers where fromJSVal = return . fmap WebGLDrawBuffers . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject WebGLDrawBuffers where typeGType _ = gTypeWebGLDrawBuffers {-# INLINE typeGType #-} noWebGLDrawBuffers :: Maybe WebGLDrawBuffers noWebGLDrawBuffers = Nothing {-# INLINE noWebGLDrawBuffers #-} foreign import javascript unsafe "window[\"WebGLDrawBuffers\"]" gTypeWebGLDrawBuffers :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebGLFramebuffer". -- -- newtype WebGLFramebuffer = WebGLFramebuffer { unWebGLFramebuffer :: JSVal } instance Eq (WebGLFramebuffer) where (WebGLFramebuffer a) == (WebGLFramebuffer b) = js_eq a b instance PToJSVal WebGLFramebuffer where pToJSVal = unWebGLFramebuffer {-# INLINE pToJSVal #-} instance PFromJSVal WebGLFramebuffer where pFromJSVal = WebGLFramebuffer {-# INLINE pFromJSVal #-} instance ToJSVal WebGLFramebuffer where toJSVal = return . unWebGLFramebuffer {-# INLINE toJSVal #-} instance FromJSVal WebGLFramebuffer where fromJSVal = return . fmap WebGLFramebuffer . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject WebGLFramebuffer where typeGType _ = gTypeWebGLFramebuffer {-# INLINE typeGType #-} noWebGLFramebuffer :: Maybe WebGLFramebuffer noWebGLFramebuffer = Nothing {-# INLINE noWebGLFramebuffer #-} foreign import javascript unsafe "window[\"WebGLFramebuffer\"]" gTypeWebGLFramebuffer :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebGLLoseContext". -- -- newtype WebGLLoseContext = WebGLLoseContext { unWebGLLoseContext :: JSVal } instance Eq (WebGLLoseContext) where (WebGLLoseContext a) == (WebGLLoseContext b) = js_eq a b instance PToJSVal WebGLLoseContext where pToJSVal = unWebGLLoseContext {-# INLINE pToJSVal #-} instance PFromJSVal WebGLLoseContext where pFromJSVal = WebGLLoseContext {-# INLINE pFromJSVal #-} instance ToJSVal WebGLLoseContext where toJSVal = return . unWebGLLoseContext {-# INLINE toJSVal #-} instance FromJSVal WebGLLoseContext where fromJSVal = return . fmap WebGLLoseContext . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject WebGLLoseContext where typeGType _ = gTypeWebGLLoseContext {-# INLINE typeGType #-} noWebGLLoseContext :: Maybe WebGLLoseContext noWebGLLoseContext = Nothing {-# INLINE noWebGLLoseContext #-} foreign import javascript unsafe "window[\"WebGLLoseContext\"]" gTypeWebGLLoseContext :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebGLProgram". -- -- newtype WebGLProgram = WebGLProgram { unWebGLProgram :: JSVal } instance Eq (WebGLProgram) where (WebGLProgram a) == (WebGLProgram b) = js_eq a b instance PToJSVal WebGLProgram where pToJSVal = unWebGLProgram {-# INLINE pToJSVal #-} instance PFromJSVal WebGLProgram where pFromJSVal = WebGLProgram {-# INLINE pFromJSVal #-} instance ToJSVal WebGLProgram where toJSVal = return . unWebGLProgram {-# INLINE toJSVal #-} instance FromJSVal WebGLProgram where fromJSVal = return . fmap WebGLProgram . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject WebGLProgram where typeGType _ = gTypeWebGLProgram {-# INLINE typeGType #-} noWebGLProgram :: Maybe WebGLProgram noWebGLProgram = Nothing {-# INLINE noWebGLProgram #-} foreign import javascript unsafe "window[\"WebGLProgram\"]" gTypeWebGLProgram :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebGLQuery". -- -- newtype WebGLQuery = WebGLQuery { unWebGLQuery :: JSVal } instance Eq (WebGLQuery) where (WebGLQuery a) == (WebGLQuery b) = js_eq a b instance PToJSVal WebGLQuery where pToJSVal = unWebGLQuery {-# INLINE pToJSVal #-} instance PFromJSVal WebGLQuery where pFromJSVal = WebGLQuery {-# INLINE pFromJSVal #-} instance ToJSVal WebGLQuery where toJSVal = return . unWebGLQuery {-# INLINE toJSVal #-} instance FromJSVal WebGLQuery where fromJSVal = return . fmap WebGLQuery . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject WebGLQuery where typeGType _ = gTypeWebGLQuery {-# INLINE typeGType #-} noWebGLQuery :: Maybe WebGLQuery noWebGLQuery = Nothing {-# INLINE noWebGLQuery #-} foreign import javascript unsafe "window[\"WebGLQuery\"]" gTypeWebGLQuery :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebGLRenderbuffer". -- -- newtype WebGLRenderbuffer = WebGLRenderbuffer { unWebGLRenderbuffer :: JSVal } instance Eq (WebGLRenderbuffer) where (WebGLRenderbuffer a) == (WebGLRenderbuffer b) = js_eq a b instance PToJSVal WebGLRenderbuffer where pToJSVal = unWebGLRenderbuffer {-# INLINE pToJSVal #-} instance PFromJSVal WebGLRenderbuffer where pFromJSVal = WebGLRenderbuffer {-# INLINE pFromJSVal #-} instance ToJSVal WebGLRenderbuffer where toJSVal = return . unWebGLRenderbuffer {-# INLINE toJSVal #-} instance FromJSVal WebGLRenderbuffer where fromJSVal = return . fmap WebGLRenderbuffer . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject WebGLRenderbuffer where typeGType _ = gTypeWebGLRenderbuffer {-# INLINE typeGType #-} noWebGLRenderbuffer :: Maybe WebGLRenderbuffer noWebGLRenderbuffer = Nothing {-# INLINE noWebGLRenderbuffer #-} foreign import javascript unsafe "window[\"WebGLRenderbuffer\"]" gTypeWebGLRenderbuffer :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebGLRenderingContext". -- Base interface functions are in: -- -- * "GHCJS.DOM.WebGLRenderingContextBase" -- -- newtype WebGLRenderingContext = WebGLRenderingContext { unWebGLRenderingContext :: JSVal } instance Eq (WebGLRenderingContext) where (WebGLRenderingContext a) == (WebGLRenderingContext b) = js_eq a b instance PToJSVal WebGLRenderingContext where pToJSVal = unWebGLRenderingContext {-# INLINE pToJSVal #-} instance PFromJSVal WebGLRenderingContext where pFromJSVal = WebGLRenderingContext {-# INLINE pFromJSVal #-} instance ToJSVal WebGLRenderingContext where toJSVal = return . unWebGLRenderingContext {-# INLINE toJSVal #-} instance FromJSVal WebGLRenderingContext where fromJSVal = return . fmap WebGLRenderingContext . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsWebGLRenderingContextBase WebGLRenderingContext instance IsGObject WebGLRenderingContext where typeGType _ = gTypeWebGLRenderingContext {-# INLINE typeGType #-} noWebGLRenderingContext :: Maybe WebGLRenderingContext noWebGLRenderingContext = Nothing {-# INLINE noWebGLRenderingContext #-} foreign import javascript unsafe "window[\"WebGLRenderingContext\"]" gTypeWebGLRenderingContext :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebGLRenderingContextBase". -- -- newtype WebGLRenderingContextBase = WebGLRenderingContextBase { unWebGLRenderingContextBase :: JSVal } instance Eq (WebGLRenderingContextBase) where (WebGLRenderingContextBase a) == (WebGLRenderingContextBase b) = js_eq a b instance PToJSVal WebGLRenderingContextBase where pToJSVal = unWebGLRenderingContextBase {-# INLINE pToJSVal #-} instance PFromJSVal WebGLRenderingContextBase where pFromJSVal = WebGLRenderingContextBase {-# INLINE pFromJSVal #-} instance ToJSVal WebGLRenderingContextBase where toJSVal = return . unWebGLRenderingContextBase {-# INLINE toJSVal #-} instance FromJSVal WebGLRenderingContextBase where fromJSVal = return . fmap WebGLRenderingContextBase . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsGObject o) => IsWebGLRenderingContextBase o toWebGLRenderingContextBase :: IsWebGLRenderingContextBase o => o -> WebGLRenderingContextBase toWebGLRenderingContextBase = WebGLRenderingContextBase . coerce instance IsWebGLRenderingContextBase WebGLRenderingContextBase instance IsGObject WebGLRenderingContextBase where typeGType _ = gTypeWebGLRenderingContextBase {-# INLINE typeGType #-} noWebGLRenderingContextBase :: Maybe WebGLRenderingContextBase noWebGLRenderingContextBase = Nothing {-# INLINE noWebGLRenderingContextBase #-} foreign import javascript unsafe "window[\"WebGLRenderingContextBase\"]" gTypeWebGLRenderingContextBase :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebGLSampler". -- -- newtype WebGLSampler = WebGLSampler { unWebGLSampler :: JSVal } instance Eq (WebGLSampler) where (WebGLSampler a) == (WebGLSampler b) = js_eq a b instance PToJSVal WebGLSampler where pToJSVal = unWebGLSampler {-# INLINE pToJSVal #-} instance PFromJSVal WebGLSampler where pFromJSVal = WebGLSampler {-# INLINE pFromJSVal #-} instance ToJSVal WebGLSampler where toJSVal = return . unWebGLSampler {-# INLINE toJSVal #-} instance FromJSVal WebGLSampler where fromJSVal = return . fmap WebGLSampler . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject WebGLSampler where typeGType _ = gTypeWebGLSampler {-# INLINE typeGType #-} noWebGLSampler :: Maybe WebGLSampler noWebGLSampler = Nothing {-# INLINE noWebGLSampler #-} foreign import javascript unsafe "window[\"WebGLSampler\"]" gTypeWebGLSampler :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebGLShader". -- -- newtype WebGLShader = WebGLShader { unWebGLShader :: JSVal } instance Eq (WebGLShader) where (WebGLShader a) == (WebGLShader b) = js_eq a b instance PToJSVal WebGLShader where pToJSVal = unWebGLShader {-# INLINE pToJSVal #-} instance PFromJSVal WebGLShader where pFromJSVal = WebGLShader {-# INLINE pFromJSVal #-} instance ToJSVal WebGLShader where toJSVal = return . unWebGLShader {-# INLINE toJSVal #-} instance FromJSVal WebGLShader where fromJSVal = return . fmap WebGLShader . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject WebGLShader where typeGType _ = gTypeWebGLShader {-# INLINE typeGType #-} noWebGLShader :: Maybe WebGLShader noWebGLShader = Nothing {-# INLINE noWebGLShader #-} foreign import javascript unsafe "window[\"WebGLShader\"]" gTypeWebGLShader :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebGLShaderPrecisionFormat". -- -- newtype WebGLShaderPrecisionFormat = WebGLShaderPrecisionFormat { unWebGLShaderPrecisionFormat :: JSVal } instance Eq (WebGLShaderPrecisionFormat) where (WebGLShaderPrecisionFormat a) == (WebGLShaderPrecisionFormat b) = js_eq a b instance PToJSVal WebGLShaderPrecisionFormat where pToJSVal = unWebGLShaderPrecisionFormat {-# INLINE pToJSVal #-} instance PFromJSVal WebGLShaderPrecisionFormat where pFromJSVal = WebGLShaderPrecisionFormat {-# INLINE pFromJSVal #-} instance ToJSVal WebGLShaderPrecisionFormat where toJSVal = return . unWebGLShaderPrecisionFormat {-# INLINE toJSVal #-} instance FromJSVal WebGLShaderPrecisionFormat where fromJSVal = return . fmap WebGLShaderPrecisionFormat . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject WebGLShaderPrecisionFormat where typeGType _ = gTypeWebGLShaderPrecisionFormat {-# INLINE typeGType #-} noWebGLShaderPrecisionFormat :: Maybe WebGLShaderPrecisionFormat noWebGLShaderPrecisionFormat = Nothing {-# INLINE noWebGLShaderPrecisionFormat #-} foreign import javascript unsafe "window[\"WebGLShaderPrecisionFormat\"]" gTypeWebGLShaderPrecisionFormat :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebGLSync". -- -- newtype WebGLSync = WebGLSync { unWebGLSync :: JSVal } instance Eq (WebGLSync) where (WebGLSync a) == (WebGLSync b) = js_eq a b instance PToJSVal WebGLSync where pToJSVal = unWebGLSync {-# INLINE pToJSVal #-} instance PFromJSVal WebGLSync where pFromJSVal = WebGLSync {-# INLINE pFromJSVal #-} instance ToJSVal WebGLSync where toJSVal = return . unWebGLSync {-# INLINE toJSVal #-} instance FromJSVal WebGLSync where fromJSVal = return . fmap WebGLSync . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject WebGLSync where typeGType _ = gTypeWebGLSync {-# INLINE typeGType #-} noWebGLSync :: Maybe WebGLSync noWebGLSync = Nothing {-# INLINE noWebGLSync #-} foreign import javascript unsafe "window[\"WebGLSync\"]" gTypeWebGLSync :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebGLTexture". -- -- newtype WebGLTexture = WebGLTexture { unWebGLTexture :: JSVal } instance Eq (WebGLTexture) where (WebGLTexture a) == (WebGLTexture b) = js_eq a b instance PToJSVal WebGLTexture where pToJSVal = unWebGLTexture {-# INLINE pToJSVal #-} instance PFromJSVal WebGLTexture where pFromJSVal = WebGLTexture {-# INLINE pFromJSVal #-} instance ToJSVal WebGLTexture where toJSVal = return . unWebGLTexture {-# INLINE toJSVal #-} instance FromJSVal WebGLTexture where fromJSVal = return . fmap WebGLTexture . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject WebGLTexture where typeGType _ = gTypeWebGLTexture {-# INLINE typeGType #-} noWebGLTexture :: Maybe WebGLTexture noWebGLTexture = Nothing {-# INLINE noWebGLTexture #-} foreign import javascript unsafe "window[\"WebGLTexture\"]" gTypeWebGLTexture :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebGLTransformFeedback". -- -- newtype WebGLTransformFeedback = WebGLTransformFeedback { unWebGLTransformFeedback :: JSVal } instance Eq (WebGLTransformFeedback) where (WebGLTransformFeedback a) == (WebGLTransformFeedback b) = js_eq a b instance PToJSVal WebGLTransformFeedback where pToJSVal = unWebGLTransformFeedback {-# INLINE pToJSVal #-} instance PFromJSVal WebGLTransformFeedback where pFromJSVal = WebGLTransformFeedback {-# INLINE pFromJSVal #-} instance ToJSVal WebGLTransformFeedback where toJSVal = return . unWebGLTransformFeedback {-# INLINE toJSVal #-} instance FromJSVal WebGLTransformFeedback where fromJSVal = return . fmap WebGLTransformFeedback . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject WebGLTransformFeedback where typeGType _ = gTypeWebGLTransformFeedback {-# INLINE typeGType #-} noWebGLTransformFeedback :: Maybe WebGLTransformFeedback noWebGLTransformFeedback = Nothing {-# INLINE noWebGLTransformFeedback #-} foreign import javascript unsafe "window[\"WebGLTransformFeedback\"]" gTypeWebGLTransformFeedback :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebGLUniformLocation". -- -- newtype WebGLUniformLocation = WebGLUniformLocation { unWebGLUniformLocation :: JSVal } instance Eq (WebGLUniformLocation) where (WebGLUniformLocation a) == (WebGLUniformLocation b) = js_eq a b instance PToJSVal WebGLUniformLocation where pToJSVal = unWebGLUniformLocation {-# INLINE pToJSVal #-} instance PFromJSVal WebGLUniformLocation where pFromJSVal = WebGLUniformLocation {-# INLINE pFromJSVal #-} instance ToJSVal WebGLUniformLocation where toJSVal = return . unWebGLUniformLocation {-# INLINE toJSVal #-} instance FromJSVal WebGLUniformLocation where fromJSVal = return . fmap WebGLUniformLocation . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject WebGLUniformLocation where typeGType _ = gTypeWebGLUniformLocation {-# INLINE typeGType #-} noWebGLUniformLocation :: Maybe WebGLUniformLocation noWebGLUniformLocation = Nothing {-# INLINE noWebGLUniformLocation #-} foreign import javascript unsafe "window[\"WebGLUniformLocation\"]" gTypeWebGLUniformLocation :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebGLVertexArrayObject". -- -- newtype WebGLVertexArrayObject = WebGLVertexArrayObject { unWebGLVertexArrayObject :: JSVal } instance Eq (WebGLVertexArrayObject) where (WebGLVertexArrayObject a) == (WebGLVertexArrayObject b) = js_eq a b instance PToJSVal WebGLVertexArrayObject where pToJSVal = unWebGLVertexArrayObject {-# INLINE pToJSVal #-} instance PFromJSVal WebGLVertexArrayObject where pFromJSVal = WebGLVertexArrayObject {-# INLINE pFromJSVal #-} instance ToJSVal WebGLVertexArrayObject where toJSVal = return . unWebGLVertexArrayObject {-# INLINE toJSVal #-} instance FromJSVal WebGLVertexArrayObject where fromJSVal = return . fmap WebGLVertexArrayObject . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject WebGLVertexArrayObject where typeGType _ = gTypeWebGLVertexArrayObject {-# INLINE typeGType #-} noWebGLVertexArrayObject :: Maybe WebGLVertexArrayObject noWebGLVertexArrayObject = Nothing {-# INLINE noWebGLVertexArrayObject #-} foreign import javascript unsafe "window[\"WebGLVertexArrayObject\"]" gTypeWebGLVertexArrayObject :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebGLVertexArrayObjectOES". -- -- newtype WebGLVertexArrayObjectOES = WebGLVertexArrayObjectOES { unWebGLVertexArrayObjectOES :: JSVal } instance Eq (WebGLVertexArrayObjectOES) where (WebGLVertexArrayObjectOES a) == (WebGLVertexArrayObjectOES b) = js_eq a b instance PToJSVal WebGLVertexArrayObjectOES where pToJSVal = unWebGLVertexArrayObjectOES {-# INLINE pToJSVal #-} instance PFromJSVal WebGLVertexArrayObjectOES where pFromJSVal = WebGLVertexArrayObjectOES {-# INLINE pFromJSVal #-} instance ToJSVal WebGLVertexArrayObjectOES where toJSVal = return . unWebGLVertexArrayObjectOES {-# INLINE toJSVal #-} instance FromJSVal WebGLVertexArrayObjectOES where fromJSVal = return . fmap WebGLVertexArrayObjectOES . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject WebGLVertexArrayObjectOES where typeGType _ = gTypeWebGLVertexArrayObjectOES {-# INLINE typeGType #-} noWebGLVertexArrayObjectOES :: Maybe WebGLVertexArrayObjectOES noWebGLVertexArrayObjectOES = Nothing {-# INLINE noWebGLVertexArrayObjectOES #-} foreign import javascript unsafe "window[\"WebGLVertexArrayObjectOES\"]" gTypeWebGLVertexArrayObjectOES :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebGPUBuffer". -- -- newtype WebGPUBuffer = WebGPUBuffer { unWebGPUBuffer :: JSVal } instance Eq (WebGPUBuffer) where (WebGPUBuffer a) == (WebGPUBuffer b) = js_eq a b instance PToJSVal WebGPUBuffer where pToJSVal = unWebGPUBuffer {-# INLINE pToJSVal #-} instance PFromJSVal WebGPUBuffer where pFromJSVal = WebGPUBuffer {-# INLINE pFromJSVal #-} instance ToJSVal WebGPUBuffer where toJSVal = return . unWebGPUBuffer {-# INLINE toJSVal #-} instance FromJSVal WebGPUBuffer where fromJSVal = return . fmap WebGPUBuffer . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject WebGPUBuffer where typeGType _ = gTypeWebGPUBuffer {-# INLINE typeGType #-} noWebGPUBuffer :: Maybe WebGPUBuffer noWebGPUBuffer = Nothing {-# INLINE noWebGPUBuffer #-} foreign import javascript unsafe "window[\"WebGPUBuffer\"]" gTypeWebGPUBuffer :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebGPUCommandBuffer". -- -- newtype WebGPUCommandBuffer = WebGPUCommandBuffer { unWebGPUCommandBuffer :: JSVal } instance Eq (WebGPUCommandBuffer) where (WebGPUCommandBuffer a) == (WebGPUCommandBuffer b) = js_eq a b instance PToJSVal WebGPUCommandBuffer where pToJSVal = unWebGPUCommandBuffer {-# INLINE pToJSVal #-} instance PFromJSVal WebGPUCommandBuffer where pFromJSVal = WebGPUCommandBuffer {-# INLINE pFromJSVal #-} instance ToJSVal WebGPUCommandBuffer where toJSVal = return . unWebGPUCommandBuffer {-# INLINE toJSVal #-} instance FromJSVal WebGPUCommandBuffer where fromJSVal = return . fmap WebGPUCommandBuffer . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject WebGPUCommandBuffer where typeGType _ = gTypeWebGPUCommandBuffer {-# INLINE typeGType #-} noWebGPUCommandBuffer :: Maybe WebGPUCommandBuffer noWebGPUCommandBuffer = Nothing {-# INLINE noWebGPUCommandBuffer #-} foreign import javascript unsafe "window[\"WebGPUCommandBuffer\"]" gTypeWebGPUCommandBuffer :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebGPUCommandQueue". -- -- newtype WebGPUCommandQueue = WebGPUCommandQueue { unWebGPUCommandQueue :: JSVal } instance Eq (WebGPUCommandQueue) where (WebGPUCommandQueue a) == (WebGPUCommandQueue b) = js_eq a b instance PToJSVal WebGPUCommandQueue where pToJSVal = unWebGPUCommandQueue {-# INLINE pToJSVal #-} instance PFromJSVal WebGPUCommandQueue where pFromJSVal = WebGPUCommandQueue {-# INLINE pFromJSVal #-} instance ToJSVal WebGPUCommandQueue where toJSVal = return . unWebGPUCommandQueue {-# INLINE toJSVal #-} instance FromJSVal WebGPUCommandQueue where fromJSVal = return . fmap WebGPUCommandQueue . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject WebGPUCommandQueue where typeGType _ = gTypeWebGPUCommandQueue {-# INLINE typeGType #-} noWebGPUCommandQueue :: Maybe WebGPUCommandQueue noWebGPUCommandQueue = Nothing {-# INLINE noWebGPUCommandQueue #-} foreign import javascript unsafe "window[\"WebGPUCommandQueue\"]" gTypeWebGPUCommandQueue :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebGPUComputeCommandEncoder". -- -- newtype WebGPUComputeCommandEncoder = WebGPUComputeCommandEncoder { unWebGPUComputeCommandEncoder :: JSVal } instance Eq (WebGPUComputeCommandEncoder) where (WebGPUComputeCommandEncoder a) == (WebGPUComputeCommandEncoder b) = js_eq a b instance PToJSVal WebGPUComputeCommandEncoder where pToJSVal = unWebGPUComputeCommandEncoder {-# INLINE pToJSVal #-} instance PFromJSVal WebGPUComputeCommandEncoder where pFromJSVal = WebGPUComputeCommandEncoder {-# INLINE pFromJSVal #-} instance ToJSVal WebGPUComputeCommandEncoder where toJSVal = return . unWebGPUComputeCommandEncoder {-# INLINE toJSVal #-} instance FromJSVal WebGPUComputeCommandEncoder where fromJSVal = return . fmap WebGPUComputeCommandEncoder . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject WebGPUComputeCommandEncoder where typeGType _ = gTypeWebGPUComputeCommandEncoder {-# INLINE typeGType #-} noWebGPUComputeCommandEncoder :: Maybe WebGPUComputeCommandEncoder noWebGPUComputeCommandEncoder = Nothing {-# INLINE noWebGPUComputeCommandEncoder #-} foreign import javascript unsafe "window[\"WebGPUComputeCommandEncoder\"]" gTypeWebGPUComputeCommandEncoder :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebGPUComputePipelineState". -- -- newtype WebGPUComputePipelineState = WebGPUComputePipelineState { unWebGPUComputePipelineState :: JSVal } instance Eq (WebGPUComputePipelineState) where (WebGPUComputePipelineState a) == (WebGPUComputePipelineState b) = js_eq a b instance PToJSVal WebGPUComputePipelineState where pToJSVal = unWebGPUComputePipelineState {-# INLINE pToJSVal #-} instance PFromJSVal WebGPUComputePipelineState where pFromJSVal = WebGPUComputePipelineState {-# INLINE pFromJSVal #-} instance ToJSVal WebGPUComputePipelineState where toJSVal = return . unWebGPUComputePipelineState {-# INLINE toJSVal #-} instance FromJSVal WebGPUComputePipelineState where fromJSVal = return . fmap WebGPUComputePipelineState . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject WebGPUComputePipelineState where typeGType _ = gTypeWebGPUComputePipelineState {-# INLINE typeGType #-} noWebGPUComputePipelineState :: Maybe WebGPUComputePipelineState noWebGPUComputePipelineState = Nothing {-# INLINE noWebGPUComputePipelineState #-} foreign import javascript unsafe "window[\"WebGPUComputePipelineState\"]" gTypeWebGPUComputePipelineState :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebGPUDepthStencilDescriptor". -- -- newtype WebGPUDepthStencilDescriptor = WebGPUDepthStencilDescriptor { unWebGPUDepthStencilDescriptor :: JSVal } instance Eq (WebGPUDepthStencilDescriptor) where (WebGPUDepthStencilDescriptor a) == (WebGPUDepthStencilDescriptor b) = js_eq a b instance PToJSVal WebGPUDepthStencilDescriptor where pToJSVal = unWebGPUDepthStencilDescriptor {-# INLINE pToJSVal #-} instance PFromJSVal WebGPUDepthStencilDescriptor where pFromJSVal = WebGPUDepthStencilDescriptor {-# INLINE pFromJSVal #-} instance ToJSVal WebGPUDepthStencilDescriptor where toJSVal = return . unWebGPUDepthStencilDescriptor {-# INLINE toJSVal #-} instance FromJSVal WebGPUDepthStencilDescriptor where fromJSVal = return . fmap WebGPUDepthStencilDescriptor . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject WebGPUDepthStencilDescriptor where typeGType _ = gTypeWebGPUDepthStencilDescriptor {-# INLINE typeGType #-} noWebGPUDepthStencilDescriptor :: Maybe WebGPUDepthStencilDescriptor noWebGPUDepthStencilDescriptor = Nothing {-# INLINE noWebGPUDepthStencilDescriptor #-} foreign import javascript unsafe "window[\"WebGPUDepthStencilDescriptor\"]" gTypeWebGPUDepthStencilDescriptor :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebGPUDepthStencilState". -- -- newtype WebGPUDepthStencilState = WebGPUDepthStencilState { unWebGPUDepthStencilState :: JSVal } instance Eq (WebGPUDepthStencilState) where (WebGPUDepthStencilState a) == (WebGPUDepthStencilState b) = js_eq a b instance PToJSVal WebGPUDepthStencilState where pToJSVal = unWebGPUDepthStencilState {-# INLINE pToJSVal #-} instance PFromJSVal WebGPUDepthStencilState where pFromJSVal = WebGPUDepthStencilState {-# INLINE pFromJSVal #-} instance ToJSVal WebGPUDepthStencilState where toJSVal = return . unWebGPUDepthStencilState {-# INLINE toJSVal #-} instance FromJSVal WebGPUDepthStencilState where fromJSVal = return . fmap WebGPUDepthStencilState . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject WebGPUDepthStencilState where typeGType _ = gTypeWebGPUDepthStencilState {-# INLINE typeGType #-} noWebGPUDepthStencilState :: Maybe WebGPUDepthStencilState noWebGPUDepthStencilState = Nothing {-# INLINE noWebGPUDepthStencilState #-} foreign import javascript unsafe "window[\"WebGPUDepthStencilState\"]" gTypeWebGPUDepthStencilState :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebGPUDrawable". -- -- newtype WebGPUDrawable = WebGPUDrawable { unWebGPUDrawable :: JSVal } instance Eq (WebGPUDrawable) where (WebGPUDrawable a) == (WebGPUDrawable b) = js_eq a b instance PToJSVal WebGPUDrawable where pToJSVal = unWebGPUDrawable {-# INLINE pToJSVal #-} instance PFromJSVal WebGPUDrawable where pFromJSVal = WebGPUDrawable {-# INLINE pFromJSVal #-} instance ToJSVal WebGPUDrawable where toJSVal = return . unWebGPUDrawable {-# INLINE toJSVal #-} instance FromJSVal WebGPUDrawable where fromJSVal = return . fmap WebGPUDrawable . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject WebGPUDrawable where typeGType _ = gTypeWebGPUDrawable {-# INLINE typeGType #-} noWebGPUDrawable :: Maybe WebGPUDrawable noWebGPUDrawable = Nothing {-# INLINE noWebGPUDrawable #-} foreign import javascript unsafe "window[\"WebGPUDrawable\"]" gTypeWebGPUDrawable :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebGPUFunction". -- -- newtype WebGPUFunction = WebGPUFunction { unWebGPUFunction :: JSVal } instance Eq (WebGPUFunction) where (WebGPUFunction a) == (WebGPUFunction b) = js_eq a b instance PToJSVal WebGPUFunction where pToJSVal = unWebGPUFunction {-# INLINE pToJSVal #-} instance PFromJSVal WebGPUFunction where pFromJSVal = WebGPUFunction {-# INLINE pFromJSVal #-} instance ToJSVal WebGPUFunction where toJSVal = return . unWebGPUFunction {-# INLINE toJSVal #-} instance FromJSVal WebGPUFunction where fromJSVal = return . fmap WebGPUFunction . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject WebGPUFunction where typeGType _ = gTypeWebGPUFunction {-# INLINE typeGType #-} noWebGPUFunction :: Maybe WebGPUFunction noWebGPUFunction = Nothing {-# INLINE noWebGPUFunction #-} foreign import javascript unsafe "window[\"WebGPUFunction\"]" gTypeWebGPUFunction :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebGPULibrary". -- -- newtype WebGPULibrary = WebGPULibrary { unWebGPULibrary :: JSVal } instance Eq (WebGPULibrary) where (WebGPULibrary a) == (WebGPULibrary b) = js_eq a b instance PToJSVal WebGPULibrary where pToJSVal = unWebGPULibrary {-# INLINE pToJSVal #-} instance PFromJSVal WebGPULibrary where pFromJSVal = WebGPULibrary {-# INLINE pFromJSVal #-} instance ToJSVal WebGPULibrary where toJSVal = return . unWebGPULibrary {-# INLINE toJSVal #-} instance FromJSVal WebGPULibrary where fromJSVal = return . fmap WebGPULibrary . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject WebGPULibrary where typeGType _ = gTypeWebGPULibrary {-# INLINE typeGType #-} noWebGPULibrary :: Maybe WebGPULibrary noWebGPULibrary = Nothing {-# INLINE noWebGPULibrary #-} foreign import javascript unsafe "window[\"WebGPULibrary\"]" gTypeWebGPULibrary :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebGPURenderCommandEncoder". -- -- newtype WebGPURenderCommandEncoder = WebGPURenderCommandEncoder { unWebGPURenderCommandEncoder :: JSVal } instance Eq (WebGPURenderCommandEncoder) where (WebGPURenderCommandEncoder a) == (WebGPURenderCommandEncoder b) = js_eq a b instance PToJSVal WebGPURenderCommandEncoder where pToJSVal = unWebGPURenderCommandEncoder {-# INLINE pToJSVal #-} instance PFromJSVal WebGPURenderCommandEncoder where pFromJSVal = WebGPURenderCommandEncoder {-# INLINE pFromJSVal #-} instance ToJSVal WebGPURenderCommandEncoder where toJSVal = return . unWebGPURenderCommandEncoder {-# INLINE toJSVal #-} instance FromJSVal WebGPURenderCommandEncoder where fromJSVal = return . fmap WebGPURenderCommandEncoder . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject WebGPURenderCommandEncoder where typeGType _ = gTypeWebGPURenderCommandEncoder {-# INLINE typeGType #-} noWebGPURenderCommandEncoder :: Maybe WebGPURenderCommandEncoder noWebGPURenderCommandEncoder = Nothing {-# INLINE noWebGPURenderCommandEncoder #-} foreign import javascript unsafe "window[\"WebGPURenderCommandEncoder\"]" gTypeWebGPURenderCommandEncoder :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebGPURenderPassAttachmentDescriptor". -- -- newtype WebGPURenderPassAttachmentDescriptor = WebGPURenderPassAttachmentDescriptor { unWebGPURenderPassAttachmentDescriptor :: JSVal } instance Eq (WebGPURenderPassAttachmentDescriptor) where (WebGPURenderPassAttachmentDescriptor a) == (WebGPURenderPassAttachmentDescriptor b) = js_eq a b instance PToJSVal WebGPURenderPassAttachmentDescriptor where pToJSVal = unWebGPURenderPassAttachmentDescriptor {-# INLINE pToJSVal #-} instance PFromJSVal WebGPURenderPassAttachmentDescriptor where pFromJSVal = WebGPURenderPassAttachmentDescriptor {-# INLINE pFromJSVal #-} instance ToJSVal WebGPURenderPassAttachmentDescriptor where toJSVal = return . unWebGPURenderPassAttachmentDescriptor {-# INLINE toJSVal #-} instance FromJSVal WebGPURenderPassAttachmentDescriptor where fromJSVal = return . fmap WebGPURenderPassAttachmentDescriptor . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsGObject o) => IsWebGPURenderPassAttachmentDescriptor o toWebGPURenderPassAttachmentDescriptor :: IsWebGPURenderPassAttachmentDescriptor o => o -> WebGPURenderPassAttachmentDescriptor toWebGPURenderPassAttachmentDescriptor = WebGPURenderPassAttachmentDescriptor . coerce instance IsWebGPURenderPassAttachmentDescriptor WebGPURenderPassAttachmentDescriptor instance IsGObject WebGPURenderPassAttachmentDescriptor where typeGType _ = gTypeWebGPURenderPassAttachmentDescriptor {-# INLINE typeGType #-} noWebGPURenderPassAttachmentDescriptor :: Maybe WebGPURenderPassAttachmentDescriptor noWebGPURenderPassAttachmentDescriptor = Nothing {-# INLINE noWebGPURenderPassAttachmentDescriptor #-} foreign import javascript unsafe "window[\"WebGPURenderPassAttachmentDescriptor\"]" gTypeWebGPURenderPassAttachmentDescriptor :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebGPURenderPassColorAttachmentDescriptor". -- Base interface functions are in: -- -- * "GHCJS.DOM.WebGPURenderPassAttachmentDescriptor" -- -- newtype WebGPURenderPassColorAttachmentDescriptor = WebGPURenderPassColorAttachmentDescriptor { unWebGPURenderPassColorAttachmentDescriptor :: JSVal } instance Eq (WebGPURenderPassColorAttachmentDescriptor) where (WebGPURenderPassColorAttachmentDescriptor a) == (WebGPURenderPassColorAttachmentDescriptor b) = js_eq a b instance PToJSVal WebGPURenderPassColorAttachmentDescriptor where pToJSVal = unWebGPURenderPassColorAttachmentDescriptor {-# INLINE pToJSVal #-} instance PFromJSVal WebGPURenderPassColorAttachmentDescriptor where pFromJSVal = WebGPURenderPassColorAttachmentDescriptor {-# INLINE pFromJSVal #-} instance ToJSVal WebGPURenderPassColorAttachmentDescriptor where toJSVal = return . unWebGPURenderPassColorAttachmentDescriptor {-# INLINE toJSVal #-} instance FromJSVal WebGPURenderPassColorAttachmentDescriptor where fromJSVal = return . fmap WebGPURenderPassColorAttachmentDescriptor . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsWebGPURenderPassAttachmentDescriptor WebGPURenderPassColorAttachmentDescriptor instance IsGObject WebGPURenderPassColorAttachmentDescriptor where typeGType _ = gTypeWebGPURenderPassColorAttachmentDescriptor {-# INLINE typeGType #-} noWebGPURenderPassColorAttachmentDescriptor :: Maybe WebGPURenderPassColorAttachmentDescriptor noWebGPURenderPassColorAttachmentDescriptor = Nothing {-# INLINE noWebGPURenderPassColorAttachmentDescriptor #-} foreign import javascript unsafe "window[\"WebGPURenderPassColorAttachmentDescriptor\"]" gTypeWebGPURenderPassColorAttachmentDescriptor :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebGPURenderPassDepthAttachmentDescriptor". -- Base interface functions are in: -- -- * "GHCJS.DOM.WebGPURenderPassAttachmentDescriptor" -- -- newtype WebGPURenderPassDepthAttachmentDescriptor = WebGPURenderPassDepthAttachmentDescriptor { unWebGPURenderPassDepthAttachmentDescriptor :: JSVal } instance Eq (WebGPURenderPassDepthAttachmentDescriptor) where (WebGPURenderPassDepthAttachmentDescriptor a) == (WebGPURenderPassDepthAttachmentDescriptor b) = js_eq a b instance PToJSVal WebGPURenderPassDepthAttachmentDescriptor where pToJSVal = unWebGPURenderPassDepthAttachmentDescriptor {-# INLINE pToJSVal #-} instance PFromJSVal WebGPURenderPassDepthAttachmentDescriptor where pFromJSVal = WebGPURenderPassDepthAttachmentDescriptor {-# INLINE pFromJSVal #-} instance ToJSVal WebGPURenderPassDepthAttachmentDescriptor where toJSVal = return . unWebGPURenderPassDepthAttachmentDescriptor {-# INLINE toJSVal #-} instance FromJSVal WebGPURenderPassDepthAttachmentDescriptor where fromJSVal = return . fmap WebGPURenderPassDepthAttachmentDescriptor . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsWebGPURenderPassAttachmentDescriptor WebGPURenderPassDepthAttachmentDescriptor instance IsGObject WebGPURenderPassDepthAttachmentDescriptor where typeGType _ = gTypeWebGPURenderPassDepthAttachmentDescriptor {-# INLINE typeGType #-} noWebGPURenderPassDepthAttachmentDescriptor :: Maybe WebGPURenderPassDepthAttachmentDescriptor noWebGPURenderPassDepthAttachmentDescriptor = Nothing {-# INLINE noWebGPURenderPassDepthAttachmentDescriptor #-} foreign import javascript unsafe "window[\"WebGPURenderPassDepthAttachmentDescriptor\"]" gTypeWebGPURenderPassDepthAttachmentDescriptor :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebGPURenderPassDescriptor". -- -- newtype WebGPURenderPassDescriptor = WebGPURenderPassDescriptor { unWebGPURenderPassDescriptor :: JSVal } instance Eq (WebGPURenderPassDescriptor) where (WebGPURenderPassDescriptor a) == (WebGPURenderPassDescriptor b) = js_eq a b instance PToJSVal WebGPURenderPassDescriptor where pToJSVal = unWebGPURenderPassDescriptor {-# INLINE pToJSVal #-} instance PFromJSVal WebGPURenderPassDescriptor where pFromJSVal = WebGPURenderPassDescriptor {-# INLINE pFromJSVal #-} instance ToJSVal WebGPURenderPassDescriptor where toJSVal = return . unWebGPURenderPassDescriptor {-# INLINE toJSVal #-} instance FromJSVal WebGPURenderPassDescriptor where fromJSVal = return . fmap WebGPURenderPassDescriptor . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject WebGPURenderPassDescriptor where typeGType _ = gTypeWebGPURenderPassDescriptor {-# INLINE typeGType #-} noWebGPURenderPassDescriptor :: Maybe WebGPURenderPassDescriptor noWebGPURenderPassDescriptor = Nothing {-# INLINE noWebGPURenderPassDescriptor #-} foreign import javascript unsafe "window[\"WebGPURenderPassDescriptor\"]" gTypeWebGPURenderPassDescriptor :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebGPURenderPipelineColorAttachmentDescriptor". -- -- newtype WebGPURenderPipelineColorAttachmentDescriptor = WebGPURenderPipelineColorAttachmentDescriptor { unWebGPURenderPipelineColorAttachmentDescriptor :: JSVal } instance Eq (WebGPURenderPipelineColorAttachmentDescriptor) where (WebGPURenderPipelineColorAttachmentDescriptor a) == (WebGPURenderPipelineColorAttachmentDescriptor b) = js_eq a b instance PToJSVal WebGPURenderPipelineColorAttachmentDescriptor where pToJSVal = unWebGPURenderPipelineColorAttachmentDescriptor {-# INLINE pToJSVal #-} instance PFromJSVal WebGPURenderPipelineColorAttachmentDescriptor where pFromJSVal = WebGPURenderPipelineColorAttachmentDescriptor {-# INLINE pFromJSVal #-} instance ToJSVal WebGPURenderPipelineColorAttachmentDescriptor where toJSVal = return . unWebGPURenderPipelineColorAttachmentDescriptor {-# INLINE toJSVal #-} instance FromJSVal WebGPURenderPipelineColorAttachmentDescriptor where fromJSVal = return . fmap WebGPURenderPipelineColorAttachmentDescriptor . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject WebGPURenderPipelineColorAttachmentDescriptor where typeGType _ = gTypeWebGPURenderPipelineColorAttachmentDescriptor {-# INLINE typeGType #-} noWebGPURenderPipelineColorAttachmentDescriptor :: Maybe WebGPURenderPipelineColorAttachmentDescriptor noWebGPURenderPipelineColorAttachmentDescriptor = Nothing {-# INLINE noWebGPURenderPipelineColorAttachmentDescriptor #-} foreign import javascript unsafe "window[\"WebGPURenderPipelineColorAttachmentDescriptor\"]" gTypeWebGPURenderPipelineColorAttachmentDescriptor :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebGPURenderPipelineDescriptor". -- -- newtype WebGPURenderPipelineDescriptor = WebGPURenderPipelineDescriptor { unWebGPURenderPipelineDescriptor :: JSVal } instance Eq (WebGPURenderPipelineDescriptor) where (WebGPURenderPipelineDescriptor a) == (WebGPURenderPipelineDescriptor b) = js_eq a b instance PToJSVal WebGPURenderPipelineDescriptor where pToJSVal = unWebGPURenderPipelineDescriptor {-# INLINE pToJSVal #-} instance PFromJSVal WebGPURenderPipelineDescriptor where pFromJSVal = WebGPURenderPipelineDescriptor {-# INLINE pFromJSVal #-} instance ToJSVal WebGPURenderPipelineDescriptor where toJSVal = return . unWebGPURenderPipelineDescriptor {-# INLINE toJSVal #-} instance FromJSVal WebGPURenderPipelineDescriptor where fromJSVal = return . fmap WebGPURenderPipelineDescriptor . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject WebGPURenderPipelineDescriptor where typeGType _ = gTypeWebGPURenderPipelineDescriptor {-# INLINE typeGType #-} noWebGPURenderPipelineDescriptor :: Maybe WebGPURenderPipelineDescriptor noWebGPURenderPipelineDescriptor = Nothing {-# INLINE noWebGPURenderPipelineDescriptor #-} foreign import javascript unsafe "window[\"WebGPURenderPipelineDescriptor\"]" gTypeWebGPURenderPipelineDescriptor :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebGPURenderPipelineState". -- -- newtype WebGPURenderPipelineState = WebGPURenderPipelineState { unWebGPURenderPipelineState :: JSVal } instance Eq (WebGPURenderPipelineState) where (WebGPURenderPipelineState a) == (WebGPURenderPipelineState b) = js_eq a b instance PToJSVal WebGPURenderPipelineState where pToJSVal = unWebGPURenderPipelineState {-# INLINE pToJSVal #-} instance PFromJSVal WebGPURenderPipelineState where pFromJSVal = WebGPURenderPipelineState {-# INLINE pFromJSVal #-} instance ToJSVal WebGPURenderPipelineState where toJSVal = return . unWebGPURenderPipelineState {-# INLINE toJSVal #-} instance FromJSVal WebGPURenderPipelineState where fromJSVal = return . fmap WebGPURenderPipelineState . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject WebGPURenderPipelineState where typeGType _ = gTypeWebGPURenderPipelineState {-# INLINE typeGType #-} noWebGPURenderPipelineState :: Maybe WebGPURenderPipelineState noWebGPURenderPipelineState = Nothing {-# INLINE noWebGPURenderPipelineState #-} foreign import javascript unsafe "window[\"WebGPURenderPipelineState\"]" gTypeWebGPURenderPipelineState :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebGPURenderingContext". -- -- newtype WebGPURenderingContext = WebGPURenderingContext { unWebGPURenderingContext :: JSVal } instance Eq (WebGPURenderingContext) where (WebGPURenderingContext a) == (WebGPURenderingContext b) = js_eq a b instance PToJSVal WebGPURenderingContext where pToJSVal = unWebGPURenderingContext {-# INLINE pToJSVal #-} instance PFromJSVal WebGPURenderingContext where pFromJSVal = WebGPURenderingContext {-# INLINE pFromJSVal #-} instance ToJSVal WebGPURenderingContext where toJSVal = return . unWebGPURenderingContext {-# INLINE toJSVal #-} instance FromJSVal WebGPURenderingContext where fromJSVal = return . fmap WebGPURenderingContext . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject WebGPURenderingContext where typeGType _ = gTypeWebGPURenderingContext {-# INLINE typeGType #-} noWebGPURenderingContext :: Maybe WebGPURenderingContext noWebGPURenderingContext = Nothing {-# INLINE noWebGPURenderingContext #-} foreign import javascript unsafe "window[\"WebGPURenderingContext\"]" gTypeWebGPURenderingContext :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebGPUSize". -- -- newtype WebGPUSize = WebGPUSize { unWebGPUSize :: JSVal } instance Eq (WebGPUSize) where (WebGPUSize a) == (WebGPUSize b) = js_eq a b instance PToJSVal WebGPUSize where pToJSVal = unWebGPUSize {-# INLINE pToJSVal #-} instance PFromJSVal WebGPUSize where pFromJSVal = WebGPUSize {-# INLINE pFromJSVal #-} instance ToJSVal WebGPUSize where toJSVal = return . unWebGPUSize {-# INLINE toJSVal #-} instance FromJSVal WebGPUSize where fromJSVal = return . fmap WebGPUSize . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject WebGPUSize where typeGType _ = gTypeWebGPUSize {-# INLINE typeGType #-} noWebGPUSize :: Maybe WebGPUSize noWebGPUSize = Nothing {-# INLINE noWebGPUSize #-} foreign import javascript unsafe "window[\"WebGPUSize\"]" gTypeWebGPUSize :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebGPUTexture". -- -- newtype WebGPUTexture = WebGPUTexture { unWebGPUTexture :: JSVal } instance Eq (WebGPUTexture) where (WebGPUTexture a) == (WebGPUTexture b) = js_eq a b instance PToJSVal WebGPUTexture where pToJSVal = unWebGPUTexture {-# INLINE pToJSVal #-} instance PFromJSVal WebGPUTexture where pFromJSVal = WebGPUTexture {-# INLINE pFromJSVal #-} instance ToJSVal WebGPUTexture where toJSVal = return . unWebGPUTexture {-# INLINE toJSVal #-} instance FromJSVal WebGPUTexture where fromJSVal = return . fmap WebGPUTexture . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject WebGPUTexture where typeGType _ = gTypeWebGPUTexture {-# INLINE typeGType #-} noWebGPUTexture :: Maybe WebGPUTexture noWebGPUTexture = Nothing {-# INLINE noWebGPUTexture #-} foreign import javascript unsafe "window[\"WebGPUTexture\"]" gTypeWebGPUTexture :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebGPUTextureDescriptor". -- -- newtype WebGPUTextureDescriptor = WebGPUTextureDescriptor { unWebGPUTextureDescriptor :: JSVal } instance Eq (WebGPUTextureDescriptor) where (WebGPUTextureDescriptor a) == (WebGPUTextureDescriptor b) = js_eq a b instance PToJSVal WebGPUTextureDescriptor where pToJSVal = unWebGPUTextureDescriptor {-# INLINE pToJSVal #-} instance PFromJSVal WebGPUTextureDescriptor where pFromJSVal = WebGPUTextureDescriptor {-# INLINE pFromJSVal #-} instance ToJSVal WebGPUTextureDescriptor where toJSVal = return . unWebGPUTextureDescriptor {-# INLINE toJSVal #-} instance FromJSVal WebGPUTextureDescriptor where fromJSVal = return . fmap WebGPUTextureDescriptor . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject WebGPUTextureDescriptor where typeGType _ = gTypeWebGPUTextureDescriptor {-# INLINE typeGType #-} noWebGPUTextureDescriptor :: Maybe WebGPUTextureDescriptor noWebGPUTextureDescriptor = Nothing {-# INLINE noWebGPUTextureDescriptor #-} foreign import javascript unsafe "window[\"WebGPUTextureDescriptor\"]" gTypeWebGPUTextureDescriptor :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebKitAnimationEvent". -- Base interface functions are in: -- -- * "GHCJS.DOM.Event" -- -- newtype WebKitAnimationEvent = WebKitAnimationEvent { unWebKitAnimationEvent :: JSVal } instance Eq (WebKitAnimationEvent) where (WebKitAnimationEvent a) == (WebKitAnimationEvent b) = js_eq a b instance PToJSVal WebKitAnimationEvent where pToJSVal = unWebKitAnimationEvent {-# INLINE pToJSVal #-} instance PFromJSVal WebKitAnimationEvent where pFromJSVal = WebKitAnimationEvent {-# INLINE pFromJSVal #-} instance ToJSVal WebKitAnimationEvent where toJSVal = return . unWebKitAnimationEvent {-# INLINE toJSVal #-} instance FromJSVal WebKitAnimationEvent where fromJSVal = return . fmap WebKitAnimationEvent . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEvent WebKitAnimationEvent instance IsGObject WebKitAnimationEvent where typeGType _ = gTypeWebKitAnimationEvent {-# INLINE typeGType #-} noWebKitAnimationEvent :: Maybe WebKitAnimationEvent noWebKitAnimationEvent = Nothing {-# INLINE noWebKitAnimationEvent #-} foreign import javascript unsafe "window[\"WebKitAnimationEvent\"]" gTypeWebKitAnimationEvent :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebKitAnimationEventInit". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventInit" -- -- newtype WebKitAnimationEventInit = WebKitAnimationEventInit { unWebKitAnimationEventInit :: JSVal } instance Eq (WebKitAnimationEventInit) where (WebKitAnimationEventInit a) == (WebKitAnimationEventInit b) = js_eq a b instance PToJSVal WebKitAnimationEventInit where pToJSVal = unWebKitAnimationEventInit {-# INLINE pToJSVal #-} instance PFromJSVal WebKitAnimationEventInit where pFromJSVal = WebKitAnimationEventInit {-# INLINE pFromJSVal #-} instance ToJSVal WebKitAnimationEventInit where toJSVal = return . unWebKitAnimationEventInit {-# INLINE toJSVal #-} instance FromJSVal WebKitAnimationEventInit where fromJSVal = return . fmap WebKitAnimationEventInit . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventInit WebKitAnimationEventInit instance IsGObject WebKitAnimationEventInit where typeGType _ = gTypeWebKitAnimationEventInit {-# INLINE typeGType #-} noWebKitAnimationEventInit :: Maybe WebKitAnimationEventInit noWebKitAnimationEventInit = Nothing {-# INLINE noWebKitAnimationEventInit #-} foreign import javascript unsafe "window[\"WebKitAnimationEventInit\"]" gTypeWebKitAnimationEventInit :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebKitCSSMatrix". -- -- newtype WebKitCSSMatrix = WebKitCSSMatrix { unWebKitCSSMatrix :: JSVal } instance Eq (WebKitCSSMatrix) where (WebKitCSSMatrix a) == (WebKitCSSMatrix b) = js_eq a b instance PToJSVal WebKitCSSMatrix where pToJSVal = unWebKitCSSMatrix {-# INLINE pToJSVal #-} instance PFromJSVal WebKitCSSMatrix where pFromJSVal = WebKitCSSMatrix {-# INLINE pFromJSVal #-} instance ToJSVal WebKitCSSMatrix where toJSVal = return . unWebKitCSSMatrix {-# INLINE toJSVal #-} instance FromJSVal WebKitCSSMatrix where fromJSVal = return . fmap WebKitCSSMatrix . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject WebKitCSSMatrix where typeGType _ = gTypeWebKitCSSMatrix {-# INLINE typeGType #-} noWebKitCSSMatrix :: Maybe WebKitCSSMatrix noWebKitCSSMatrix = Nothing {-# INLINE noWebKitCSSMatrix #-} foreign import javascript unsafe "window[\"WebKitCSSMatrix\"]" gTypeWebKitCSSMatrix :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebKitCSSRegionRule". -- Base interface functions are in: -- -- * "GHCJS.DOM.CSSRule" -- -- newtype WebKitCSSRegionRule = WebKitCSSRegionRule { unWebKitCSSRegionRule :: JSVal } instance Eq (WebKitCSSRegionRule) where (WebKitCSSRegionRule a) == (WebKitCSSRegionRule b) = js_eq a b instance PToJSVal WebKitCSSRegionRule where pToJSVal = unWebKitCSSRegionRule {-# INLINE pToJSVal #-} instance PFromJSVal WebKitCSSRegionRule where pFromJSVal = WebKitCSSRegionRule {-# INLINE pFromJSVal #-} instance ToJSVal WebKitCSSRegionRule where toJSVal = return . unWebKitCSSRegionRule {-# INLINE toJSVal #-} instance FromJSVal WebKitCSSRegionRule where fromJSVal = return . fmap WebKitCSSRegionRule . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsCSSRule WebKitCSSRegionRule instance IsGObject WebKitCSSRegionRule where typeGType _ = gTypeWebKitCSSRegionRule {-# INLINE typeGType #-} noWebKitCSSRegionRule :: Maybe WebKitCSSRegionRule noWebKitCSSRegionRule = Nothing {-# INLINE noWebKitCSSRegionRule #-} foreign import javascript unsafe "window[\"WebKitCSSRegionRule\"]" gTypeWebKitCSSRegionRule :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebKitCSSViewportRule". -- Base interface functions are in: -- -- * "GHCJS.DOM.CSSRule" -- -- newtype WebKitCSSViewportRule = WebKitCSSViewportRule { unWebKitCSSViewportRule :: JSVal } instance Eq (WebKitCSSViewportRule) where (WebKitCSSViewportRule a) == (WebKitCSSViewportRule b) = js_eq a b instance PToJSVal WebKitCSSViewportRule where pToJSVal = unWebKitCSSViewportRule {-# INLINE pToJSVal #-} instance PFromJSVal WebKitCSSViewportRule where pFromJSVal = WebKitCSSViewportRule {-# INLINE pFromJSVal #-} instance ToJSVal WebKitCSSViewportRule where toJSVal = return . unWebKitCSSViewportRule {-# INLINE toJSVal #-} instance FromJSVal WebKitCSSViewportRule where fromJSVal = return . fmap WebKitCSSViewportRule . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsCSSRule WebKitCSSViewportRule instance IsGObject WebKitCSSViewportRule where typeGType _ = gTypeWebKitCSSViewportRule {-# INLINE typeGType #-} noWebKitCSSViewportRule :: Maybe WebKitCSSViewportRule noWebKitCSSViewportRule = Nothing {-# INLINE noWebKitCSSViewportRule #-} foreign import javascript unsafe "window[\"WebKitCSSViewportRule\"]" gTypeWebKitCSSViewportRule :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebKitMediaKeyError". -- -- newtype WebKitMediaKeyError = WebKitMediaKeyError { unWebKitMediaKeyError :: JSVal } instance Eq (WebKitMediaKeyError) where (WebKitMediaKeyError a) == (WebKitMediaKeyError b) = js_eq a b instance PToJSVal WebKitMediaKeyError where pToJSVal = unWebKitMediaKeyError {-# INLINE pToJSVal #-} instance PFromJSVal WebKitMediaKeyError where pFromJSVal = WebKitMediaKeyError {-# INLINE pFromJSVal #-} instance ToJSVal WebKitMediaKeyError where toJSVal = return . unWebKitMediaKeyError {-# INLINE toJSVal #-} instance FromJSVal WebKitMediaKeyError where fromJSVal = return . fmap WebKitMediaKeyError . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject WebKitMediaKeyError where typeGType _ = gTypeWebKitMediaKeyError {-# INLINE typeGType #-} noWebKitMediaKeyError :: Maybe WebKitMediaKeyError noWebKitMediaKeyError = Nothing {-# INLINE noWebKitMediaKeyError #-} foreign import javascript unsafe "window[\"WebKitMediaKeyError\"]" gTypeWebKitMediaKeyError :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebKitMediaKeyMessageEvent". -- Base interface functions are in: -- -- * "GHCJS.DOM.Event" -- -- newtype WebKitMediaKeyMessageEvent = WebKitMediaKeyMessageEvent { unWebKitMediaKeyMessageEvent :: JSVal } instance Eq (WebKitMediaKeyMessageEvent) where (WebKitMediaKeyMessageEvent a) == (WebKitMediaKeyMessageEvent b) = js_eq a b instance PToJSVal WebKitMediaKeyMessageEvent where pToJSVal = unWebKitMediaKeyMessageEvent {-# INLINE pToJSVal #-} instance PFromJSVal WebKitMediaKeyMessageEvent where pFromJSVal = WebKitMediaKeyMessageEvent {-# INLINE pFromJSVal #-} instance ToJSVal WebKitMediaKeyMessageEvent where toJSVal = return . unWebKitMediaKeyMessageEvent {-# INLINE toJSVal #-} instance FromJSVal WebKitMediaKeyMessageEvent where fromJSVal = return . fmap WebKitMediaKeyMessageEvent . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEvent WebKitMediaKeyMessageEvent instance IsGObject WebKitMediaKeyMessageEvent where typeGType _ = gTypeWebKitMediaKeyMessageEvent {-# INLINE typeGType #-} noWebKitMediaKeyMessageEvent :: Maybe WebKitMediaKeyMessageEvent noWebKitMediaKeyMessageEvent = Nothing {-# INLINE noWebKitMediaKeyMessageEvent #-} foreign import javascript unsafe "window[\"WebKitMediaKeyMessageEvent\"]" gTypeWebKitMediaKeyMessageEvent :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebKitMediaKeyMessageEventInit". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventInit" -- -- newtype WebKitMediaKeyMessageEventInit = WebKitMediaKeyMessageEventInit { unWebKitMediaKeyMessageEventInit :: JSVal } instance Eq (WebKitMediaKeyMessageEventInit) where (WebKitMediaKeyMessageEventInit a) == (WebKitMediaKeyMessageEventInit b) = js_eq a b instance PToJSVal WebKitMediaKeyMessageEventInit where pToJSVal = unWebKitMediaKeyMessageEventInit {-# INLINE pToJSVal #-} instance PFromJSVal WebKitMediaKeyMessageEventInit where pFromJSVal = WebKitMediaKeyMessageEventInit {-# INLINE pFromJSVal #-} instance ToJSVal WebKitMediaKeyMessageEventInit where toJSVal = return . unWebKitMediaKeyMessageEventInit {-# INLINE toJSVal #-} instance FromJSVal WebKitMediaKeyMessageEventInit where fromJSVal = return . fmap WebKitMediaKeyMessageEventInit . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventInit WebKitMediaKeyMessageEventInit instance IsGObject WebKitMediaKeyMessageEventInit where typeGType _ = gTypeWebKitMediaKeyMessageEventInit {-# INLINE typeGType #-} noWebKitMediaKeyMessageEventInit :: Maybe WebKitMediaKeyMessageEventInit noWebKitMediaKeyMessageEventInit = Nothing {-# INLINE noWebKitMediaKeyMessageEventInit #-} foreign import javascript unsafe "window[\"WebKitMediaKeyMessageEventInit\"]" gTypeWebKitMediaKeyMessageEventInit :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebKitMediaKeyNeededEvent". -- Base interface functions are in: -- -- * "GHCJS.DOM.Event" -- -- newtype WebKitMediaKeyNeededEvent = WebKitMediaKeyNeededEvent { unWebKitMediaKeyNeededEvent :: JSVal } instance Eq (WebKitMediaKeyNeededEvent) where (WebKitMediaKeyNeededEvent a) == (WebKitMediaKeyNeededEvent b) = js_eq a b instance PToJSVal WebKitMediaKeyNeededEvent where pToJSVal = unWebKitMediaKeyNeededEvent {-# INLINE pToJSVal #-} instance PFromJSVal WebKitMediaKeyNeededEvent where pFromJSVal = WebKitMediaKeyNeededEvent {-# INLINE pFromJSVal #-} instance ToJSVal WebKitMediaKeyNeededEvent where toJSVal = return . unWebKitMediaKeyNeededEvent {-# INLINE toJSVal #-} instance FromJSVal WebKitMediaKeyNeededEvent where fromJSVal = return . fmap WebKitMediaKeyNeededEvent . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEvent WebKitMediaKeyNeededEvent instance IsGObject WebKitMediaKeyNeededEvent where typeGType _ = gTypeWebKitMediaKeyNeededEvent {-# INLINE typeGType #-} noWebKitMediaKeyNeededEvent :: Maybe WebKitMediaKeyNeededEvent noWebKitMediaKeyNeededEvent = Nothing {-# INLINE noWebKitMediaKeyNeededEvent #-} foreign import javascript unsafe "window[\"WebKitMediaKeyNeededEvent\"]" gTypeWebKitMediaKeyNeededEvent :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebKitMediaKeyNeededEventInit". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventInit" -- -- newtype WebKitMediaKeyNeededEventInit = WebKitMediaKeyNeededEventInit { unWebKitMediaKeyNeededEventInit :: JSVal } instance Eq (WebKitMediaKeyNeededEventInit) where (WebKitMediaKeyNeededEventInit a) == (WebKitMediaKeyNeededEventInit b) = js_eq a b instance PToJSVal WebKitMediaKeyNeededEventInit where pToJSVal = unWebKitMediaKeyNeededEventInit {-# INLINE pToJSVal #-} instance PFromJSVal WebKitMediaKeyNeededEventInit where pFromJSVal = WebKitMediaKeyNeededEventInit {-# INLINE pFromJSVal #-} instance ToJSVal WebKitMediaKeyNeededEventInit where toJSVal = return . unWebKitMediaKeyNeededEventInit {-# INLINE toJSVal #-} instance FromJSVal WebKitMediaKeyNeededEventInit where fromJSVal = return . fmap WebKitMediaKeyNeededEventInit . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventInit WebKitMediaKeyNeededEventInit instance IsGObject WebKitMediaKeyNeededEventInit where typeGType _ = gTypeWebKitMediaKeyNeededEventInit {-# INLINE typeGType #-} noWebKitMediaKeyNeededEventInit :: Maybe WebKitMediaKeyNeededEventInit noWebKitMediaKeyNeededEventInit = Nothing {-# INLINE noWebKitMediaKeyNeededEventInit #-} foreign import javascript unsafe "window[\"WebKitMediaKeyNeededEventInit\"]" gTypeWebKitMediaKeyNeededEventInit :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebKitMediaKeySession". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventTarget" -- -- newtype WebKitMediaKeySession = WebKitMediaKeySession { unWebKitMediaKeySession :: JSVal } instance Eq (WebKitMediaKeySession) where (WebKitMediaKeySession a) == (WebKitMediaKeySession b) = js_eq a b instance PToJSVal WebKitMediaKeySession where pToJSVal = unWebKitMediaKeySession {-# INLINE pToJSVal #-} instance PFromJSVal WebKitMediaKeySession where pFromJSVal = WebKitMediaKeySession {-# INLINE pFromJSVal #-} instance ToJSVal WebKitMediaKeySession where toJSVal = return . unWebKitMediaKeySession {-# INLINE toJSVal #-} instance FromJSVal WebKitMediaKeySession where fromJSVal = return . fmap WebKitMediaKeySession . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventTarget WebKitMediaKeySession instance IsGObject WebKitMediaKeySession where typeGType _ = gTypeWebKitMediaKeySession {-# INLINE typeGType #-} noWebKitMediaKeySession :: Maybe WebKitMediaKeySession noWebKitMediaKeySession = Nothing {-# INLINE noWebKitMediaKeySession #-} foreign import javascript unsafe "window[\"WebKitMediaKeySession\"]" gTypeWebKitMediaKeySession :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebKitMediaKeys". -- -- newtype WebKitMediaKeys = WebKitMediaKeys { unWebKitMediaKeys :: JSVal } instance Eq (WebKitMediaKeys) where (WebKitMediaKeys a) == (WebKitMediaKeys b) = js_eq a b instance PToJSVal WebKitMediaKeys where pToJSVal = unWebKitMediaKeys {-# INLINE pToJSVal #-} instance PFromJSVal WebKitMediaKeys where pFromJSVal = WebKitMediaKeys {-# INLINE pFromJSVal #-} instance ToJSVal WebKitMediaKeys where toJSVal = return . unWebKitMediaKeys {-# INLINE toJSVal #-} instance FromJSVal WebKitMediaKeys where fromJSVal = return . fmap WebKitMediaKeys . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject WebKitMediaKeys where typeGType _ = gTypeWebKitMediaKeys {-# INLINE typeGType #-} noWebKitMediaKeys :: Maybe WebKitMediaKeys noWebKitMediaKeys = Nothing {-# INLINE noWebKitMediaKeys #-} foreign import javascript unsafe "window[\"WebKitMediaKeys\"]" gTypeWebKitMediaKeys :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebKitNamedFlow". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventTarget" -- -- newtype WebKitNamedFlow = WebKitNamedFlow { unWebKitNamedFlow :: JSVal } instance Eq (WebKitNamedFlow) where (WebKitNamedFlow a) == (WebKitNamedFlow b) = js_eq a b instance PToJSVal WebKitNamedFlow where pToJSVal = unWebKitNamedFlow {-# INLINE pToJSVal #-} instance PFromJSVal WebKitNamedFlow where pFromJSVal = WebKitNamedFlow {-# INLINE pFromJSVal #-} instance ToJSVal WebKitNamedFlow where toJSVal = return . unWebKitNamedFlow {-# INLINE toJSVal #-} instance FromJSVal WebKitNamedFlow where fromJSVal = return . fmap WebKitNamedFlow . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventTarget WebKitNamedFlow instance IsGObject WebKitNamedFlow where typeGType _ = gTypeWebKitNamedFlow {-# INLINE typeGType #-} noWebKitNamedFlow :: Maybe WebKitNamedFlow noWebKitNamedFlow = Nothing {-# INLINE noWebKitNamedFlow #-} foreign import javascript unsafe "window[\"WebKitNamedFlow\"]" gTypeWebKitNamedFlow :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebKitNamespace". -- -- newtype WebKitNamespace = WebKitNamespace { unWebKitNamespace :: JSVal } instance Eq (WebKitNamespace) where (WebKitNamespace a) == (WebKitNamespace b) = js_eq a b instance PToJSVal WebKitNamespace where pToJSVal = unWebKitNamespace {-# INLINE pToJSVal #-} instance PFromJSVal WebKitNamespace where pFromJSVal = WebKitNamespace {-# INLINE pFromJSVal #-} instance ToJSVal WebKitNamespace where toJSVal = return . unWebKitNamespace {-# INLINE toJSVal #-} instance FromJSVal WebKitNamespace where fromJSVal = return . fmap WebKitNamespace . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject WebKitNamespace where typeGType _ = gTypeWebKitNamespace {-# INLINE typeGType #-} noWebKitNamespace :: Maybe WebKitNamespace noWebKitNamespace = Nothing {-# INLINE noWebKitNamespace #-} foreign import javascript unsafe "window[\"WebKitNamespace\"]" gTypeWebKitNamespace :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebKitPlaybackTargetAvailabilityEvent". -- Base interface functions are in: -- -- * "GHCJS.DOM.Event" -- -- newtype WebKitPlaybackTargetAvailabilityEvent = WebKitPlaybackTargetAvailabilityEvent { unWebKitPlaybackTargetAvailabilityEvent :: JSVal } instance Eq (WebKitPlaybackTargetAvailabilityEvent) where (WebKitPlaybackTargetAvailabilityEvent a) == (WebKitPlaybackTargetAvailabilityEvent b) = js_eq a b instance PToJSVal WebKitPlaybackTargetAvailabilityEvent where pToJSVal = unWebKitPlaybackTargetAvailabilityEvent {-# INLINE pToJSVal #-} instance PFromJSVal WebKitPlaybackTargetAvailabilityEvent where pFromJSVal = WebKitPlaybackTargetAvailabilityEvent {-# INLINE pFromJSVal #-} instance ToJSVal WebKitPlaybackTargetAvailabilityEvent where toJSVal = return . unWebKitPlaybackTargetAvailabilityEvent {-# INLINE toJSVal #-} instance FromJSVal WebKitPlaybackTargetAvailabilityEvent where fromJSVal = return . fmap WebKitPlaybackTargetAvailabilityEvent . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEvent WebKitPlaybackTargetAvailabilityEvent instance IsGObject WebKitPlaybackTargetAvailabilityEvent where typeGType _ = gTypeWebKitPlaybackTargetAvailabilityEvent {-# INLINE typeGType #-} noWebKitPlaybackTargetAvailabilityEvent :: Maybe WebKitPlaybackTargetAvailabilityEvent noWebKitPlaybackTargetAvailabilityEvent = Nothing {-# INLINE noWebKitPlaybackTargetAvailabilityEvent #-} foreign import javascript unsafe "window[\"WebKitPlaybackTargetAvailabilityEvent\"]" gTypeWebKitPlaybackTargetAvailabilityEvent :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebKitPlaybackTargetAvailabilityEventInit". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventInit" -- -- newtype WebKitPlaybackTargetAvailabilityEventInit = WebKitPlaybackTargetAvailabilityEventInit { unWebKitPlaybackTargetAvailabilityEventInit :: JSVal } instance Eq (WebKitPlaybackTargetAvailabilityEventInit) where (WebKitPlaybackTargetAvailabilityEventInit a) == (WebKitPlaybackTargetAvailabilityEventInit b) = js_eq a b instance PToJSVal WebKitPlaybackTargetAvailabilityEventInit where pToJSVal = unWebKitPlaybackTargetAvailabilityEventInit {-# INLINE pToJSVal #-} instance PFromJSVal WebKitPlaybackTargetAvailabilityEventInit where pFromJSVal = WebKitPlaybackTargetAvailabilityEventInit {-# INLINE pFromJSVal #-} instance ToJSVal WebKitPlaybackTargetAvailabilityEventInit where toJSVal = return . unWebKitPlaybackTargetAvailabilityEventInit {-# INLINE toJSVal #-} instance FromJSVal WebKitPlaybackTargetAvailabilityEventInit where fromJSVal = return . fmap WebKitPlaybackTargetAvailabilityEventInit . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventInit WebKitPlaybackTargetAvailabilityEventInit instance IsGObject WebKitPlaybackTargetAvailabilityEventInit where typeGType _ = gTypeWebKitPlaybackTargetAvailabilityEventInit {-# INLINE typeGType #-} noWebKitPlaybackTargetAvailabilityEventInit :: Maybe WebKitPlaybackTargetAvailabilityEventInit noWebKitPlaybackTargetAvailabilityEventInit = Nothing {-# INLINE noWebKitPlaybackTargetAvailabilityEventInit #-} foreign import javascript unsafe "window[\"WebKitPlaybackTargetAvailabilityEventInit\"]" gTypeWebKitPlaybackTargetAvailabilityEventInit :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebKitPoint". -- -- newtype WebKitPoint = WebKitPoint { unWebKitPoint :: JSVal } instance Eq (WebKitPoint) where (WebKitPoint a) == (WebKitPoint b) = js_eq a b instance PToJSVal WebKitPoint where pToJSVal = unWebKitPoint {-# INLINE pToJSVal #-} instance PFromJSVal WebKitPoint where pFromJSVal = WebKitPoint {-# INLINE pFromJSVal #-} instance ToJSVal WebKitPoint where toJSVal = return . unWebKitPoint {-# INLINE toJSVal #-} instance FromJSVal WebKitPoint where fromJSVal = return . fmap WebKitPoint . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject WebKitPoint where typeGType _ = gTypeWebKitPoint {-# INLINE typeGType #-} noWebKitPoint :: Maybe WebKitPoint noWebKitPoint = Nothing {-# INLINE noWebKitPoint #-} foreign import javascript unsafe "window[\"WebKitPoint\"]" gTypeWebKitPoint :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebKitSubtleCrypto". -- -- newtype WebKitSubtleCrypto = WebKitSubtleCrypto { unWebKitSubtleCrypto :: JSVal } instance Eq (WebKitSubtleCrypto) where (WebKitSubtleCrypto a) == (WebKitSubtleCrypto b) = js_eq a b instance PToJSVal WebKitSubtleCrypto where pToJSVal = unWebKitSubtleCrypto {-# INLINE pToJSVal #-} instance PFromJSVal WebKitSubtleCrypto where pFromJSVal = WebKitSubtleCrypto {-# INLINE pFromJSVal #-} instance ToJSVal WebKitSubtleCrypto where toJSVal = return . unWebKitSubtleCrypto {-# INLINE toJSVal #-} instance FromJSVal WebKitSubtleCrypto where fromJSVal = return . fmap WebKitSubtleCrypto . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject WebKitSubtleCrypto where typeGType _ = gTypeWebKitSubtleCrypto {-# INLINE typeGType #-} noWebKitSubtleCrypto :: Maybe WebKitSubtleCrypto noWebKitSubtleCrypto = Nothing {-# INLINE noWebKitSubtleCrypto #-} foreign import javascript unsafe "window[\"WebKitSubtleCrypto\"]" gTypeWebKitSubtleCrypto :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebKitTransitionEvent". -- Base interface functions are in: -- -- * "GHCJS.DOM.Event" -- -- newtype WebKitTransitionEvent = WebKitTransitionEvent { unWebKitTransitionEvent :: JSVal } instance Eq (WebKitTransitionEvent) where (WebKitTransitionEvent a) == (WebKitTransitionEvent b) = js_eq a b instance PToJSVal WebKitTransitionEvent where pToJSVal = unWebKitTransitionEvent {-# INLINE pToJSVal #-} instance PFromJSVal WebKitTransitionEvent where pFromJSVal = WebKitTransitionEvent {-# INLINE pFromJSVal #-} instance ToJSVal WebKitTransitionEvent where toJSVal = return . unWebKitTransitionEvent {-# INLINE toJSVal #-} instance FromJSVal WebKitTransitionEvent where fromJSVal = return . fmap WebKitTransitionEvent . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEvent WebKitTransitionEvent instance IsGObject WebKitTransitionEvent where typeGType _ = gTypeWebKitTransitionEvent {-# INLINE typeGType #-} noWebKitTransitionEvent :: Maybe WebKitTransitionEvent noWebKitTransitionEvent = Nothing {-# INLINE noWebKitTransitionEvent #-} foreign import javascript unsafe "window[\"WebKitTransitionEvent\"]" gTypeWebKitTransitionEvent :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebKitTransitionEventInit". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventInit" -- -- newtype WebKitTransitionEventInit = WebKitTransitionEventInit { unWebKitTransitionEventInit :: JSVal } instance Eq (WebKitTransitionEventInit) where (WebKitTransitionEventInit a) == (WebKitTransitionEventInit b) = js_eq a b instance PToJSVal WebKitTransitionEventInit where pToJSVal = unWebKitTransitionEventInit {-# INLINE pToJSVal #-} instance PFromJSVal WebKitTransitionEventInit where pFromJSVal = WebKitTransitionEventInit {-# INLINE pFromJSVal #-} instance ToJSVal WebKitTransitionEventInit where toJSVal = return . unWebKitTransitionEventInit {-# INLINE toJSVal #-} instance FromJSVal WebKitTransitionEventInit where fromJSVal = return . fmap WebKitTransitionEventInit . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventInit WebKitTransitionEventInit instance IsGObject WebKitTransitionEventInit where typeGType _ = gTypeWebKitTransitionEventInit {-# INLINE typeGType #-} noWebKitTransitionEventInit :: Maybe WebKitTransitionEventInit noWebKitTransitionEventInit = Nothing {-# INLINE noWebKitTransitionEventInit #-} foreign import javascript unsafe "window[\"WebKitTransitionEventInit\"]" gTypeWebKitTransitionEventInit :: GType -- | Functions for this inteface are in "GHCJS.DOM.WebSocket". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventTarget" -- -- newtype WebSocket = WebSocket { unWebSocket :: JSVal } instance Eq (WebSocket) where (WebSocket a) == (WebSocket b) = js_eq a b instance PToJSVal WebSocket where pToJSVal = unWebSocket {-# INLINE pToJSVal #-} instance PFromJSVal WebSocket where pFromJSVal = WebSocket {-# INLINE pFromJSVal #-} instance ToJSVal WebSocket where toJSVal = return . unWebSocket {-# INLINE toJSVal #-} instance FromJSVal WebSocket where fromJSVal = return . fmap WebSocket . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventTarget WebSocket instance IsGObject WebSocket where typeGType _ = gTypeWebSocket {-# INLINE typeGType #-} noWebSocket :: Maybe WebSocket noWebSocket = Nothing {-# INLINE noWebSocket #-} foreign import javascript unsafe "window[\"WebSocket\"]" gTypeWebSocket :: GType -- | Functions for this inteface are in "GHCJS.DOM.WheelEvent". -- Base interface functions are in: -- -- * "GHCJS.DOM.MouseEvent" -- * "GHCJS.DOM.UIEvent" -- * "GHCJS.DOM.Event" -- -- newtype WheelEvent = WheelEvent { unWheelEvent :: JSVal } instance Eq (WheelEvent) where (WheelEvent a) == (WheelEvent b) = js_eq a b instance PToJSVal WheelEvent where pToJSVal = unWheelEvent {-# INLINE pToJSVal #-} instance PFromJSVal WheelEvent where pFromJSVal = WheelEvent {-# INLINE pFromJSVal #-} instance ToJSVal WheelEvent where toJSVal = return . unWheelEvent {-# INLINE toJSVal #-} instance FromJSVal WheelEvent where fromJSVal = return . fmap WheelEvent . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsMouseEvent WheelEvent instance IsUIEvent WheelEvent instance IsEvent WheelEvent instance IsGObject WheelEvent where typeGType _ = gTypeWheelEvent {-# INLINE typeGType #-} noWheelEvent :: Maybe WheelEvent noWheelEvent = Nothing {-# INLINE noWheelEvent #-} foreign import javascript unsafe "window[\"WheelEvent\"]" gTypeWheelEvent :: GType -- | Functions for this inteface are in "GHCJS.DOM.WheelEventInit". -- Base interface functions are in: -- -- * "GHCJS.DOM.MouseEventInit" -- * "GHCJS.DOM.EventModifierInit" -- * "GHCJS.DOM.UIEventInit" -- * "GHCJS.DOM.EventInit" -- -- newtype WheelEventInit = WheelEventInit { unWheelEventInit :: JSVal } instance Eq (WheelEventInit) where (WheelEventInit a) == (WheelEventInit b) = js_eq a b instance PToJSVal WheelEventInit where pToJSVal = unWheelEventInit {-# INLINE pToJSVal #-} instance PFromJSVal WheelEventInit where pFromJSVal = WheelEventInit {-# INLINE pFromJSVal #-} instance ToJSVal WheelEventInit where toJSVal = return . unWheelEventInit {-# INLINE toJSVal #-} instance FromJSVal WheelEventInit where fromJSVal = return . fmap WheelEventInit . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsMouseEventInit WheelEventInit instance IsEventModifierInit WheelEventInit instance IsUIEventInit WheelEventInit instance IsEventInit WheelEventInit instance IsGObject WheelEventInit where typeGType _ = gTypeWheelEventInit {-# INLINE typeGType #-} noWheelEventInit :: Maybe WheelEventInit noWheelEventInit = Nothing {-# INLINE noWheelEventInit #-} foreign import javascript unsafe "window[\"WheelEventInit\"]" gTypeWheelEventInit :: GType -- | Functions for this inteface are in "GHCJS.DOM.Window". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.WindowOrWorkerGlobalScope" -- * "GHCJS.DOM.WindowEventHandlers" -- * "GHCJS.DOM.GlobalPerformance" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.GlobalCrypto" -- -- newtype Window = Window { unWindow :: JSVal } instance Eq (Window) where (Window a) == (Window b) = js_eq a b instance PToJSVal Window where pToJSVal = unWindow {-# INLINE pToJSVal #-} instance PFromJSVal Window where pFromJSVal = Window {-# INLINE pFromJSVal #-} instance ToJSVal Window where toJSVal = return . unWindow {-# INLINE toJSVal #-} instance FromJSVal Window where fromJSVal = return . fmap Window . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventTarget Window instance IsWindowOrWorkerGlobalScope Window instance IsWindowEventHandlers Window instance IsGlobalPerformance Window instance IsGlobalEventHandlers Window instance IsGlobalCrypto Window instance IsGObject Window where typeGType _ = gTypeWindow {-# INLINE typeGType #-} noWindow :: Maybe Window noWindow = Nothing {-# INLINE noWindow #-} foreign import javascript unsafe "window[\"Window\"]" gTypeWindow :: GType -- | Functions for this inteface are in "GHCJS.DOM.WindowEventHandlers". -- -- newtype WindowEventHandlers = WindowEventHandlers { unWindowEventHandlers :: JSVal } instance Eq (WindowEventHandlers) where (WindowEventHandlers a) == (WindowEventHandlers b) = js_eq a b instance PToJSVal WindowEventHandlers where pToJSVal = unWindowEventHandlers {-# INLINE pToJSVal #-} instance PFromJSVal WindowEventHandlers where pFromJSVal = WindowEventHandlers {-# INLINE pFromJSVal #-} instance ToJSVal WindowEventHandlers where toJSVal = return . unWindowEventHandlers {-# INLINE toJSVal #-} instance FromJSVal WindowEventHandlers where fromJSVal = return . fmap WindowEventHandlers . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsGObject o) => IsWindowEventHandlers o toWindowEventHandlers :: IsWindowEventHandlers o => o -> WindowEventHandlers toWindowEventHandlers = WindowEventHandlers . coerce instance IsWindowEventHandlers WindowEventHandlers instance IsGObject WindowEventHandlers where typeGType _ = gTypeWindowEventHandlers {-# INLINE typeGType #-} noWindowEventHandlers :: Maybe WindowEventHandlers noWindowEventHandlers = Nothing {-# INLINE noWindowEventHandlers #-} foreign import javascript unsafe "window[\"WindowEventHandlers\"]" gTypeWindowEventHandlers :: GType -- | Functions for this inteface are in "GHCJS.DOM.WindowOrWorkerGlobalScope". -- -- newtype WindowOrWorkerGlobalScope = WindowOrWorkerGlobalScope { unWindowOrWorkerGlobalScope :: JSVal } instance Eq (WindowOrWorkerGlobalScope) where (WindowOrWorkerGlobalScope a) == (WindowOrWorkerGlobalScope b) = js_eq a b instance PToJSVal WindowOrWorkerGlobalScope where pToJSVal = unWindowOrWorkerGlobalScope {-# INLINE pToJSVal #-} instance PFromJSVal WindowOrWorkerGlobalScope where pFromJSVal = WindowOrWorkerGlobalScope {-# INLINE pFromJSVal #-} instance ToJSVal WindowOrWorkerGlobalScope where toJSVal = return . unWindowOrWorkerGlobalScope {-# INLINE toJSVal #-} instance FromJSVal WindowOrWorkerGlobalScope where fromJSVal = return . fmap WindowOrWorkerGlobalScope . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsGObject o) => IsWindowOrWorkerGlobalScope o toWindowOrWorkerGlobalScope :: IsWindowOrWorkerGlobalScope o => o -> WindowOrWorkerGlobalScope toWindowOrWorkerGlobalScope = WindowOrWorkerGlobalScope . coerce instance IsWindowOrWorkerGlobalScope WindowOrWorkerGlobalScope instance IsGObject WindowOrWorkerGlobalScope where typeGType _ = gTypeWindowOrWorkerGlobalScope {-# INLINE typeGType #-} noWindowOrWorkerGlobalScope :: Maybe WindowOrWorkerGlobalScope noWindowOrWorkerGlobalScope = Nothing {-# INLINE noWindowOrWorkerGlobalScope #-} foreign import javascript unsafe "window[\"WindowOrWorkerGlobalScope\"]" gTypeWindowOrWorkerGlobalScope :: GType -- | Functions for this inteface are in "GHCJS.DOM.Worker". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.AbstractWorker" -- -- newtype Worker = Worker { unWorker :: JSVal } instance Eq (Worker) where (Worker a) == (Worker b) = js_eq a b instance PToJSVal Worker where pToJSVal = unWorker {-# INLINE pToJSVal #-} instance PFromJSVal Worker where pFromJSVal = Worker {-# INLINE pFromJSVal #-} instance ToJSVal Worker where toJSVal = return . unWorker {-# INLINE toJSVal #-} instance FromJSVal Worker where fromJSVal = return . fmap Worker . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsEventTarget Worker instance IsAbstractWorker Worker instance IsGObject Worker where typeGType _ = gTypeWorker {-# INLINE typeGType #-} noWorker :: Maybe Worker noWorker = Nothing {-# INLINE noWorker #-} foreign import javascript unsafe "window[\"Worker\"]" gTypeWorker :: GType -- | Functions for this inteface are in "GHCJS.DOM.WorkerGlobalScope". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.WindowOrWorkerGlobalScope" -- * "GHCJS.DOM.GlobalPerformance" -- * "GHCJS.DOM.GlobalCrypto" -- -- newtype WorkerGlobalScope = WorkerGlobalScope { unWorkerGlobalScope :: JSVal } instance Eq (WorkerGlobalScope) where (WorkerGlobalScope a) == (WorkerGlobalScope b) = js_eq a b instance PToJSVal WorkerGlobalScope where pToJSVal = unWorkerGlobalScope {-# INLINE pToJSVal #-} instance PFromJSVal WorkerGlobalScope where pFromJSVal = WorkerGlobalScope {-# INLINE pFromJSVal #-} instance ToJSVal WorkerGlobalScope where toJSVal = return . unWorkerGlobalScope {-# INLINE toJSVal #-} instance FromJSVal WorkerGlobalScope where fromJSVal = return . fmap WorkerGlobalScope . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsEventTarget o, IsWindowOrWorkerGlobalScope o, IsGlobalPerformance o, IsGlobalCrypto o, IsGObject o) => IsWorkerGlobalScope o toWorkerGlobalScope :: IsWorkerGlobalScope o => o -> WorkerGlobalScope toWorkerGlobalScope = WorkerGlobalScope . coerce instance IsWorkerGlobalScope WorkerGlobalScope instance IsEventTarget WorkerGlobalScope instance IsWindowOrWorkerGlobalScope WorkerGlobalScope instance IsGlobalPerformance WorkerGlobalScope instance IsGlobalCrypto WorkerGlobalScope instance IsGObject WorkerGlobalScope where typeGType _ = gTypeWorkerGlobalScope {-# INLINE typeGType #-} noWorkerGlobalScope :: Maybe WorkerGlobalScope noWorkerGlobalScope = Nothing {-# INLINE noWorkerGlobalScope #-} foreign import javascript unsafe "window[\"WorkerGlobalScope\"]" gTypeWorkerGlobalScope :: GType -- | Functions for this inteface are in "GHCJS.DOM.WorkerLocation". -- -- newtype WorkerLocation = WorkerLocation { unWorkerLocation :: JSVal } instance Eq (WorkerLocation) where (WorkerLocation a) == (WorkerLocation b) = js_eq a b instance PToJSVal WorkerLocation where pToJSVal = unWorkerLocation {-# INLINE pToJSVal #-} instance PFromJSVal WorkerLocation where pFromJSVal = WorkerLocation {-# INLINE pFromJSVal #-} instance ToJSVal WorkerLocation where toJSVal = return . unWorkerLocation {-# INLINE toJSVal #-} instance FromJSVal WorkerLocation where fromJSVal = return . fmap WorkerLocation . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject WorkerLocation where typeGType _ = gTypeWorkerLocation {-# INLINE typeGType #-} noWorkerLocation :: Maybe WorkerLocation noWorkerLocation = Nothing {-# INLINE noWorkerLocation #-} foreign import javascript unsafe "window[\"WorkerLocation\"]" gTypeWorkerLocation :: GType -- | Functions for this inteface are in "GHCJS.DOM.WorkerNavigator". -- Base interface functions are in: -- -- * "GHCJS.DOM.NavigatorOnLine" -- * "GHCJS.DOM.NavigatorLanguage" -- * "GHCJS.DOM.NavigatorID" -- * "GHCJS.DOM.NavigatorConcurrentHardware" -- -- newtype WorkerNavigator = WorkerNavigator { unWorkerNavigator :: JSVal } instance Eq (WorkerNavigator) where (WorkerNavigator a) == (WorkerNavigator b) = js_eq a b instance PToJSVal WorkerNavigator where pToJSVal = unWorkerNavigator {-# INLINE pToJSVal #-} instance PFromJSVal WorkerNavigator where pFromJSVal = WorkerNavigator {-# INLINE pFromJSVal #-} instance ToJSVal WorkerNavigator where toJSVal = return . unWorkerNavigator {-# INLINE toJSVal #-} instance FromJSVal WorkerNavigator where fromJSVal = return . fmap WorkerNavigator . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsNavigatorOnLine WorkerNavigator instance IsNavigatorLanguage WorkerNavigator instance IsNavigatorID WorkerNavigator instance IsNavigatorConcurrentHardware WorkerNavigator instance IsGObject WorkerNavigator where typeGType _ = gTypeWorkerNavigator {-# INLINE typeGType #-} noWorkerNavigator :: Maybe WorkerNavigator noWorkerNavigator = Nothing {-# INLINE noWorkerNavigator #-} foreign import javascript unsafe "window[\"WorkerNavigator\"]" gTypeWorkerNavigator :: GType -- | Functions for this inteface are in "GHCJS.DOM.WritableStream". -- -- newtype WritableStream = WritableStream { unWritableStream :: JSVal } instance Eq (WritableStream) where (WritableStream a) == (WritableStream b) = js_eq a b instance PToJSVal WritableStream where pToJSVal = unWritableStream {-# INLINE pToJSVal #-} instance PFromJSVal WritableStream where pFromJSVal = WritableStream {-# INLINE pFromJSVal #-} instance ToJSVal WritableStream where toJSVal = return . unWritableStream {-# INLINE toJSVal #-} instance FromJSVal WritableStream where fromJSVal = return . fmap WritableStream . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject WritableStream where typeGType _ = gTypeWritableStream {-# INLINE typeGType #-} noWritableStream :: Maybe WritableStream noWritableStream = Nothing {-# INLINE noWritableStream #-} foreign import javascript unsafe "window[\"WritableStream\"]" gTypeWritableStream :: GType -- | Functions for this inteface are in "GHCJS.DOM.XMLDocument". -- Base interface functions are in: -- -- * "GHCJS.DOM.Document" -- * "GHCJS.DOM.Node" -- * "GHCJS.DOM.EventTarget" -- * "GHCJS.DOM.GlobalEventHandlers" -- * "GHCJS.DOM.DocumentOrShadowRoot" -- * "GHCJS.DOM.NonElementParentNode" -- * "GHCJS.DOM.ParentNode" -- * "GHCJS.DOM.DocumentAndElementEventHandlers" -- -- newtype XMLDocument = XMLDocument { unXMLDocument :: JSVal } instance Eq (XMLDocument) where (XMLDocument a) == (XMLDocument b) = js_eq a b instance PToJSVal XMLDocument where pToJSVal = unXMLDocument {-# INLINE pToJSVal #-} instance PFromJSVal XMLDocument where pFromJSVal = XMLDocument {-# INLINE pFromJSVal #-} instance ToJSVal XMLDocument where toJSVal = return . unXMLDocument {-# INLINE toJSVal #-} instance FromJSVal XMLDocument where fromJSVal = return . fmap XMLDocument . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsDocument XMLDocument instance IsNode XMLDocument instance IsEventTarget XMLDocument instance IsGlobalEventHandlers XMLDocument instance IsDocumentOrShadowRoot XMLDocument instance IsNonElementParentNode XMLDocument instance IsParentNode XMLDocument instance IsDocumentAndElementEventHandlers XMLDocument instance IsGObject XMLDocument where typeGType _ = gTypeXMLDocument {-# INLINE typeGType #-} noXMLDocument :: Maybe XMLDocument noXMLDocument = Nothing {-# INLINE noXMLDocument #-} foreign import javascript unsafe "window[\"XMLDocument\"]" gTypeXMLDocument :: GType -- | Functions for this inteface are in "GHCJS.DOM.XMLHttpRequest". -- Base interface functions are in: -- -- * "GHCJS.DOM.XMLHttpRequestEventTarget" -- * "GHCJS.DOM.EventTarget" -- -- newtype XMLHttpRequest = XMLHttpRequest { unXMLHttpRequest :: JSVal } instance Eq (XMLHttpRequest) where (XMLHttpRequest a) == (XMLHttpRequest b) = js_eq a b instance PToJSVal XMLHttpRequest where pToJSVal = unXMLHttpRequest {-# INLINE pToJSVal #-} instance PFromJSVal XMLHttpRequest where pFromJSVal = XMLHttpRequest {-# INLINE pFromJSVal #-} instance ToJSVal XMLHttpRequest where toJSVal = return . unXMLHttpRequest {-# INLINE toJSVal #-} instance FromJSVal XMLHttpRequest where fromJSVal = return . fmap XMLHttpRequest . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsXMLHttpRequestEventTarget XMLHttpRequest instance IsEventTarget XMLHttpRequest instance IsGObject XMLHttpRequest where typeGType _ = gTypeXMLHttpRequest {-# INLINE typeGType #-} noXMLHttpRequest :: Maybe XMLHttpRequest noXMLHttpRequest = Nothing {-# INLINE noXMLHttpRequest #-} foreign import javascript unsafe "window[\"XMLHttpRequest\"]" gTypeXMLHttpRequest :: GType -- | Functions for this inteface are in "GHCJS.DOM.XMLHttpRequestEventTarget". -- Base interface functions are in: -- -- * "GHCJS.DOM.EventTarget" -- -- newtype XMLHttpRequestEventTarget = XMLHttpRequestEventTarget { unXMLHttpRequestEventTarget :: JSVal } instance Eq (XMLHttpRequestEventTarget) where (XMLHttpRequestEventTarget a) == (XMLHttpRequestEventTarget b) = js_eq a b instance PToJSVal XMLHttpRequestEventTarget where pToJSVal = unXMLHttpRequestEventTarget {-# INLINE pToJSVal #-} instance PFromJSVal XMLHttpRequestEventTarget where pFromJSVal = XMLHttpRequestEventTarget {-# INLINE pFromJSVal #-} instance ToJSVal XMLHttpRequestEventTarget where toJSVal = return . unXMLHttpRequestEventTarget {-# INLINE toJSVal #-} instance FromJSVal XMLHttpRequestEventTarget where fromJSVal = return . fmap XMLHttpRequestEventTarget . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} class (IsEventTarget o, IsGObject o) => IsXMLHttpRequestEventTarget o toXMLHttpRequestEventTarget :: IsXMLHttpRequestEventTarget o => o -> XMLHttpRequestEventTarget toXMLHttpRequestEventTarget = XMLHttpRequestEventTarget . coerce instance IsXMLHttpRequestEventTarget XMLHttpRequestEventTarget instance IsEventTarget XMLHttpRequestEventTarget instance IsGObject XMLHttpRequestEventTarget where typeGType _ = gTypeXMLHttpRequestEventTarget {-# INLINE typeGType #-} noXMLHttpRequestEventTarget :: Maybe XMLHttpRequestEventTarget noXMLHttpRequestEventTarget = Nothing {-# INLINE noXMLHttpRequestEventTarget #-} foreign import javascript unsafe "window[\"XMLHttpRequestEventTarget\"]" gTypeXMLHttpRequestEventTarget :: GType -- | Functions for this inteface are in "GHCJS.DOM.XMLHttpRequestProgressEvent". -- Base interface functions are in: -- -- * "GHCJS.DOM.ProgressEvent" -- * "GHCJS.DOM.Event" -- -- newtype XMLHttpRequestProgressEvent = XMLHttpRequestProgressEvent { unXMLHttpRequestProgressEvent :: JSVal } instance Eq (XMLHttpRequestProgressEvent) where (XMLHttpRequestProgressEvent a) == (XMLHttpRequestProgressEvent b) = js_eq a b instance PToJSVal XMLHttpRequestProgressEvent where pToJSVal = unXMLHttpRequestProgressEvent {-# INLINE pToJSVal #-} instance PFromJSVal XMLHttpRequestProgressEvent where pFromJSVal = XMLHttpRequestProgressEvent {-# INLINE pFromJSVal #-} instance ToJSVal XMLHttpRequestProgressEvent where toJSVal = return . unXMLHttpRequestProgressEvent {-# INLINE toJSVal #-} instance FromJSVal XMLHttpRequestProgressEvent where fromJSVal = return . fmap XMLHttpRequestProgressEvent . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsProgressEvent XMLHttpRequestProgressEvent instance IsEvent XMLHttpRequestProgressEvent instance IsGObject XMLHttpRequestProgressEvent where typeGType _ = gTypeXMLHttpRequestProgressEvent {-# INLINE typeGType #-} noXMLHttpRequestProgressEvent :: Maybe XMLHttpRequestProgressEvent noXMLHttpRequestProgressEvent = Nothing {-# INLINE noXMLHttpRequestProgressEvent #-} foreign import javascript unsafe "window[\"XMLHttpRequestProgressEvent\"]" gTypeXMLHttpRequestProgressEvent :: GType -- | Functions for this inteface are in "GHCJS.DOM.XMLHttpRequestUpload". -- Base interface functions are in: -- -- * "GHCJS.DOM.XMLHttpRequestEventTarget" -- * "GHCJS.DOM.EventTarget" -- -- newtype XMLHttpRequestUpload = XMLHttpRequestUpload { unXMLHttpRequestUpload :: JSVal } instance Eq (XMLHttpRequestUpload) where (XMLHttpRequestUpload a) == (XMLHttpRequestUpload b) = js_eq a b instance PToJSVal XMLHttpRequestUpload where pToJSVal = unXMLHttpRequestUpload {-# INLINE pToJSVal #-} instance PFromJSVal XMLHttpRequestUpload where pFromJSVal = XMLHttpRequestUpload {-# INLINE pFromJSVal #-} instance ToJSVal XMLHttpRequestUpload where toJSVal = return . unXMLHttpRequestUpload {-# INLINE toJSVal #-} instance FromJSVal XMLHttpRequestUpload where fromJSVal = return . fmap XMLHttpRequestUpload . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsXMLHttpRequestEventTarget XMLHttpRequestUpload instance IsEventTarget XMLHttpRequestUpload instance IsGObject XMLHttpRequestUpload where typeGType _ = gTypeXMLHttpRequestUpload {-# INLINE typeGType #-} noXMLHttpRequestUpload :: Maybe XMLHttpRequestUpload noXMLHttpRequestUpload = Nothing {-# INLINE noXMLHttpRequestUpload #-} foreign import javascript unsafe "window[\"XMLHttpRequestUpload\"]" gTypeXMLHttpRequestUpload :: GType -- | Functions for this inteface are in "GHCJS.DOM.XMLSerializer". -- -- newtype XMLSerializer = XMLSerializer { unXMLSerializer :: JSVal } instance Eq (XMLSerializer) where (XMLSerializer a) == (XMLSerializer b) = js_eq a b instance PToJSVal XMLSerializer where pToJSVal = unXMLSerializer {-# INLINE pToJSVal #-} instance PFromJSVal XMLSerializer where pFromJSVal = XMLSerializer {-# INLINE pFromJSVal #-} instance ToJSVal XMLSerializer where toJSVal = return . unXMLSerializer {-# INLINE toJSVal #-} instance FromJSVal XMLSerializer where fromJSVal = return . fmap XMLSerializer . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject XMLSerializer where typeGType _ = gTypeXMLSerializer {-# INLINE typeGType #-} noXMLSerializer :: Maybe XMLSerializer noXMLSerializer = Nothing {-# INLINE noXMLSerializer #-} foreign import javascript unsafe "window[\"XMLSerializer\"]" gTypeXMLSerializer :: GType -- | Functions for this inteface are in "GHCJS.DOM.XPathEvaluator". -- -- newtype XPathEvaluator = XPathEvaluator { unXPathEvaluator :: JSVal } instance Eq (XPathEvaluator) where (XPathEvaluator a) == (XPathEvaluator b) = js_eq a b instance PToJSVal XPathEvaluator where pToJSVal = unXPathEvaluator {-# INLINE pToJSVal #-} instance PFromJSVal XPathEvaluator where pFromJSVal = XPathEvaluator {-# INLINE pFromJSVal #-} instance ToJSVal XPathEvaluator where toJSVal = return . unXPathEvaluator {-# INLINE toJSVal #-} instance FromJSVal XPathEvaluator where fromJSVal = return . fmap XPathEvaluator . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject XPathEvaluator where typeGType _ = gTypeXPathEvaluator {-# INLINE typeGType #-} noXPathEvaluator :: Maybe XPathEvaluator noXPathEvaluator = Nothing {-# INLINE noXPathEvaluator #-} foreign import javascript unsafe "window[\"XPathEvaluator\"]" gTypeXPathEvaluator :: GType -- | Functions for this inteface are in "GHCJS.DOM.XPathException". -- -- newtype XPathException = XPathException { unXPathException :: JSVal } instance Eq (XPathException) where (XPathException a) == (XPathException b) = js_eq a b instance PToJSVal XPathException where pToJSVal = unXPathException {-# INLINE pToJSVal #-} instance PFromJSVal XPathException where pFromJSVal = XPathException {-# INLINE pFromJSVal #-} instance ToJSVal XPathException where toJSVal = return . unXPathException {-# INLINE toJSVal #-} instance FromJSVal XPathException where fromJSVal = return . fmap XPathException . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject XPathException where typeGType _ = gTypeXPathException {-# INLINE typeGType #-} noXPathException :: Maybe XPathException noXPathException = Nothing {-# INLINE noXPathException #-} foreign import javascript unsafe "window[\"XPathException\"]" gTypeXPathException :: GType -- | Functions for this inteface are in "GHCJS.DOM.XPathExpression". -- -- newtype XPathExpression = XPathExpression { unXPathExpression :: JSVal } instance Eq (XPathExpression) where (XPathExpression a) == (XPathExpression b) = js_eq a b instance PToJSVal XPathExpression where pToJSVal = unXPathExpression {-# INLINE pToJSVal #-} instance PFromJSVal XPathExpression where pFromJSVal = XPathExpression {-# INLINE pFromJSVal #-} instance ToJSVal XPathExpression where toJSVal = return . unXPathExpression {-# INLINE toJSVal #-} instance FromJSVal XPathExpression where fromJSVal = return . fmap XPathExpression . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject XPathExpression where typeGType _ = gTypeXPathExpression {-# INLINE typeGType #-} noXPathExpression :: Maybe XPathExpression noXPathExpression = Nothing {-# INLINE noXPathExpression #-} foreign import javascript unsafe "window[\"XPathExpression\"]" gTypeXPathExpression :: GType -- | Functions for this inteface are in "GHCJS.DOM.XPathNSResolver". -- -- newtype XPathNSResolver = XPathNSResolver { unXPathNSResolver :: JSVal } instance Eq (XPathNSResolver) where (XPathNSResolver a) == (XPathNSResolver b) = js_eq a b instance PToJSVal XPathNSResolver where pToJSVal = unXPathNSResolver {-# INLINE pToJSVal #-} instance PFromJSVal XPathNSResolver where pFromJSVal = XPathNSResolver {-# INLINE pFromJSVal #-} instance ToJSVal XPathNSResolver where toJSVal = return . unXPathNSResolver {-# INLINE toJSVal #-} instance FromJSVal XPathNSResolver where fromJSVal = return . fmap XPathNSResolver . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject XPathNSResolver where typeGType _ = gTypeXPathNSResolver {-# INLINE typeGType #-} noXPathNSResolver :: Maybe XPathNSResolver noXPathNSResolver = Nothing {-# INLINE noXPathNSResolver #-} foreign import javascript unsafe "window[\"XPathNSResolver\"]" gTypeXPathNSResolver :: GType -- | Functions for this inteface are in "GHCJS.DOM.XPathResult". -- -- newtype XPathResult = XPathResult { unXPathResult :: JSVal } instance Eq (XPathResult) where (XPathResult a) == (XPathResult b) = js_eq a b instance PToJSVal XPathResult where pToJSVal = unXPathResult {-# INLINE pToJSVal #-} instance PFromJSVal XPathResult where pFromJSVal = XPathResult {-# INLINE pFromJSVal #-} instance ToJSVal XPathResult where toJSVal = return . unXPathResult {-# INLINE toJSVal #-} instance FromJSVal XPathResult where fromJSVal = return . fmap XPathResult . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject XPathResult where typeGType _ = gTypeXPathResult {-# INLINE typeGType #-} noXPathResult :: Maybe XPathResult noXPathResult = Nothing {-# INLINE noXPathResult #-} foreign import javascript unsafe "window[\"XPathResult\"]" gTypeXPathResult :: GType -- | Functions for this inteface are in "GHCJS.DOM.XSLTProcessor". -- -- newtype XSLTProcessor = XSLTProcessor { unXSLTProcessor :: JSVal } instance Eq (XSLTProcessor) where (XSLTProcessor a) == (XSLTProcessor b) = js_eq a b instance PToJSVal XSLTProcessor where pToJSVal = unXSLTProcessor {-# INLINE pToJSVal #-} instance PFromJSVal XSLTProcessor where pFromJSVal = XSLTProcessor {-# INLINE pFromJSVal #-} instance ToJSVal XSLTProcessor where toJSVal = return . unXSLTProcessor {-# INLINE toJSVal #-} instance FromJSVal XSLTProcessor where fromJSVal = return . fmap XSLTProcessor . maybeJSNullOrUndefined {-# INLINE fromJSVal #-} instance IsGObject XSLTProcessor where typeGType _ = gTypeXSLTProcessor {-# INLINE typeGType #-} noXSLTProcessor :: Maybe XSLTProcessor noXSLTProcessor = Nothing {-# INLINE noXSLTProcessor #-} foreign import javascript unsafe "window[\"XSLTProcessor\"]" gTypeXSLTProcessor :: GType