Safe Haskell | None |
---|---|
Language | Haskell2010 |
JSDOM.Types
Contents
- JavaScript Context and Monad
- DOM Context and Monad
- JavaScript Value
- JavaScript String
- JavaScript Array
- JavaScript Object
- Nullable
- DOM String
- Object
- TypedArray
- Promise
- Callbacks
- Custom Types
- Record Type
- Dictionaries
- Mutation Callback
- Date
- Arrays
- Geolocation
- Crypto
- WebGL typedefs
- Used for better error messages
- Interface types from IDL files
- data JSContextRef :: *
- data JSM a :: * -> *
- askJSM :: MonadJSM m => m JSContextRef
- runJSM :: MonadIO m => JSM a -> JSContextRef -> m a
- class (Applicative m, MonadIO m) => MonadJSM m where
- liftJSM :: MonadJSM m => JSM a -> m a
- type DOMContext = JSContextRef
- type DOM = JSM
- askDOM :: MonadDOM m => m DOMContext
- runDOM :: MonadIO m => DOM a -> DOMContext -> m a
- type MonadDOM = MonadJSM
- liftDOM :: MonadDOM m => DOM a -> m a
- data JSVal :: *
- class ToJSVal a where
- class FromJSVal a where
- class PToJSVal a where
- class PFromJSVal a where
- integralToDoubleToJSVal :: Integral a => a -> JSM JSVal
- integralFromDoubleFromJSVal :: Integral a => JSVal -> JSM (Maybe a)
- integralFromDoubleFromJSValUnchecked :: Integral a => JSVal -> JSM a
- data JSString :: *
- class ToJSVal a => ToJSString a where
- class FromJSVal a => FromJSString a where
- toMaybeJSString :: ToJSString a => Maybe a -> JSM JSVal
- fromMaybeJSString :: FromJSString a => JSVal -> JSM (Maybe a)
- noJSString :: Maybe JSString
- fromJSArray :: FromJSVal o => JSVal -> JSM [Maybe o]
- fromJSArrayUnchecked :: FromJSVal o => JSVal -> JSM [o]
- newtype Object :: * = Object JSVal
- newtype Nullable a :: * -> * = Nullable a
- nullableToMaybe :: FromJSVal a => JSVal -> JSM (Maybe a)
- maybeToNullable :: ToJSVal a => Maybe a -> JSM JSVal
- type DOMString = JSString
- type ToDOMString s = ToJSString s
- type FromDOMString s = FromJSString s
- type IsDOMString s = (ToDOMString s, FromDOMString s)
- noDOMString :: Maybe DOMString
- type USVString = JSString
- type IsUSVString s = (ToDOMString s, FromDOMString s)
- noUSVString :: Maybe USVString
- type ByteString = JSString
- type IsByteString s = (ToDOMString s, FromDOMString s)
- noByteString :: Maybe ByteString
- type CSSOMString = JSString
- type IsCSSOMString s = (ToDOMString s, FromDOMString s)
- noCSSOMString :: Maybe CSSOMString
- maybeNullOrUndefined :: ToJSVal value => value -> JSM (Maybe JSVal)
- maybeNullOrUndefined' :: ToJSVal value => (JSVal -> JSM a) -> value -> JSM (Maybe a)
- newtype GType = GType Object
- newtype GObject = GObject {}
- noGObject :: Maybe GObject
- class (ToJSVal o, FromJSVal o, Coercible o JSVal) => IsGObject o
- toGObject :: IsGObject o => o -> GObject
- gTypeGObject :: JSM GType
- isA :: IsGObject o => o -> GType -> JSM Bool
- objectToString :: (IsGObject self, FromJSString result) => self -> JSM result
- castTo :: forall obj obj' m. (Coercible obj JSVal, IsGObject obj', MonadJSM m) => (JSVal -> obj') -> obj -> m (Maybe obj')
- unsafeCastTo :: forall obj obj' m. (HasCallStack, Coercible obj JSVal, IsGObject obj', MonadJSM m) => (JSVal -> obj') -> obj -> m obj'
- uncheckedCastTo :: (Coercible obj JSVal, IsGObject obj') => (JSVal -> obj') -> obj -> obj'
- strictEqual :: (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
- newtype RawTypedArray = RawTypedArray {}
- class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsRawTypedArray o
- toRawTypedArray :: IsRawTypedArray o => o -> RawTypedArray
- noRawTypedArray :: Maybe RawTypedArray
- newtype Function = Function {
- unFunction :: JSVal
- class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsFunction o
- toFunction :: IsFunction o => o -> Function
- noFunction :: Maybe Function
- newtype PromiseRejected = PromiseRejected {}
- noPromiseRejected :: Maybe PromiseRejected
- readPromise :: JSVal -> JSM JSVal
- newtype Callback a = Callback Function
- withCallback :: (MonadDOM m, Coercible c Function) => JSM c -> (c -> JSM a) -> m a
- newtype AudioBufferCallback = AudioBufferCallback (Callback (JSVal -> IO ()))
- noAudioBufferCallback :: Maybe AudioBufferCallback
- newtype BlobCallback = BlobCallback (Callback (JSVal -> IO ()))
- noBlobCallback :: Maybe BlobCallback
- newtype DatabaseCallback = DatabaseCallback (Callback (JSVal -> IO ()))
- noDatabaseCallback :: Maybe DatabaseCallback
- newtype IntersectionObserverCallback = IntersectionObserverCallback (Callback (JSVal -> JSVal -> IO ()))
- noIntersectionObserverCallback :: Maybe IntersectionObserverCallback
- newtype MediaQueryListListener = MediaQueryListListener (Callback (JSVal -> IO ()))
- noMediaQueryListListener :: Maybe MediaQueryListListener
- newtype MediaStreamTrackSourcesCallback = MediaStreamTrackSourcesCallback (Callback (JSVal -> IO ()))
- noMediaStreamTrackSourcesCallback :: Maybe MediaStreamTrackSourcesCallback
- newtype NavigatorUserMediaErrorCallback = NavigatorUserMediaErrorCallback (Callback (JSVal -> IO ()))
- noNavigatorUserMediaErrorCallback :: Maybe NavigatorUserMediaErrorCallback
- newtype NavigatorUserMediaSuccessCallback = NavigatorUserMediaSuccessCallback (Callback (JSVal -> IO ()))
- noNavigatorUserMediaSuccessCallback :: Maybe NavigatorUserMediaSuccessCallback
- newtype NotificationPermissionCallback permissions = NotificationPermissionCallback (Callback (JSVal -> IO ()))
- newtype NodeFilter = NodeFilter (Callback (JSVal -> IO ()))
- noNodeFilter :: Maybe NodeFilter
- newtype PositionCallback = PositionCallback (Callback (JSVal -> IO ()))
- noPositionCallback :: Maybe PositionCallback
- newtype PositionErrorCallback = PositionErrorCallback (Callback (JSVal -> IO ()))
- noPositionErrorCallback :: Maybe PositionErrorCallback
- newtype PerformanceObserverCallback = PerformanceObserverCallback (Callback (JSVal -> JSVal -> IO ()))
- noPerformanceObserverCallback :: Maybe PerformanceObserverCallback
- newtype RequestAnimationFrameCallback = RequestAnimationFrameCallback (Callback (JSVal -> IO ()))
- noRequestAnimationFrameCallback :: Maybe RequestAnimationFrameCallback
- newtype RTCPeerConnectionErrorCallback = RTCPeerConnectionErrorCallback (Callback (JSVal -> IO ()))
- noRTCPeerConnectionErrorCallback :: Maybe RTCPeerConnectionErrorCallback
- newtype RTCSessionDescriptionCallback = RTCSessionDescriptionCallback (Callback (JSVal -> IO ()))
- noRTCSessionDescriptionCallback :: Maybe RTCSessionDescriptionCallback
- newtype RTCStatsCallback = RTCStatsCallback (Callback (JSVal -> IO ()))
- noRTCStatsCallback :: Maybe RTCStatsCallback
- newtype SQLStatementCallback = SQLStatementCallback (Callback (JSVal -> JSVal -> IO ()))
- noSQLStatementCallback :: Maybe SQLStatementCallback
- newtype SQLStatementErrorCallback = SQLStatementErrorCallback (Callback (JSVal -> JSVal -> IO ()))
- noSQLStatementErrorCallback :: Maybe SQLStatementErrorCallback
- newtype SQLTransactionCallback = SQLTransactionCallback (Callback (JSVal -> IO ()))
- noSQLTransactionCallback :: Maybe SQLTransactionCallback
- newtype SQLTransactionErrorCallback = SQLTransactionErrorCallback (Callback (JSVal -> IO ()))
- noSQLTransactionErrorCallback :: Maybe SQLTransactionErrorCallback
- newtype StorageErrorCallback = StorageErrorCallback (Callback (JSVal -> IO ()))
- noStorageErrorCallback :: Maybe StorageErrorCallback
- newtype StorageQuotaCallback = StorageQuotaCallback (Callback (JSVal -> IO ()))
- noStorageQuotaCallback :: Maybe StorageQuotaCallback
- newtype StorageUsageCallback = StorageUsageCallback (Callback (JSVal -> JSVal -> IO ()))
- noStorageUsageCallback :: Maybe StorageUsageCallback
- newtype StringCallback s = StringCallback (Callback (JSVal -> IO ()))
- newtype VoidCallback = VoidCallback (Callback (IO ()))
- noVoidCallback :: Maybe VoidCallback
- type DOMHighResTimeStamp = Double
- noDOMHighResTimeStamp :: Maybe DOMHighResTimeStamp
- type PerformanceEntryList = [PerformanceEntry]
- noPerformanceEntryList :: Maybe PerformanceEntryList
- newtype Record key value = Record {}
- newtype Dictionary = Dictionary {}
- class IsGObject o => IsDictionary o
- toDictionary :: IsDictionary o => o -> Dictionary
- noDictionary :: Maybe Dictionary
- newtype MutationCallback = MutationCallback {}
- class IsGObject o => IsMutationCallback o
- toMutationCallback :: IsMutationCallback o => o -> MutationCallback
- noMutationCallback :: Maybe MutationCallback
- newtype Date = Date {}
- class IsGObject o => IsDate o
- toDate :: IsDate o => o -> Date
- gTypeDate :: JSM GType
- noDate :: Maybe Date
- newtype Array = Array {}
- class IsGObject o => IsArray o
- toArray :: IsArray o => o -> Array
- gTypeArray :: JSM GType
- noArray :: Maybe Array
- newtype ObjectArray = ObjectArray {}
- class IsGObject o => IsObjectArray o
- toObjectArray :: IsObjectArray o => o -> ObjectArray
- noObjectArray :: Maybe ObjectArray
- newtype ArrayBuffer = ArrayBuffer {}
- class IsGObject o => IsArrayBuffer o
- toArrayBuffer :: IsArrayBuffer o => o -> ArrayBuffer
- gTypeArrayBuffer :: JSM GType
- noArrayBuffer :: Maybe ArrayBuffer
- newtype ArrayBufferView = ArrayBufferView {}
- class IsGObject o => IsArrayBufferView o
- toArrayBufferView :: IsArrayBufferView o => o -> ArrayBufferView
- noArrayBufferView :: Maybe ArrayBufferView
- newtype Float32Array = Float32Array {}
- class IsGObject o => IsFloat32Array o
- toFloat32Array :: IsFloat32Array o => o -> Float32Array
- gTypeFloat32Array :: JSM GType
- noFloat32Array :: Maybe Float32Array
- newtype Float64Array = Float64Array {}
- class IsGObject o => IsFloat64Array o
- toFloat64Array :: IsFloat64Array o => o -> Float64Array
- gTypeFloat64Array :: JSM GType
- noFloat64Array :: Maybe Float64Array
- newtype Uint8Array = Uint8Array {}
- class IsGObject o => IsUint8Array o
- toUint8Array :: IsUint8Array o => o -> Uint8Array
- gTypeUint8Array :: JSM GType
- noUint8Array :: Maybe Uint8Array
- newtype Uint8ClampedArray = Uint8ClampedArray {}
- class IsGObject o => IsUint8ClampedArray o
- toUint8ClampedArray :: IsUint8ClampedArray o => o -> Uint8ClampedArray
- gTypeUint8ClampedArray :: JSM GType
- noUint8ClampedArray :: Maybe Uint8ClampedArray
- newtype Uint16Array = Uint16Array {}
- class IsGObject o => IsUint16Array o
- toUint16Array :: IsUint16Array o => o -> Uint16Array
- gTypeUint16Array :: JSM GType
- noUint16Array :: Maybe Uint16Array
- newtype Uint32Array = Uint32Array {}
- class IsGObject o => IsUint32Array o
- toUint32Array :: IsUint32Array o => o -> Uint32Array
- gTypeUint32Array :: JSM GType
- noUint32Array :: Maybe Uint32Array
- newtype Int8Array = Int8Array {
- unInt8Array :: JSVal
- class IsGObject o => IsInt8Array o
- toInt8Array :: IsInt8Array o => o -> Int8Array
- gTypeInt8Array :: JSM GType
- noInt8Array :: Maybe Int8Array
- newtype Int16Array = Int16Array {}
- class IsGObject o => IsInt16Array o
- toInt16Array :: IsInt16Array o => o -> Int16Array
- gTypeInt16Array :: JSM GType
- noInt16Array :: Maybe Int16Array
- newtype Int32Array = Int32Array {}
- class IsGObject o => IsInt32Array o
- toInt32Array :: IsInt32Array o => o -> Int32Array
- gTypeInt32Array :: JSM GType
- noInt32Array :: Maybe Int32Array
- newtype SerializedScriptValue = SerializedScriptValue {}
- class IsGObject o => IsSerializedScriptValue o
- toSerializedScriptValue :: IsSerializedScriptValue o => o -> SerializedScriptValue
- noSerializedScriptValue :: Maybe SerializedScriptValue
- newtype Algorithm = Algorithm {
- unAlgorithm :: JSVal
- class IsGObject o => IsAlgorithm o
- toAlgorithm :: IsAlgorithm o => o -> Algorithm
- noAlgorithm :: Maybe Algorithm
- newtype CryptoOperationData = CryptoOperationData {}
- class IsGObject o => IsCryptoOperationData o
- toCryptoOperationData :: IsCryptoOperationData o => o -> CryptoOperationData
- noCryptoOperationData :: Maybe CryptoOperationData
- type GLenum = Word32
- type GLboolean = Bool
- type GLbitfield = Word32
- type GLbyte = Int8
- type GLshort = Int16
- type GLint = Int32
- type GLsizei = Int32
- type GLintptr = Int64
- type GLsizeiptr = Int64
- type GLubyte = Word8
- type GLushort = Word16
- type GLuint = Word32
- type GLfloat = Double
- type GLclampf = Double
- type GLint64 = Int64
- type GLuint64 = Word64
- noGLenum :: Maybe GLenum
- noGLboolean :: Maybe GLboolean
- noGLbitfield :: Maybe GLbitfield
- noGLbyte :: Maybe GLbyte
- noGLshort :: Maybe GLshort
- noGLint :: Maybe GLint
- noGLsizei :: Maybe GLsizei
- noGLintptr :: Maybe GLintptr
- noGLsizeiptr :: Maybe GLsizeiptr
- noGLubyte :: Maybe GLubyte
- noGLushort :: Maybe GLushort
- noGLuint :: Maybe GLuint
- noGLfloat :: Maybe GLfloat
- noGLclampf :: Maybe GLclampf
- noGLint64 :: Maybe GLint64
- noGLuint64 :: Maybe GLuint64
- type HasCallStack = ?callStack :: CallStack
- newtype AddEventListenerOptionsOrBool = AddEventListenerOptionsOrBool {}
- class (FromJSVal o, ToJSVal o, PToJSVal o) => IsAddEventListenerOptionsOrBool o
- toAddEventListenerOptionsOrBool :: IsAddEventListenerOptionsOrBool o => o -> AddEventListenerOptionsOrBool
- newtype BinaryData = BinaryData {}
- class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsBinaryData o
- toBinaryData :: IsBinaryData o => o -> BinaryData
- newtype BlobPart = BlobPart {
- unBlobPart :: JSVal
- class (FromJSVal o, ToJSVal o) => IsBlobPart o
- newtype BodyInit = BodyInit {
- unBodyInit :: JSVal
- class (FromJSVal o, ToJSVal o) => IsBodyInit o
- newtype BufferDataSource = BufferDataSource {}
- class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsBufferDataSource o
- toBufferDataSource :: IsBufferDataSource o => o -> BufferDataSource
- newtype BufferSource = BufferSource {}
- class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsBufferSource o
- toBufferSource :: IsBufferSource o => o -> BufferSource
- newtype CanvasImageSource = CanvasImageSource {}
- class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsCanvasImageSource o
- toCanvasImageSource :: IsCanvasImageSource o => o -> CanvasImageSource
- newtype CanvasStyle = CanvasStyle {}
- class (FromJSVal o, ToJSVal o) => IsCanvasStyle o
- newtype CredentialBodyType = CredentialBodyType {}
- class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsCredentialBodyType o
- toCredentialBodyType :: IsCredentialBodyType o => o -> CredentialBodyType
- newtype CryptoKeyOrKeyPair = CryptoKeyOrKeyPair {}
- class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsCryptoKeyOrKeyPair o
- toCryptoKeyOrKeyPair :: IsCryptoKeyOrKeyPair o => o -> CryptoKeyOrKeyPair
- newtype EventListenerOptionsOrBool = EventListenerOptionsOrBool {}
- class (FromJSVal o, ToJSVal o, PToJSVal o) => IsEventListenerOptionsOrBool o
- toEventListenerOptionsOrBool :: IsEventListenerOptionsOrBool o => o -> EventListenerOptionsOrBool
- newtype Float32List = Float32List {}
- class (FromJSVal o, ToJSVal o) => IsFloat32List o
- newtype HTMLCollectionOrElement = HTMLCollectionOrElement {}
- class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsHTMLCollectionOrElement o
- toHTMLCollectionOrElement :: IsHTMLCollectionOrElement o => o -> HTMLCollectionOrElement
- newtype HTMLElementOrLong = HTMLElementOrLong {}
- class (FromJSVal o, ToJSVal o) => IsHTMLElementOrLong o
- newtype HTMLOptionElementOrGroup = HTMLOptionElementOrGroup {}
- class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsHTMLOptionElementOrGroup o
- toHTMLOptionElementOrGroup :: IsHTMLOptionElementOrGroup o => o -> HTMLOptionElementOrGroup
- newtype IDBCursorSource = IDBCursorSource {}
- class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsIDBCursorSource o
- toIDBCursorSource :: IsIDBCursorSource o => o -> IDBCursorSource
- newtype IDBKeyPath = IDBKeyPath {}
- class (FromJSVal o, ToJSVal o) => IsIDBKeyPath o
- newtype IDBRequestResult = IDBRequestResult {}
- class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsIDBRequestResult o
- toIDBRequestResult :: IsIDBRequestResult o => o -> IDBRequestResult
- newtype IDBRequestSource = IDBRequestSource {}
- class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsIDBRequestSource o
- toIDBRequestSource :: IsIDBRequestSource o => o -> IDBRequestSource
- newtype Int32List = Int32List {
- unInt32List :: JSVal
- class (FromJSVal o, ToJSVal o) => IsInt32List o
- newtype KeyData = KeyData {}
- class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsKeyData o
- toKeyData :: IsKeyData o => o -> KeyData
- newtype MediaProvider = MediaProvider {}
- class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsMediaProvider o
- toMediaProvider :: IsMediaProvider o => o -> MediaProvider
- newtype MediaStreamTrackOrKind = MediaStreamTrackOrKind {}
- class (FromJSVal o, ToJSVal o) => IsMediaStreamTrackOrKind o
- newtype MessageEventSource = MessageEventSource {}
- class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsMessageEventSource o
- toMessageEventSource :: IsMessageEventSource o => o -> MessageEventSource
- newtype NodeOrString = NodeOrString {}
- class (FromJSVal o, ToJSVal o) => IsNodeOrString o
- newtype RTCIceCandidateOrInit = RTCIceCandidateOrInit {}
- class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsRTCIceCandidateOrInit o
- toRTCIceCandidateOrInit :: IsRTCIceCandidateOrInit o => o -> RTCIceCandidateOrInit
- newtype RadioNodeListOrElement = RadioNodeListOrElement {}
- class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsRadioNodeListOrElement o
- toRadioNodeListOrElement :: IsRadioNodeListOrElement o => o -> RadioNodeListOrElement
- newtype RenderingContext = RenderingContext {}
- class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsRenderingContext o
- toRenderingContext :: IsRenderingContext o => o -> RenderingContext
- newtype SQLValue = SQLValue {
- unSQLValue :: JSVal
- class (FromJSVal o, ToJSVal o) => IsSQLValue o
- newtype StringOrArrayBuffer = StringOrArrayBuffer {}
- class (FromJSVal o, ToJSVal o) => IsStringOrArrayBuffer o
- newtype StringOrBinaryData = StringOrBinaryData {}
- class (FromJSVal o, ToJSVal o) => IsStringOrBinaryData o
- newtype StringOrStrings = StringOrStrings {}
- class (FromJSVal o, ToJSVal o) => IsStringOrStrings o
- newtype TexImageSource = TexImageSource {}
- class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsTexImageSource o
- toTexImageSource :: IsTexImageSource o => o -> TexImageSource
- newtype Track = Track {}
- class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsTrack o
- toTrack :: IsTrack o => o -> Track
- newtype URLSearchParamsInit = URLSearchParamsInit {}
- class (FromJSVal o, ToJSVal o) => IsURLSearchParamsInit o
- newtype XMLHttpRequestBody = XMLHttpRequestBody {}
- class (FromJSVal o, ToJSVal o) => IsXMLHttpRequestBody o
- newtype ANGLEInstancedArrays = ANGLEInstancedArrays {}
- noANGLEInstancedArrays :: Maybe ANGLEInstancedArrays
- gTypeANGLEInstancedArrays :: JSM GType
- newtype AbstractWorker = AbstractWorker {}
- class IsGObject o => IsAbstractWorker o
- toAbstractWorker :: IsAbstractWorker o => o -> AbstractWorker
- noAbstractWorker :: Maybe AbstractWorker
- gTypeAbstractWorker :: JSM GType
- newtype Acceleration = Acceleration {}
- noAcceleration :: Maybe Acceleration
- gTypeAcceleration :: JSM GType
- newtype AddEventListenerOptions = AddEventListenerOptions {}
- noAddEventListenerOptions :: Maybe AddEventListenerOptions
- gTypeAddEventListenerOptions :: JSM GType
- newtype AesCbcCfbParams = AesCbcCfbParams {}
- noAesCbcCfbParams :: Maybe AesCbcCfbParams
- gTypeAesCbcCfbParams :: JSM GType
- newtype AesCtrParams = AesCtrParams {}
- noAesCtrParams :: Maybe AesCtrParams
- gTypeAesCtrParams :: JSM GType
- newtype AesGcmParams = AesGcmParams {}
- noAesGcmParams :: Maybe AesGcmParams
- gTypeAesGcmParams :: JSM GType
- newtype AesKeyParams = AesKeyParams {}
- noAesKeyParams :: Maybe AesKeyParams
- gTypeAesKeyParams :: JSM GType
- newtype AnalyserNode = AnalyserNode {}
- noAnalyserNode :: Maybe AnalyserNode
- gTypeAnalyserNode :: JSM GType
- newtype Animatable = Animatable {}
- class IsGObject o => IsAnimatable o
- toAnimatable :: IsAnimatable o => o -> Animatable
- noAnimatable :: Maybe Animatable
- gTypeAnimatable :: JSM GType
- newtype Animation = Animation {
- unAnimation :: JSVal
- noAnimation :: Maybe Animation
- gTypeAnimation :: JSM GType
- newtype AnimationEffect = AnimationEffect {}
- class IsGObject o => IsAnimationEffect o
- toAnimationEffect :: IsAnimationEffect o => o -> AnimationEffect
- noAnimationEffect :: Maybe AnimationEffect
- gTypeAnimationEffect :: JSM GType
- newtype AnimationEvent = AnimationEvent {}
- noAnimationEvent :: Maybe AnimationEvent
- gTypeAnimationEvent :: JSM GType
- newtype AnimationEventInit = AnimationEventInit {}
- noAnimationEventInit :: Maybe AnimationEventInit
- gTypeAnimationEventInit :: JSM GType
- newtype AnimationTimeline = AnimationTimeline {}
- class IsGObject o => IsAnimationTimeline o
- toAnimationTimeline :: IsAnimationTimeline o => o -> AnimationTimeline
- noAnimationTimeline :: Maybe AnimationTimeline
- gTypeAnimationTimeline :: JSM GType
- newtype ApplePayError = ApplePayError {}
- noApplePayError :: Maybe ApplePayError
- gTypeApplePayError :: JSM GType
- newtype ApplePayLineItem = ApplePayLineItem {}
- noApplePayLineItem :: Maybe ApplePayLineItem
- gTypeApplePayLineItem :: JSM GType
- newtype ApplePayPayment = ApplePayPayment {}
- noApplePayPayment :: Maybe ApplePayPayment
- gTypeApplePayPayment :: JSM GType
- newtype ApplePayPaymentAuthorizationResult = ApplePayPaymentAuthorizationResult {}
- noApplePayPaymentAuthorizationResult :: Maybe ApplePayPaymentAuthorizationResult
- gTypeApplePayPaymentAuthorizationResult :: JSM GType
- newtype ApplePayPaymentAuthorizedEvent = ApplePayPaymentAuthorizedEvent {}
- noApplePayPaymentAuthorizedEvent :: Maybe ApplePayPaymentAuthorizedEvent
- gTypeApplePayPaymentAuthorizedEvent :: JSM GType
- newtype ApplePayPaymentContact = ApplePayPaymentContact {}
- noApplePayPaymentContact :: Maybe ApplePayPaymentContact
- gTypeApplePayPaymentContact :: JSM GType
- newtype ApplePayPaymentMethod = ApplePayPaymentMethod {}
- noApplePayPaymentMethod :: Maybe ApplePayPaymentMethod
- gTypeApplePayPaymentMethod :: JSM GType
- newtype ApplePayPaymentMethodSelectedEvent = ApplePayPaymentMethodSelectedEvent {}
- noApplePayPaymentMethodSelectedEvent :: Maybe ApplePayPaymentMethodSelectedEvent
- gTypeApplePayPaymentMethodSelectedEvent :: JSM GType
- newtype ApplePayPaymentMethodUpdate = ApplePayPaymentMethodUpdate {}
- noApplePayPaymentMethodUpdate :: Maybe ApplePayPaymentMethodUpdate
- gTypeApplePayPaymentMethodUpdate :: JSM GType
- newtype ApplePayPaymentPass = ApplePayPaymentPass {}
- noApplePayPaymentPass :: Maybe ApplePayPaymentPass
- gTypeApplePayPaymentPass :: JSM GType
- newtype ApplePayPaymentRequest = ApplePayPaymentRequest {}
- noApplePayPaymentRequest :: Maybe ApplePayPaymentRequest
- gTypeApplePayPaymentRequest :: JSM GType
- newtype ApplePayPaymentToken = ApplePayPaymentToken {}
- noApplePayPaymentToken :: Maybe ApplePayPaymentToken
- gTypeApplePayPaymentToken :: JSM GType
- newtype ApplePaySession = ApplePaySession {}
- noApplePaySession :: Maybe ApplePaySession
- gTypeApplePaySession :: JSM GType
- newtype ApplePayShippingContactSelectedEvent = ApplePayShippingContactSelectedEvent {}
- noApplePayShippingContactSelectedEvent :: Maybe ApplePayShippingContactSelectedEvent
- gTypeApplePayShippingContactSelectedEvent :: JSM GType
- newtype ApplePayShippingContactUpdate = ApplePayShippingContactUpdate {}
- noApplePayShippingContactUpdate :: Maybe ApplePayShippingContactUpdate
- gTypeApplePayShippingContactUpdate :: JSM GType
- newtype ApplePayShippingMethod = ApplePayShippingMethod {}
- noApplePayShippingMethod :: Maybe ApplePayShippingMethod
- gTypeApplePayShippingMethod :: JSM GType
- newtype ApplePayShippingMethodSelectedEvent = ApplePayShippingMethodSelectedEvent {}
- noApplePayShippingMethodSelectedEvent :: Maybe ApplePayShippingMethodSelectedEvent
- gTypeApplePayShippingMethodSelectedEvent :: JSM GType
- newtype ApplePayShippingMethodUpdate = ApplePayShippingMethodUpdate {}
- noApplePayShippingMethodUpdate :: Maybe ApplePayShippingMethodUpdate
- gTypeApplePayShippingMethodUpdate :: JSM GType
- newtype ApplePayValidateMerchantEvent = ApplePayValidateMerchantEvent {}
- noApplePayValidateMerchantEvent :: Maybe ApplePayValidateMerchantEvent
- gTypeApplePayValidateMerchantEvent :: JSM GType
- newtype ApplicationCache = ApplicationCache {}
- noApplicationCache :: Maybe ApplicationCache
- gTypeApplicationCache :: JSM GType
- newtype AssignedNodesOptions = AssignedNodesOptions {}
- noAssignedNodesOptions :: Maybe AssignedNodesOptions
- gTypeAssignedNodesOptions :: JSM GType
- newtype Attr = Attr {}
- noAttr :: Maybe Attr
- gTypeAttr :: JSM GType
- newtype AudioBuffer = AudioBuffer {}
- noAudioBuffer :: Maybe AudioBuffer
- gTypeAudioBuffer :: JSM GType
- newtype AudioBufferSourceNode = AudioBufferSourceNode {}
- noAudioBufferSourceNode :: Maybe AudioBufferSourceNode
- gTypeAudioBufferSourceNode :: JSM GType
- newtype AudioContext = AudioContext {}
- class (IsEventTarget o, IsGObject o) => IsAudioContext o
- toAudioContext :: IsAudioContext o => o -> AudioContext
- noAudioContext :: Maybe AudioContext
- gTypeAudioContext :: JSM GType
- newtype AudioDestinationNode = AudioDestinationNode {}
- noAudioDestinationNode :: Maybe AudioDestinationNode
- gTypeAudioDestinationNode :: JSM GType
- newtype AudioListener = AudioListener {}
- noAudioListener :: Maybe AudioListener
- gTypeAudioListener :: JSM GType
- newtype AudioNode = AudioNode {
- unAudioNode :: JSVal
- class (IsEventTarget o, IsGObject o) => IsAudioNode o
- toAudioNode :: IsAudioNode o => o -> AudioNode
- noAudioNode :: Maybe AudioNode
- gTypeAudioNode :: JSM GType
- newtype AudioParam = AudioParam {}
- noAudioParam :: Maybe AudioParam
- gTypeAudioParam :: JSM GType
- newtype AudioProcessingEvent = AudioProcessingEvent {}
- noAudioProcessingEvent :: Maybe AudioProcessingEvent
- gTypeAudioProcessingEvent :: JSM GType
- newtype AudioTrack = AudioTrack {}
- noAudioTrack :: Maybe AudioTrack
- gTypeAudioTrack :: JSM GType
- newtype AudioTrackList = AudioTrackList {}
- noAudioTrackList :: Maybe AudioTrackList
- gTypeAudioTrackList :: JSM GType
- newtype AutocompleteErrorEvent = AutocompleteErrorEvent {}
- noAutocompleteErrorEvent :: Maybe AutocompleteErrorEvent
- gTypeAutocompleteErrorEvent :: JSM GType
- newtype AutocompleteErrorEventInit = AutocompleteErrorEventInit {}
- noAutocompleteErrorEventInit :: Maybe AutocompleteErrorEventInit
- gTypeAutocompleteErrorEventInit :: JSM GType
- newtype BarProp = BarProp {}
- noBarProp :: Maybe BarProp
- gTypeBarProp :: JSM GType
- newtype BasicCredential = BasicCredential {}
- class IsGObject o => IsBasicCredential o
- toBasicCredential :: IsBasicCredential o => o -> BasicCredential
- noBasicCredential :: Maybe BasicCredential
- gTypeBasicCredential :: JSM GType
- newtype BeforeLoadEvent = BeforeLoadEvent {}
- noBeforeLoadEvent :: Maybe BeforeLoadEvent
- gTypeBeforeLoadEvent :: JSM GType
- newtype BeforeLoadEventInit = BeforeLoadEventInit {}
- noBeforeLoadEventInit :: Maybe BeforeLoadEventInit
- gTypeBeforeLoadEventInit :: JSM GType
- newtype BeforeUnloadEvent = BeforeUnloadEvent {}
- noBeforeUnloadEvent :: Maybe BeforeUnloadEvent
- gTypeBeforeUnloadEvent :: JSM GType
- newtype BiquadFilterNode = BiquadFilterNode {}
- noBiquadFilterNode :: Maybe BiquadFilterNode
- gTypeBiquadFilterNode :: JSM GType
- newtype Blob = Blob {}
- class IsGObject o => IsBlob o
- toBlob :: IsBlob o => o -> Blob
- noBlob :: Maybe Blob
- gTypeBlob :: JSM GType
- newtype BlobPropertyBag = BlobPropertyBag {}
- class IsGObject o => IsBlobPropertyBag o
- toBlobPropertyBag :: IsBlobPropertyBag o => o -> BlobPropertyBag
- noBlobPropertyBag :: Maybe BlobPropertyBag
- gTypeBlobPropertyBag :: JSM GType
- newtype Body = Body {}
- class IsGObject o => IsBody o
- toBody :: IsBody o => o -> Body
- noBody :: Maybe Body
- gTypeBody :: JSM GType
- newtype ByteLengthQueuingStrategy = ByteLengthQueuingStrategy {}
- noByteLengthQueuingStrategy :: Maybe ByteLengthQueuingStrategy
- gTypeByteLengthQueuingStrategy :: JSM GType
- newtype CDATASection = CDATASection {}
- noCDATASection :: Maybe CDATASection
- gTypeCDATASection :: JSM GType
- newtype CSS = CSS {}
- noCSS :: Maybe CSS
- gTypeCSS :: JSM GType
- newtype CSSFontFaceLoadEvent = CSSFontFaceLoadEvent {}
- noCSSFontFaceLoadEvent :: Maybe CSSFontFaceLoadEvent
- gTypeCSSFontFaceLoadEvent :: JSM GType
- newtype CSSFontFaceLoadEventInit = CSSFontFaceLoadEventInit {}
- noCSSFontFaceLoadEventInit :: Maybe CSSFontFaceLoadEventInit
- gTypeCSSFontFaceLoadEventInit :: JSM GType
- newtype CSSFontFaceRule = CSSFontFaceRule {}
- noCSSFontFaceRule :: Maybe CSSFontFaceRule
- gTypeCSSFontFaceRule :: JSM GType
- newtype CSSImportRule = CSSImportRule {}
- noCSSImportRule :: Maybe CSSImportRule
- gTypeCSSImportRule :: JSM GType
- newtype CSSKeyframeRule = CSSKeyframeRule {}
- noCSSKeyframeRule :: Maybe CSSKeyframeRule
- gTypeCSSKeyframeRule :: JSM GType
- newtype CSSKeyframesRule = CSSKeyframesRule {}
- noCSSKeyframesRule :: Maybe CSSKeyframesRule
- gTypeCSSKeyframesRule :: JSM GType
- newtype CSSMediaRule = CSSMediaRule {}
- noCSSMediaRule :: Maybe CSSMediaRule
- gTypeCSSMediaRule :: JSM GType
- newtype CSSNamespaceRule = CSSNamespaceRule {}
- noCSSNamespaceRule :: Maybe CSSNamespaceRule
- gTypeCSSNamespaceRule :: JSM GType
- newtype CSSPageRule = CSSPageRule {}
- noCSSPageRule :: Maybe CSSPageRule
- gTypeCSSPageRule :: JSM GType
- newtype CSSPrimitiveValue = CSSPrimitiveValue {}
- noCSSPrimitiveValue :: Maybe CSSPrimitiveValue
- gTypeCSSPrimitiveValue :: JSM GType
- newtype CSSRule = CSSRule {}
- class IsGObject o => IsCSSRule o
- toCSSRule :: IsCSSRule o => o -> CSSRule
- noCSSRule :: Maybe CSSRule
- gTypeCSSRule :: JSM GType
- newtype CSSRuleList = CSSRuleList {}
- noCSSRuleList :: Maybe CSSRuleList
- gTypeCSSRuleList :: JSM GType
- newtype CSSStyleDeclaration = CSSStyleDeclaration {}
- noCSSStyleDeclaration :: Maybe CSSStyleDeclaration
- gTypeCSSStyleDeclaration :: JSM GType
- newtype CSSStyleRule = CSSStyleRule {}
- noCSSStyleRule :: Maybe CSSStyleRule
- gTypeCSSStyleRule :: JSM GType
- newtype CSSStyleSheet = CSSStyleSheet {}
- noCSSStyleSheet :: Maybe CSSStyleSheet
- gTypeCSSStyleSheet :: JSM GType
- newtype CSSSupportsRule = CSSSupportsRule {}
- noCSSSupportsRule :: Maybe CSSSupportsRule
- gTypeCSSSupportsRule :: JSM GType
- newtype CSSUnknownRule = CSSUnknownRule {}
- noCSSUnknownRule :: Maybe CSSUnknownRule
- gTypeCSSUnknownRule :: JSM GType
- newtype CSSValue = CSSValue {
- unCSSValue :: JSVal
- class IsGObject o => IsCSSValue o
- toCSSValue :: IsCSSValue o => o -> CSSValue
- noCSSValue :: Maybe CSSValue
- gTypeCSSValue :: JSM GType
- newtype CSSValueList = CSSValueList {}
- noCSSValueList :: Maybe CSSValueList
- gTypeCSSValueList :: JSM GType
- newtype CanvasCaptureMediaStreamTrack = CanvasCaptureMediaStreamTrack {}
- noCanvasCaptureMediaStreamTrack :: Maybe CanvasCaptureMediaStreamTrack
- gTypeCanvasCaptureMediaStreamTrack :: JSM GType
- newtype CanvasGradient = CanvasGradient {}
- noCanvasGradient :: Maybe CanvasGradient
- gTypeCanvasGradient :: JSM GType
- newtype CanvasPath = CanvasPath {}
- class IsGObject o => IsCanvasPath o
- toCanvasPath :: IsCanvasPath o => o -> CanvasPath
- noCanvasPath :: Maybe CanvasPath
- gTypeCanvasPath :: JSM GType
- newtype CanvasPattern = CanvasPattern {}
- noCanvasPattern :: Maybe CanvasPattern
- gTypeCanvasPattern :: JSM GType
- newtype CanvasProxy = CanvasProxy {}
- noCanvasProxy :: Maybe CanvasProxy
- gTypeCanvasProxy :: JSM GType
- newtype CanvasRenderingContext2D = CanvasRenderingContext2D {}
- noCanvasRenderingContext2D :: Maybe CanvasRenderingContext2D
- gTypeCanvasRenderingContext2D :: JSM GType
- newtype ChannelMergerNode = ChannelMergerNode {}
- noChannelMergerNode :: Maybe ChannelMergerNode
- gTypeChannelMergerNode :: JSM GType
- newtype ChannelSplitterNode = ChannelSplitterNode {}
- noChannelSplitterNode :: Maybe ChannelSplitterNode
- gTypeChannelSplitterNode :: JSM GType
- newtype CharacterData = CharacterData {}
- class (IsNode o, IsEventTarget o, IsNonDocumentTypeChildNode o, IsChildNode o, IsGObject o) => IsCharacterData o
- toCharacterData :: IsCharacterData o => o -> CharacterData
- noCharacterData :: Maybe CharacterData
- gTypeCharacterData :: JSM GType
- newtype ChildNode = ChildNode {
- unChildNode :: JSVal
- class IsGObject o => IsChildNode o
- toChildNode :: IsChildNode o => o -> ChildNode
- noChildNode :: Maybe ChildNode
- gTypeChildNode :: JSM GType
- newtype ClipboardEvent = ClipboardEvent {}
- noClipboardEvent :: Maybe ClipboardEvent
- gTypeClipboardEvent :: JSM GType
- newtype ClipboardEventInit = ClipboardEventInit {}
- noClipboardEventInit :: Maybe ClipboardEventInit
- gTypeClipboardEventInit :: JSM GType
- newtype CloseEvent = CloseEvent {}
- noCloseEvent :: Maybe CloseEvent
- gTypeCloseEvent :: JSM GType
- newtype CloseEventInit = CloseEventInit {}
- noCloseEventInit :: Maybe CloseEventInit
- gTypeCloseEventInit :: JSM GType
- newtype CommandLineAPIHost = CommandLineAPIHost {}
- noCommandLineAPIHost :: Maybe CommandLineAPIHost
- gTypeCommandLineAPIHost :: JSM GType
- newtype Comment = Comment {}
- noComment :: Maybe Comment
- gTypeComment :: JSM GType
- newtype CompositionEvent = CompositionEvent {}
- noCompositionEvent :: Maybe CompositionEvent
- gTypeCompositionEvent :: JSM GType
- newtype CompositionEventInit = CompositionEventInit {}
- noCompositionEventInit :: Maybe CompositionEventInit
- gTypeCompositionEventInit :: JSM GType
- newtype ConstrainBooleanParameters = ConstrainBooleanParameters {}
- noConstrainBooleanParameters :: Maybe ConstrainBooleanParameters
- gTypeConstrainBooleanParameters :: JSM GType
- newtype ConstrainDOMStringParameters = ConstrainDOMStringParameters {}
- noConstrainDOMStringParameters :: Maybe ConstrainDOMStringParameters
- gTypeConstrainDOMStringParameters :: JSM GType
- newtype ConstrainDoubleRange = ConstrainDoubleRange {}
- noConstrainDoubleRange :: Maybe ConstrainDoubleRange
- gTypeConstrainDoubleRange :: JSM GType
- newtype ConstrainLongRange = ConstrainLongRange {}
- noConstrainLongRange :: Maybe ConstrainLongRange
- gTypeConstrainLongRange :: JSM GType
- newtype ConvolverNode = ConvolverNode {}
- noConvolverNode :: Maybe ConvolverNode
- gTypeConvolverNode :: JSM GType
- newtype Coordinates = Coordinates {}
- noCoordinates :: Maybe Coordinates
- gTypeCoordinates :: JSM GType
- newtype CountQueuingStrategy = CountQueuingStrategy {}
- noCountQueuingStrategy :: Maybe CountQueuingStrategy
- gTypeCountQueuingStrategy :: JSM GType
- newtype Counter = Counter {}
- noCounter :: Maybe Counter
- gTypeCounter :: JSM GType
- newtype CredentialData = CredentialData {}
- class IsGObject o => IsCredentialData o
- toCredentialData :: IsCredentialData o => o -> CredentialData
- noCredentialData :: Maybe CredentialData
- gTypeCredentialData :: JSM GType
- newtype Crypto = Crypto {}
- noCrypto :: Maybe Crypto
- gTypeCrypto :: JSM GType
- newtype CryptoAlgorithmParameters = CryptoAlgorithmParameters {}
- class IsGObject o => IsCryptoAlgorithmParameters o
- toCryptoAlgorithmParameters :: IsCryptoAlgorithmParameters o => o -> CryptoAlgorithmParameters
- noCryptoAlgorithmParameters :: Maybe CryptoAlgorithmParameters
- gTypeCryptoAlgorithmParameters :: JSM GType
- newtype CryptoKey = CryptoKey {
- unCryptoKey :: JSVal
- noCryptoKey :: Maybe CryptoKey
- gTypeCryptoKey :: JSM GType
- newtype CryptoKeyPair = CryptoKeyPair {}
- noCryptoKeyPair :: Maybe CryptoKeyPair
- gTypeCryptoKeyPair :: JSM GType
- newtype CustomElementRegistry = CustomElementRegistry {}
- noCustomElementRegistry :: Maybe CustomElementRegistry
- gTypeCustomElementRegistry :: JSM GType
- newtype CustomEvent = CustomEvent {}
- noCustomEvent :: Maybe CustomEvent
- gTypeCustomEvent :: JSM GType
- newtype CustomEventInit = CustomEventInit {}
- noCustomEventInit :: Maybe CustomEventInit
- gTypeCustomEventInit :: JSM GType
- newtype DOMError = DOMError {
- unDOMError :: JSVal
- class IsGObject o => IsDOMError o
- toDOMError :: IsDOMError o => o -> DOMError
- noDOMError :: Maybe DOMError
- gTypeDOMError :: JSM GType
- newtype DOMException = DOMException {}
- noDOMException :: Maybe DOMException
- gTypeDOMException :: JSM GType
- newtype DOMImplementation = DOMImplementation {}
- noDOMImplementation :: Maybe DOMImplementation
- gTypeDOMImplementation :: JSM GType
- newtype DOMNamedFlowCollection = DOMNamedFlowCollection {}
- noDOMNamedFlowCollection :: Maybe DOMNamedFlowCollection
- gTypeDOMNamedFlowCollection :: JSM GType
- newtype DOMParser = DOMParser {
- unDOMParser :: JSVal
- noDOMParser :: Maybe DOMParser
- gTypeDOMParser :: JSM GType
- newtype DOMPoint = DOMPoint {
- unDOMPoint :: JSVal
- noDOMPoint :: Maybe DOMPoint
- gTypeDOMPoint :: JSM GType
- newtype DOMPointInit = DOMPointInit {}
- noDOMPointInit :: Maybe DOMPointInit
- gTypeDOMPointInit :: JSM GType
- newtype DOMPointReadOnly = DOMPointReadOnly {}
- class IsGObject o => IsDOMPointReadOnly o
- toDOMPointReadOnly :: IsDOMPointReadOnly o => o -> DOMPointReadOnly
- noDOMPointReadOnly :: Maybe DOMPointReadOnly
- gTypeDOMPointReadOnly :: JSM GType
- newtype DOMRect = DOMRect {}
- noDOMRect :: Maybe DOMRect
- gTypeDOMRect :: JSM GType
- newtype DOMRectInit = DOMRectInit {}
- noDOMRectInit :: Maybe DOMRectInit
- gTypeDOMRectInit :: JSM GType
- newtype DOMRectReadOnly = DOMRectReadOnly {}
- class IsGObject o => IsDOMRectReadOnly o
- toDOMRectReadOnly :: IsDOMRectReadOnly o => o -> DOMRectReadOnly
- noDOMRectReadOnly :: Maybe DOMRectReadOnly
- gTypeDOMRectReadOnly :: JSM GType
- newtype DOMStringList = DOMStringList {}
- noDOMStringList :: Maybe DOMStringList
- gTypeDOMStringList :: JSM GType
- newtype DOMStringMap = DOMStringMap {}
- noDOMStringMap :: Maybe DOMStringMap
- gTypeDOMStringMap :: JSM GType
- newtype DOMTokenList = DOMTokenList {}
- noDOMTokenList :: Maybe DOMTokenList
- gTypeDOMTokenList :: JSM GType
- newtype DataCue = DataCue {}
- noDataCue :: Maybe DataCue
- gTypeDataCue :: JSM GType
- newtype DataTransfer = DataTransfer {}
- noDataTransfer :: Maybe DataTransfer
- gTypeDataTransfer :: JSM GType
- newtype DataTransferItem = DataTransferItem {}
- noDataTransferItem :: Maybe DataTransferItem
- gTypeDataTransferItem :: JSM GType
- newtype DataTransferItemList = DataTransferItemList {}
- noDataTransferItemList :: Maybe DataTransferItemList
- gTypeDataTransferItemList :: JSM GType
- newtype Database = Database {
- unDatabase :: JSVal
- noDatabase :: Maybe Database
- gTypeDatabase :: JSM GType
- newtype DedicatedWorkerGlobalScope = DedicatedWorkerGlobalScope {}
- noDedicatedWorkerGlobalScope :: Maybe DedicatedWorkerGlobalScope
- gTypeDedicatedWorkerGlobalScope :: JSM GType
- newtype DelayNode = DelayNode {
- unDelayNode :: JSVal
- noDelayNode :: Maybe DelayNode
- gTypeDelayNode :: JSM GType
- newtype DeviceMotionEvent = DeviceMotionEvent {}
- noDeviceMotionEvent :: Maybe DeviceMotionEvent
- gTypeDeviceMotionEvent :: JSM GType
- newtype DeviceOrientationEvent = DeviceOrientationEvent {}
- noDeviceOrientationEvent :: Maybe DeviceOrientationEvent
- gTypeDeviceOrientationEvent :: JSM GType
- newtype DeviceProximityEvent = DeviceProximityEvent {}
- noDeviceProximityEvent :: Maybe DeviceProximityEvent
- gTypeDeviceProximityEvent :: JSM GType
- newtype DeviceProximityEventInit = DeviceProximityEventInit {}
- noDeviceProximityEventInit :: Maybe DeviceProximityEventInit
- gTypeDeviceProximityEventInit :: JSM GType
- newtype Document = Document {
- unDocument :: JSVal
- class (IsNode o, IsEventTarget o, IsGlobalEventHandlers o, IsDocumentOrShadowRoot o, IsNonElementParentNode o, IsParentNode o, IsDocumentAndElementEventHandlers o, IsGObject o) => IsDocument o
- toDocument :: IsDocument o => o -> Document
- noDocument :: Maybe Document
- gTypeDocument :: JSM GType
- newtype DocumentAndElementEventHandlers = DocumentAndElementEventHandlers {}
- class IsGObject o => IsDocumentAndElementEventHandlers o
- toDocumentAndElementEventHandlers :: IsDocumentAndElementEventHandlers o => o -> DocumentAndElementEventHandlers
- noDocumentAndElementEventHandlers :: Maybe DocumentAndElementEventHandlers
- gTypeDocumentAndElementEventHandlers :: JSM GType
- newtype DocumentFragment = DocumentFragment {}
- class (IsNode o, IsEventTarget o, IsNonElementParentNode o, IsParentNode o, IsGObject o) => IsDocumentFragment o
- toDocumentFragment :: IsDocumentFragment o => o -> DocumentFragment
- noDocumentFragment :: Maybe DocumentFragment
- gTypeDocumentFragment :: JSM GType
- newtype DocumentOrShadowRoot = DocumentOrShadowRoot {}
- class IsGObject o => IsDocumentOrShadowRoot o
- toDocumentOrShadowRoot :: IsDocumentOrShadowRoot o => o -> DocumentOrShadowRoot
- noDocumentOrShadowRoot :: Maybe DocumentOrShadowRoot
- gTypeDocumentOrShadowRoot :: JSM GType
- newtype DocumentTimeline = DocumentTimeline {}
- noDocumentTimeline :: Maybe DocumentTimeline
- gTypeDocumentTimeline :: JSM GType
- newtype DocumentType = DocumentType {}
- noDocumentType :: Maybe DocumentType
- gTypeDocumentType :: JSM GType
- newtype DoubleRange = DoubleRange {}
- class IsGObject o => IsDoubleRange o
- toDoubleRange :: IsDoubleRange o => o -> DoubleRange
- noDoubleRange :: Maybe DoubleRange
- gTypeDoubleRange :: JSM GType
- newtype DynamicsCompressorNode = DynamicsCompressorNode {}
- noDynamicsCompressorNode :: Maybe DynamicsCompressorNode
- gTypeDynamicsCompressorNode :: JSM GType
- newtype EXTBlendMinMax = EXTBlendMinMax {}
- noEXTBlendMinMax :: Maybe EXTBlendMinMax
- gTypeEXTBlendMinMax :: JSM GType
- newtype EXTFragDepth = EXTFragDepth {}
- noEXTFragDepth :: Maybe EXTFragDepth
- gTypeEXTFragDepth :: JSM GType
- newtype EXTShaderTextureLOD = EXTShaderTextureLOD {}
- noEXTShaderTextureLOD :: Maybe EXTShaderTextureLOD
- gTypeEXTShaderTextureLOD :: JSM GType
- newtype EXTTextureFilterAnisotropic = EXTTextureFilterAnisotropic {}
- noEXTTextureFilterAnisotropic :: Maybe EXTTextureFilterAnisotropic
- gTypeEXTTextureFilterAnisotropic :: JSM GType
- newtype EXTsRGB = EXTsRGB {}
- noEXTsRGB :: Maybe EXTsRGB
- gTypeEXTsRGB :: JSM GType
- newtype EcKeyParams = EcKeyParams {}
- noEcKeyParams :: Maybe EcKeyParams
- gTypeEcKeyParams :: JSM GType
- newtype EcdhKeyDeriveParams = EcdhKeyDeriveParams {}
- noEcdhKeyDeriveParams :: Maybe EcdhKeyDeriveParams
- gTypeEcdhKeyDeriveParams :: JSM GType
- newtype EcdsaParams = EcdsaParams {}
- noEcdsaParams :: Maybe EcdsaParams
- gTypeEcdsaParams :: JSM GType
- newtype Element = Element {}
- 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
- noElement :: Maybe Element
- gTypeElement :: JSM GType
- newtype ElementCSSInlineStyle = ElementCSSInlineStyle {}
- class IsGObject o => IsElementCSSInlineStyle o
- toElementCSSInlineStyle :: IsElementCSSInlineStyle o => o -> ElementCSSInlineStyle
- noElementCSSInlineStyle :: Maybe ElementCSSInlineStyle
- gTypeElementCSSInlineStyle :: JSM GType
- newtype ErrorEvent = ErrorEvent {}
- noErrorEvent :: Maybe ErrorEvent
- gTypeErrorEvent :: JSM GType
- newtype ErrorEventInit = ErrorEventInit {}
- noErrorEventInit :: Maybe ErrorEventInit
- gTypeErrorEventInit :: JSM GType
- newtype Event = Event {}
- class IsGObject o => IsEvent o
- toEvent :: IsEvent o => o -> Event
- noEvent :: Maybe Event
- gTypeEvent :: JSM GType
- newtype EventInit = EventInit {
- unEventInit :: JSVal
- class IsGObject o => IsEventInit o
- toEventInit :: IsEventInit o => o -> EventInit
- noEventInit :: Maybe EventInit
- gTypeEventInit :: JSM GType
- newtype EventListener = EventListener {}
- noEventListener :: Maybe EventListener
- gTypeEventListener :: JSM GType
- newtype EventListenerOptions = EventListenerOptions {}
- class IsGObject o => IsEventListenerOptions o
- toEventListenerOptions :: IsEventListenerOptions o => o -> EventListenerOptions
- noEventListenerOptions :: Maybe EventListenerOptions
- gTypeEventListenerOptions :: JSM GType
- newtype EventModifierInit = EventModifierInit {}
- class (IsUIEventInit o, IsEventInit o, IsGObject o) => IsEventModifierInit o
- toEventModifierInit :: IsEventModifierInit o => o -> EventModifierInit
- noEventModifierInit :: Maybe EventModifierInit
- gTypeEventModifierInit :: JSM GType
- newtype EventSource = EventSource {}
- noEventSource :: Maybe EventSource
- gTypeEventSource :: JSM GType
- newtype EventSourceInit = EventSourceInit {}
- noEventSourceInit :: Maybe EventSourceInit
- gTypeEventSourceInit :: JSM GType
- newtype EventTarget = EventTarget {}
- class IsGObject o => IsEventTarget o
- toEventTarget :: IsEventTarget o => o -> EventTarget
- noEventTarget :: Maybe EventTarget
- gTypeEventTarget :: JSM GType
- newtype File = File {}
- noFile :: Maybe File
- gTypeFile :: JSM GType
- newtype FileError = FileError {
- unFileError :: JSVal
- noFileError :: Maybe FileError
- gTypeFileError :: JSM GType
- newtype FileException = FileException {}
- noFileException :: Maybe FileException
- gTypeFileException :: JSM GType
- newtype FileList = FileList {
- unFileList :: JSVal
- noFileList :: Maybe FileList
- gTypeFileList :: JSM GType
- newtype FilePropertyBag = FilePropertyBag {}
- noFilePropertyBag :: Maybe FilePropertyBag
- gTypeFilePropertyBag :: JSM GType
- newtype FileReader = FileReader {}
- noFileReader :: Maybe FileReader
- gTypeFileReader :: JSM GType
- newtype FileReaderSync = FileReaderSync {}
- noFileReaderSync :: Maybe FileReaderSync
- gTypeFileReaderSync :: JSM GType
- newtype FocusEvent = FocusEvent {}
- noFocusEvent :: Maybe FocusEvent
- gTypeFocusEvent :: JSM GType
- newtype FocusEventInit = FocusEventInit {}
- noFocusEventInit :: Maybe FocusEventInit
- gTypeFocusEventInit :: JSM GType
- newtype FontFace = FontFace {
- unFontFace :: JSVal
- noFontFace :: Maybe FontFace
- gTypeFontFace :: JSM GType
- newtype FontFaceDescriptors = FontFaceDescriptors {}
- noFontFaceDescriptors :: Maybe FontFaceDescriptors
- gTypeFontFaceDescriptors :: JSM GType
- newtype FontFaceSet = FontFaceSet {}
- noFontFaceSet :: Maybe FontFaceSet
- gTypeFontFaceSet :: JSM GType
- newtype FormData = FormData {
- unFormData :: JSVal
- noFormData :: Maybe FormData
- gTypeFormData :: JSM GType
- newtype GainNode = GainNode {
- unGainNode :: JSVal
- noGainNode :: Maybe GainNode
- gTypeGainNode :: JSM GType
- newtype Gamepad = Gamepad {}
- noGamepad :: Maybe Gamepad
- gTypeGamepad :: JSM GType
- newtype GamepadButton = GamepadButton {}
- noGamepadButton :: Maybe GamepadButton
- gTypeGamepadButton :: JSM GType
- newtype GamepadEvent = GamepadEvent {}
- noGamepadEvent :: Maybe GamepadEvent
- gTypeGamepadEvent :: JSM GType
- newtype GamepadEventInit = GamepadEventInit {}
- noGamepadEventInit :: Maybe GamepadEventInit
- gTypeGamepadEventInit :: JSM GType
- newtype Geolocation = Geolocation {}
- noGeolocation :: Maybe Geolocation
- gTypeGeolocation :: JSM GType
- newtype Geoposition = Geoposition {}
- noGeoposition :: Maybe Geoposition
- gTypeGeoposition :: JSM GType
- newtype GetRootNodeOptions = GetRootNodeOptions {}
- noGetRootNodeOptions :: Maybe GetRootNodeOptions
- gTypeGetRootNodeOptions :: JSM GType
- newtype GlobalCrypto = GlobalCrypto {}
- class IsGObject o => IsGlobalCrypto o
- toGlobalCrypto :: IsGlobalCrypto o => o -> GlobalCrypto
- noGlobalCrypto :: Maybe GlobalCrypto
- gTypeGlobalCrypto :: JSM GType
- newtype GlobalEventHandlers = GlobalEventHandlers {}
- class IsGObject o => IsGlobalEventHandlers o
- toGlobalEventHandlers :: IsGlobalEventHandlers o => o -> GlobalEventHandlers
- noGlobalEventHandlers :: Maybe GlobalEventHandlers
- gTypeGlobalEventHandlers :: JSM GType
- newtype GlobalPerformance = GlobalPerformance {}
- class IsGObject o => IsGlobalPerformance o
- toGlobalPerformance :: IsGlobalPerformance o => o -> GlobalPerformance
- noGlobalPerformance :: Maybe GlobalPerformance
- gTypeGlobalPerformance :: JSM GType
- newtype HTMLAllCollection = HTMLAllCollection {}
- noHTMLAllCollection :: Maybe HTMLAllCollection
- gTypeHTMLAllCollection :: JSM GType
- newtype HTMLAnchorElement = HTMLAnchorElement {}
- noHTMLAnchorElement :: Maybe HTMLAnchorElement
- gTypeHTMLAnchorElement :: JSM GType
- newtype HTMLAppletElement = HTMLAppletElement {}
- noHTMLAppletElement :: Maybe HTMLAppletElement
- gTypeHTMLAppletElement :: JSM GType
- newtype HTMLAreaElement = HTMLAreaElement {}
- noHTMLAreaElement :: Maybe HTMLAreaElement
- gTypeHTMLAreaElement :: JSM GType
- newtype HTMLAttachmentElement = HTMLAttachmentElement {}
- noHTMLAttachmentElement :: Maybe HTMLAttachmentElement
- gTypeHTMLAttachmentElement :: JSM GType
- newtype HTMLAudioElement = HTMLAudioElement {}
- noHTMLAudioElement :: Maybe HTMLAudioElement
- gTypeHTMLAudioElement :: JSM GType
- newtype HTMLBRElement = HTMLBRElement {}
- noHTMLBRElement :: Maybe HTMLBRElement
- gTypeHTMLBRElement :: JSM GType
- newtype HTMLBaseElement = HTMLBaseElement {}
- noHTMLBaseElement :: Maybe HTMLBaseElement
- gTypeHTMLBaseElement :: JSM GType
- newtype HTMLBodyElement = HTMLBodyElement {}
- noHTMLBodyElement :: Maybe HTMLBodyElement
- gTypeHTMLBodyElement :: JSM GType
- newtype HTMLButtonElement = HTMLButtonElement {}
- noHTMLButtonElement :: Maybe HTMLButtonElement
- gTypeHTMLButtonElement :: JSM GType
- newtype HTMLCanvasElement = HTMLCanvasElement {}
- noHTMLCanvasElement :: Maybe HTMLCanvasElement
- gTypeHTMLCanvasElement :: JSM GType
- newtype HTMLCollection = HTMLCollection {}
- class IsGObject o => IsHTMLCollection o
- toHTMLCollection :: IsHTMLCollection o => o -> HTMLCollection
- noHTMLCollection :: Maybe HTMLCollection
- gTypeHTMLCollection :: JSM GType
- newtype HTMLDListElement = HTMLDListElement {}
- noHTMLDListElement :: Maybe HTMLDListElement
- gTypeHTMLDListElement :: JSM GType
- newtype HTMLDataElement = HTMLDataElement {}
- noHTMLDataElement :: Maybe HTMLDataElement
- gTypeHTMLDataElement :: JSM GType
- newtype HTMLDataListElement = HTMLDataListElement {}
- noHTMLDataListElement :: Maybe HTMLDataListElement
- gTypeHTMLDataListElement :: JSM GType
- newtype HTMLDetailsElement = HTMLDetailsElement {}
- noHTMLDetailsElement :: Maybe HTMLDetailsElement
- gTypeHTMLDetailsElement :: JSM GType
- newtype HTMLDirectoryElement = HTMLDirectoryElement {}
- noHTMLDirectoryElement :: Maybe HTMLDirectoryElement
- gTypeHTMLDirectoryElement :: JSM GType
- newtype HTMLDivElement = HTMLDivElement {}
- noHTMLDivElement :: Maybe HTMLDivElement
- gTypeHTMLDivElement :: JSM GType
- newtype HTMLDocument = HTMLDocument {}
- noHTMLDocument :: Maybe HTMLDocument
- gTypeHTMLDocument :: JSM GType
- newtype HTMLElement = HTMLElement {}
- 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
- noHTMLElement :: Maybe HTMLElement
- gTypeHTMLElement :: JSM GType
- newtype HTMLEmbedElement = HTMLEmbedElement {}
- noHTMLEmbedElement :: Maybe HTMLEmbedElement
- gTypeHTMLEmbedElement :: JSM GType
- newtype HTMLFieldSetElement = HTMLFieldSetElement {}
- noHTMLFieldSetElement :: Maybe HTMLFieldSetElement
- gTypeHTMLFieldSetElement :: JSM GType
- newtype HTMLFontElement = HTMLFontElement {}
- noHTMLFontElement :: Maybe HTMLFontElement
- gTypeHTMLFontElement :: JSM GType
- newtype HTMLFormControlsCollection = HTMLFormControlsCollection {}
- noHTMLFormControlsCollection :: Maybe HTMLFormControlsCollection
- gTypeHTMLFormControlsCollection :: JSM GType
- newtype HTMLFormElement = HTMLFormElement {}
- noHTMLFormElement :: Maybe HTMLFormElement
- gTypeHTMLFormElement :: JSM GType
- newtype HTMLFrameElement = HTMLFrameElement {}
- noHTMLFrameElement :: Maybe HTMLFrameElement
- gTypeHTMLFrameElement :: JSM GType
- newtype HTMLFrameSetElement = HTMLFrameSetElement {}
- noHTMLFrameSetElement :: Maybe HTMLFrameSetElement
- gTypeHTMLFrameSetElement :: JSM GType
- newtype HTMLHRElement = HTMLHRElement {}
- noHTMLHRElement :: Maybe HTMLHRElement
- gTypeHTMLHRElement :: JSM GType
- newtype HTMLHeadElement = HTMLHeadElement {}
- noHTMLHeadElement :: Maybe HTMLHeadElement
- gTypeHTMLHeadElement :: JSM GType
- newtype HTMLHeadingElement = HTMLHeadingElement {}
- noHTMLHeadingElement :: Maybe HTMLHeadingElement
- gTypeHTMLHeadingElement :: JSM GType
- newtype HTMLHtmlElement = HTMLHtmlElement {}
- noHTMLHtmlElement :: Maybe HTMLHtmlElement
- gTypeHTMLHtmlElement :: JSM GType
- newtype HTMLHyperlinkElementUtils = HTMLHyperlinkElementUtils {}
- class IsGObject o => IsHTMLHyperlinkElementUtils o
- toHTMLHyperlinkElementUtils :: IsHTMLHyperlinkElementUtils o => o -> HTMLHyperlinkElementUtils
- noHTMLHyperlinkElementUtils :: Maybe HTMLHyperlinkElementUtils
- gTypeHTMLHyperlinkElementUtils :: JSM GType
- newtype HTMLIFrameElement = HTMLIFrameElement {}
- noHTMLIFrameElement :: Maybe HTMLIFrameElement
- gTypeHTMLIFrameElement :: JSM GType
- newtype HTMLImageElement = HTMLImageElement {}
- noHTMLImageElement :: Maybe HTMLImageElement
- gTypeHTMLImageElement :: JSM GType
- newtype HTMLInputElement = HTMLInputElement {}
- noHTMLInputElement :: Maybe HTMLInputElement
- gTypeHTMLInputElement :: JSM GType
- newtype HTMLKeygenElement = HTMLKeygenElement {}
- noHTMLKeygenElement :: Maybe HTMLKeygenElement
- gTypeHTMLKeygenElement :: JSM GType
- newtype HTMLLIElement = HTMLLIElement {}
- noHTMLLIElement :: Maybe HTMLLIElement
- gTypeHTMLLIElement :: JSM GType
- newtype HTMLLabelElement = HTMLLabelElement {}
- noHTMLLabelElement :: Maybe HTMLLabelElement
- gTypeHTMLLabelElement :: JSM GType
- newtype HTMLLegendElement = HTMLLegendElement {}
- noHTMLLegendElement :: Maybe HTMLLegendElement
- gTypeHTMLLegendElement :: JSM GType
- newtype HTMLLinkElement = HTMLLinkElement {}
- noHTMLLinkElement :: Maybe HTMLLinkElement
- gTypeHTMLLinkElement :: JSM GType
- newtype HTMLMapElement = HTMLMapElement {}
- noHTMLMapElement :: Maybe HTMLMapElement
- gTypeHTMLMapElement :: JSM GType
- newtype HTMLMarqueeElement = HTMLMarqueeElement {}
- noHTMLMarqueeElement :: Maybe HTMLMarqueeElement
- gTypeHTMLMarqueeElement :: JSM GType
- newtype HTMLMediaElement = HTMLMediaElement {}
- 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
- noHTMLMediaElement :: Maybe HTMLMediaElement
- gTypeHTMLMediaElement :: JSM GType
- newtype HTMLMenuElement = HTMLMenuElement {}
- noHTMLMenuElement :: Maybe HTMLMenuElement
- gTypeHTMLMenuElement :: JSM GType
- newtype HTMLMetaElement = HTMLMetaElement {}
- noHTMLMetaElement :: Maybe HTMLMetaElement
- gTypeHTMLMetaElement :: JSM GType
- newtype HTMLMeterElement = HTMLMeterElement {}
- noHTMLMeterElement :: Maybe HTMLMeterElement
- gTypeHTMLMeterElement :: JSM GType
- newtype HTMLModElement = HTMLModElement {}
- noHTMLModElement :: Maybe HTMLModElement
- gTypeHTMLModElement :: JSM GType
- newtype HTMLOListElement = HTMLOListElement {}
- noHTMLOListElement :: Maybe HTMLOListElement
- gTypeHTMLOListElement :: JSM GType
- newtype HTMLObjectElement = HTMLObjectElement {}
- noHTMLObjectElement :: Maybe HTMLObjectElement
- gTypeHTMLObjectElement :: JSM GType
- newtype HTMLOptGroupElement = HTMLOptGroupElement {}
- noHTMLOptGroupElement :: Maybe HTMLOptGroupElement
- gTypeHTMLOptGroupElement :: JSM GType
- newtype HTMLOptionElement = HTMLOptionElement {}
- noHTMLOptionElement :: Maybe HTMLOptionElement
- gTypeHTMLOptionElement :: JSM GType
- newtype HTMLOptionsCollection = HTMLOptionsCollection {}
- noHTMLOptionsCollection :: Maybe HTMLOptionsCollection
- gTypeHTMLOptionsCollection :: JSM GType
- newtype HTMLOutputElement = HTMLOutputElement {}
- noHTMLOutputElement :: Maybe HTMLOutputElement
- gTypeHTMLOutputElement :: JSM GType
- newtype HTMLParagraphElement = HTMLParagraphElement {}
- noHTMLParagraphElement :: Maybe HTMLParagraphElement
- gTypeHTMLParagraphElement :: JSM GType
- newtype HTMLParamElement = HTMLParamElement {}
- noHTMLParamElement :: Maybe HTMLParamElement
- gTypeHTMLParamElement :: JSM GType
- newtype HTMLPictureElement = HTMLPictureElement {}
- noHTMLPictureElement :: Maybe HTMLPictureElement
- gTypeHTMLPictureElement :: JSM GType
- newtype HTMLPreElement = HTMLPreElement {}
- noHTMLPreElement :: Maybe HTMLPreElement
- gTypeHTMLPreElement :: JSM GType
- newtype HTMLProgressElement = HTMLProgressElement {}
- noHTMLProgressElement :: Maybe HTMLProgressElement
- gTypeHTMLProgressElement :: JSM GType
- newtype HTMLQuoteElement = HTMLQuoteElement {}
- noHTMLQuoteElement :: Maybe HTMLQuoteElement
- gTypeHTMLQuoteElement :: JSM GType
- newtype HTMLScriptElement = HTMLScriptElement {}
- noHTMLScriptElement :: Maybe HTMLScriptElement
- gTypeHTMLScriptElement :: JSM GType
- newtype HTMLSelectElement = HTMLSelectElement {}
- noHTMLSelectElement :: Maybe HTMLSelectElement
- gTypeHTMLSelectElement :: JSM GType
- newtype HTMLSlotElement = HTMLSlotElement {}
- noHTMLSlotElement :: Maybe HTMLSlotElement
- gTypeHTMLSlotElement :: JSM GType
- newtype HTMLSourceElement = HTMLSourceElement {}
- noHTMLSourceElement :: Maybe HTMLSourceElement
- gTypeHTMLSourceElement :: JSM GType
- newtype HTMLSpanElement = HTMLSpanElement {}
- noHTMLSpanElement :: Maybe HTMLSpanElement
- gTypeHTMLSpanElement :: JSM GType
- newtype HTMLStyleElement = HTMLStyleElement {}
- noHTMLStyleElement :: Maybe HTMLStyleElement
- gTypeHTMLStyleElement :: JSM GType
- newtype HTMLTableCaptionElement = HTMLTableCaptionElement {}
- noHTMLTableCaptionElement :: Maybe HTMLTableCaptionElement
- gTypeHTMLTableCaptionElement :: JSM GType
- newtype HTMLTableCellElement = HTMLTableCellElement {}
- noHTMLTableCellElement :: Maybe HTMLTableCellElement
- gTypeHTMLTableCellElement :: JSM GType
- newtype HTMLTableColElement = HTMLTableColElement {}
- noHTMLTableColElement :: Maybe HTMLTableColElement
- gTypeHTMLTableColElement :: JSM GType
- newtype HTMLTableElement = HTMLTableElement {}
- noHTMLTableElement :: Maybe HTMLTableElement
- gTypeHTMLTableElement :: JSM GType
- newtype HTMLTableRowElement = HTMLTableRowElement {}
- noHTMLTableRowElement :: Maybe HTMLTableRowElement
- gTypeHTMLTableRowElement :: JSM GType
- newtype HTMLTableSectionElement = HTMLTableSectionElement {}
- noHTMLTableSectionElement :: Maybe HTMLTableSectionElement
- gTypeHTMLTableSectionElement :: JSM GType
- newtype HTMLTemplateElement = HTMLTemplateElement {}
- noHTMLTemplateElement :: Maybe HTMLTemplateElement
- gTypeHTMLTemplateElement :: JSM GType
- newtype HTMLTextAreaElement = HTMLTextAreaElement {}
- noHTMLTextAreaElement :: Maybe HTMLTextAreaElement
- gTypeHTMLTextAreaElement :: JSM GType
- newtype HTMLTimeElement = HTMLTimeElement {}
- noHTMLTimeElement :: Maybe HTMLTimeElement
- gTypeHTMLTimeElement :: JSM GType
- newtype HTMLTitleElement = HTMLTitleElement {}
- noHTMLTitleElement :: Maybe HTMLTitleElement
- gTypeHTMLTitleElement :: JSM GType
- newtype HTMLTrackElement = HTMLTrackElement {}
- noHTMLTrackElement :: Maybe HTMLTrackElement
- gTypeHTMLTrackElement :: JSM GType
- newtype HTMLUListElement = HTMLUListElement {}
- noHTMLUListElement :: Maybe HTMLUListElement
- gTypeHTMLUListElement :: JSM GType
- newtype HTMLUnknownElement = HTMLUnknownElement {}
- noHTMLUnknownElement :: Maybe HTMLUnknownElement
- gTypeHTMLUnknownElement :: JSM GType
- newtype HTMLVideoElement = HTMLVideoElement {}
- noHTMLVideoElement :: Maybe HTMLVideoElement
- gTypeHTMLVideoElement :: JSM GType
- newtype HashChangeEvent = HashChangeEvent {}
- noHashChangeEvent :: Maybe HashChangeEvent
- gTypeHashChangeEvent :: JSM GType
- newtype HashChangeEventInit = HashChangeEventInit {}
- noHashChangeEventInit :: Maybe HashChangeEventInit
- gTypeHashChangeEventInit :: JSM GType
- newtype Headers = Headers {}
- noHeaders :: Maybe Headers
- gTypeHeaders :: JSM GType
- newtype History = History {}
- noHistory :: Maybe History
- gTypeHistory :: JSM GType
- newtype HkdfParams = HkdfParams {}
- noHkdfParams :: Maybe HkdfParams
- gTypeHkdfParams :: JSM GType
- newtype HmacKeyParams = HmacKeyParams {}
- noHmacKeyParams :: Maybe HmacKeyParams
- gTypeHmacKeyParams :: JSM GType
- newtype IDBCursor = IDBCursor {
- unIDBCursor :: JSVal
- class IsGObject o => IsIDBCursor o
- toIDBCursor :: IsIDBCursor o => o -> IDBCursor
- noIDBCursor :: Maybe IDBCursor
- gTypeIDBCursor :: JSM GType
- newtype IDBCursorWithValue = IDBCursorWithValue {}
- noIDBCursorWithValue :: Maybe IDBCursorWithValue
- gTypeIDBCursorWithValue :: JSM GType
- newtype IDBDatabase = IDBDatabase {}
- noIDBDatabase :: Maybe IDBDatabase
- gTypeIDBDatabase :: JSM GType
- newtype IDBFactory = IDBFactory {}
- noIDBFactory :: Maybe IDBFactory
- gTypeIDBFactory :: JSM GType
- newtype IDBIndex = IDBIndex {
- unIDBIndex :: JSVal
- noIDBIndex :: Maybe IDBIndex
- gTypeIDBIndex :: JSM GType
- newtype IDBIndexParameters = IDBIndexParameters {}
- noIDBIndexParameters :: Maybe IDBIndexParameters
- gTypeIDBIndexParameters :: JSM GType
- newtype IDBKeyRange = IDBKeyRange {}
- noIDBKeyRange :: Maybe IDBKeyRange
- gTypeIDBKeyRange :: JSM GType
- newtype IDBObjectStore = IDBObjectStore {}
- noIDBObjectStore :: Maybe IDBObjectStore
- gTypeIDBObjectStore :: JSM GType
- newtype IDBObjectStoreParameters = IDBObjectStoreParameters {}
- noIDBObjectStoreParameters :: Maybe IDBObjectStoreParameters
- gTypeIDBObjectStoreParameters :: JSM GType
- newtype IDBOpenDBRequest = IDBOpenDBRequest {}
- noIDBOpenDBRequest :: Maybe IDBOpenDBRequest
- gTypeIDBOpenDBRequest :: JSM GType
- newtype IDBRequest = IDBRequest {}
- class (IsEventTarget o, IsGObject o) => IsIDBRequest o
- toIDBRequest :: IsIDBRequest o => o -> IDBRequest
- noIDBRequest :: Maybe IDBRequest
- gTypeIDBRequest :: JSM GType
- newtype IDBTransaction = IDBTransaction {}
- noIDBTransaction :: Maybe IDBTransaction
- gTypeIDBTransaction :: JSM GType
- newtype IDBVersionChangeEvent = IDBVersionChangeEvent {}
- noIDBVersionChangeEvent :: Maybe IDBVersionChangeEvent
- gTypeIDBVersionChangeEvent :: JSM GType
- newtype IDBVersionChangeEventInit = IDBVersionChangeEventInit {}
- noIDBVersionChangeEventInit :: Maybe IDBVersionChangeEventInit
- gTypeIDBVersionChangeEventInit :: JSM GType
- newtype ImageData = ImageData {
- unImageData :: JSVal
- noImageData :: Maybe ImageData
- gTypeImageData :: JSM GType
- newtype InputEvent = InputEvent {}
- noInputEvent :: Maybe InputEvent
- gTypeInputEvent :: JSM GType
- newtype InputEventInit = InputEventInit {}
- noInputEventInit :: Maybe InputEventInit
- gTypeInputEventInit :: JSM GType
- newtype InspectorFrontendHost = InspectorFrontendHost {}
- noInspectorFrontendHost :: Maybe InspectorFrontendHost
- gTypeInspectorFrontendHost :: JSM GType
- newtype IntersectionObserver = IntersectionObserver {}
- noIntersectionObserver :: Maybe IntersectionObserver
- gTypeIntersectionObserver :: JSM GType
- newtype IntersectionObserverEntry = IntersectionObserverEntry {}
- noIntersectionObserverEntry :: Maybe IntersectionObserverEntry
- gTypeIntersectionObserverEntry :: JSM GType
- newtype IntersectionObserverEntryInit = IntersectionObserverEntryInit {}
- noIntersectionObserverEntryInit :: Maybe IntersectionObserverEntryInit
- gTypeIntersectionObserverEntryInit :: JSM GType
- newtype IntersectionObserverInit = IntersectionObserverInit {}
- noIntersectionObserverInit :: Maybe IntersectionObserverInit
- gTypeIntersectionObserverInit :: JSM GType
- newtype JsonWebKey = JsonWebKey {}
- noJsonWebKey :: Maybe JsonWebKey
- gTypeJsonWebKey :: JSM GType
- newtype KeyboardEvent = KeyboardEvent {}
- noKeyboardEvent :: Maybe KeyboardEvent
- gTypeKeyboardEvent :: JSM GType
- newtype KeyboardEventInit = KeyboardEventInit {}
- noKeyboardEventInit :: Maybe KeyboardEventInit
- gTypeKeyboardEventInit :: JSM GType
- newtype KeyframeEffect = KeyframeEffect {}
- noKeyframeEffect :: Maybe KeyframeEffect
- gTypeKeyframeEffect :: JSM GType
- newtype Location = Location {
- unLocation :: JSVal
- noLocation :: Maybe Location
- gTypeLocation :: JSM GType
- newtype LongRange = LongRange {
- unLongRange :: JSVal
- class IsGObject o => IsLongRange o
- toLongRange :: IsLongRange o => o -> LongRange
- noLongRange :: Maybe LongRange
- gTypeLongRange :: JSM GType
- newtype MediaController = MediaController {}
- noMediaController :: Maybe MediaController
- gTypeMediaController :: JSM GType
- newtype MediaControlsHost = MediaControlsHost {}
- noMediaControlsHost :: Maybe MediaControlsHost
- gTypeMediaControlsHost :: JSM GType
- newtype MediaDeviceInfo = MediaDeviceInfo {}
- noMediaDeviceInfo :: Maybe MediaDeviceInfo
- gTypeMediaDeviceInfo :: JSM GType
- newtype MediaDevices = MediaDevices {}
- noMediaDevices :: Maybe MediaDevices
- gTypeMediaDevices :: JSM GType
- newtype MediaElementAudioSourceNode = MediaElementAudioSourceNode {}
- noMediaElementAudioSourceNode :: Maybe MediaElementAudioSourceNode
- gTypeMediaElementAudioSourceNode :: JSM GType
- newtype MediaEncryptedEvent = MediaEncryptedEvent {}
- noMediaEncryptedEvent :: Maybe MediaEncryptedEvent
- gTypeMediaEncryptedEvent :: JSM GType
- newtype MediaEncryptedEventInit = MediaEncryptedEventInit {}
- noMediaEncryptedEventInit :: Maybe MediaEncryptedEventInit
- gTypeMediaEncryptedEventInit :: JSM GType
- newtype MediaError = MediaError {}
- noMediaError :: Maybe MediaError
- gTypeMediaError :: JSM GType
- newtype MediaKeyMessageEvent = MediaKeyMessageEvent {}
- noMediaKeyMessageEvent :: Maybe MediaKeyMessageEvent
- gTypeMediaKeyMessageEvent :: JSM GType
- newtype MediaKeyMessageEventInit = MediaKeyMessageEventInit {}
- noMediaKeyMessageEventInit :: Maybe MediaKeyMessageEventInit
- gTypeMediaKeyMessageEventInit :: JSM GType
- newtype MediaKeySession = MediaKeySession {}
- noMediaKeySession :: Maybe MediaKeySession
- gTypeMediaKeySession :: JSM GType
- newtype MediaKeyStatusMap = MediaKeyStatusMap {}
- noMediaKeyStatusMap :: Maybe MediaKeyStatusMap
- gTypeMediaKeyStatusMap :: JSM GType
- newtype MediaKeySystemAccess = MediaKeySystemAccess {}
- noMediaKeySystemAccess :: Maybe MediaKeySystemAccess
- gTypeMediaKeySystemAccess :: JSM GType
- newtype MediaKeySystemConfiguration = MediaKeySystemConfiguration {}
- noMediaKeySystemConfiguration :: Maybe MediaKeySystemConfiguration
- gTypeMediaKeySystemConfiguration :: JSM GType
- newtype MediaKeySystemMediaCapability = MediaKeySystemMediaCapability {}
- noMediaKeySystemMediaCapability :: Maybe MediaKeySystemMediaCapability
- gTypeMediaKeySystemMediaCapability :: JSM GType
- newtype MediaKeys = MediaKeys {
- unMediaKeys :: JSVal
- noMediaKeys :: Maybe MediaKeys
- gTypeMediaKeys :: JSM GType
- newtype MediaList = MediaList {
- unMediaList :: JSVal
- noMediaList :: Maybe MediaList
- gTypeMediaList :: JSM GType
- newtype MediaMetadata = MediaMetadata {}
- noMediaMetadata :: Maybe MediaMetadata
- gTypeMediaMetadata :: JSM GType
- newtype MediaQueryList = MediaQueryList {}
- noMediaQueryList :: Maybe MediaQueryList
- gTypeMediaQueryList :: JSM GType
- newtype MediaRemoteControls = MediaRemoteControls {}
- noMediaRemoteControls :: Maybe MediaRemoteControls
- gTypeMediaRemoteControls :: JSM GType
- newtype MediaSession = MediaSession {}
- noMediaSession :: Maybe MediaSession
- gTypeMediaSession :: JSM GType
- newtype MediaSource = MediaSource {}
- noMediaSource :: Maybe MediaSource
- gTypeMediaSource :: JSM GType
- newtype MediaStream = MediaStream {}
- noMediaStream :: Maybe MediaStream
- gTypeMediaStream :: JSM GType
- newtype MediaStreamAudioDestinationNode = MediaStreamAudioDestinationNode {}
- noMediaStreamAudioDestinationNode :: Maybe MediaStreamAudioDestinationNode
- gTypeMediaStreamAudioDestinationNode :: JSM GType
- newtype MediaStreamAudioSourceNode = MediaStreamAudioSourceNode {}
- noMediaStreamAudioSourceNode :: Maybe MediaStreamAudioSourceNode
- gTypeMediaStreamAudioSourceNode :: JSM GType
- newtype MediaStreamConstraints = MediaStreamConstraints {}
- noMediaStreamConstraints :: Maybe MediaStreamConstraints
- gTypeMediaStreamConstraints :: JSM GType
- newtype MediaStreamEvent = MediaStreamEvent {}
- noMediaStreamEvent :: Maybe MediaStreamEvent
- gTypeMediaStreamEvent :: JSM GType
- newtype MediaStreamEventInit = MediaStreamEventInit {}
- noMediaStreamEventInit :: Maybe MediaStreamEventInit
- gTypeMediaStreamEventInit :: JSM GType
- newtype MediaStreamTrack = MediaStreamTrack {}
- class (IsEventTarget o, IsGObject o) => IsMediaStreamTrack o
- toMediaStreamTrack :: IsMediaStreamTrack o => o -> MediaStreamTrack
- noMediaStreamTrack :: Maybe MediaStreamTrack
- gTypeMediaStreamTrack :: JSM GType
- newtype MediaStreamTrackEvent = MediaStreamTrackEvent {}
- noMediaStreamTrackEvent :: Maybe MediaStreamTrackEvent
- gTypeMediaStreamTrackEvent :: JSM GType
- newtype MediaStreamTrackEventInit = MediaStreamTrackEventInit {}
- noMediaStreamTrackEventInit :: Maybe MediaStreamTrackEventInit
- gTypeMediaStreamTrackEventInit :: JSM GType
- newtype MediaTrackCapabilities = MediaTrackCapabilities {}
- noMediaTrackCapabilities :: Maybe MediaTrackCapabilities
- gTypeMediaTrackCapabilities :: JSM GType
- newtype MediaTrackConstraintSet = MediaTrackConstraintSet {}
- class IsGObject o => IsMediaTrackConstraintSet o
- toMediaTrackConstraintSet :: IsMediaTrackConstraintSet o => o -> MediaTrackConstraintSet
- noMediaTrackConstraintSet :: Maybe MediaTrackConstraintSet
- gTypeMediaTrackConstraintSet :: JSM GType
- newtype MediaTrackConstraints = MediaTrackConstraints {}
- noMediaTrackConstraints :: Maybe MediaTrackConstraints
- gTypeMediaTrackConstraints :: JSM GType
- newtype MediaTrackSettings = MediaTrackSettings {}
- noMediaTrackSettings :: Maybe MediaTrackSettings
- gTypeMediaTrackSettings :: JSM GType
- newtype MediaTrackSupportedConstraints = MediaTrackSupportedConstraints {}
- noMediaTrackSupportedConstraints :: Maybe MediaTrackSupportedConstraints
- gTypeMediaTrackSupportedConstraints :: JSM GType
- newtype MessageChannel = MessageChannel {}
- noMessageChannel :: Maybe MessageChannel
- gTypeMessageChannel :: JSM GType
- newtype MessageEvent = MessageEvent {}
- noMessageEvent :: Maybe MessageEvent
- gTypeMessageEvent :: JSM GType
- newtype MessageEventInit = MessageEventInit {}
- noMessageEventInit :: Maybe MessageEventInit
- gTypeMessageEventInit :: JSM GType
- newtype MessagePort = MessagePort {}
- noMessagePort :: Maybe MessagePort
- gTypeMessagePort :: JSM GType
- newtype MimeType = MimeType {
- unMimeType :: JSVal
- noMimeType :: Maybe MimeType
- gTypeMimeType :: JSM GType
- newtype MimeTypeArray = MimeTypeArray {}
- noMimeTypeArray :: Maybe MimeTypeArray
- gTypeMimeTypeArray :: JSM GType
- newtype MouseEvent = MouseEvent {}
- class (IsUIEvent o, IsEvent o, IsGObject o) => IsMouseEvent o
- toMouseEvent :: IsMouseEvent o => o -> MouseEvent
- noMouseEvent :: Maybe MouseEvent
- gTypeMouseEvent :: JSM GType
- newtype MouseEventInit = MouseEventInit {}
- class (IsEventModifierInit o, IsUIEventInit o, IsEventInit o, IsGObject o) => IsMouseEventInit o
- toMouseEventInit :: IsMouseEventInit o => o -> MouseEventInit
- noMouseEventInit :: Maybe MouseEventInit
- gTypeMouseEventInit :: JSM GType
- newtype MutationEvent = MutationEvent {}
- noMutationEvent :: Maybe MutationEvent
- gTypeMutationEvent :: JSM GType
- newtype MutationObserver = MutationObserver {}
- noMutationObserver :: Maybe MutationObserver
- gTypeMutationObserver :: JSM GType
- newtype MutationObserverInit = MutationObserverInit {}
- noMutationObserverInit :: Maybe MutationObserverInit
- gTypeMutationObserverInit :: JSM GType
- newtype MutationRecord = MutationRecord {}
- noMutationRecord :: Maybe MutationRecord
- gTypeMutationRecord :: JSM GType
- newtype NamedNodeMap = NamedNodeMap {}
- noNamedNodeMap :: Maybe NamedNodeMap
- gTypeNamedNodeMap :: JSM GType
- newtype Navigator = Navigator {
- unNavigator :: JSVal
- noNavigator :: Maybe Navigator
- gTypeNavigator :: JSM GType
- newtype NavigatorConcurrentHardware = NavigatorConcurrentHardware {}
- class IsGObject o => IsNavigatorConcurrentHardware o
- toNavigatorConcurrentHardware :: IsNavigatorConcurrentHardware o => o -> NavigatorConcurrentHardware
- noNavigatorConcurrentHardware :: Maybe NavigatorConcurrentHardware
- gTypeNavigatorConcurrentHardware :: JSM GType
- newtype NavigatorID = NavigatorID {}
- class IsGObject o => IsNavigatorID o
- toNavigatorID :: IsNavigatorID o => o -> NavigatorID
- noNavigatorID :: Maybe NavigatorID
- gTypeNavigatorID :: JSM GType
- newtype NavigatorLanguage = NavigatorLanguage {}
- class IsGObject o => IsNavigatorLanguage o
- toNavigatorLanguage :: IsNavigatorLanguage o => o -> NavigatorLanguage
- noNavigatorLanguage :: Maybe NavigatorLanguage
- gTypeNavigatorLanguage :: JSM GType
- newtype NavigatorOnLine = NavigatorOnLine {}
- class IsGObject o => IsNavigatorOnLine o
- toNavigatorOnLine :: IsNavigatorOnLine o => o -> NavigatorOnLine
- noNavigatorOnLine :: Maybe NavigatorOnLine
- gTypeNavigatorOnLine :: JSM GType
- newtype NavigatorUserMediaError = NavigatorUserMediaError {}
- noNavigatorUserMediaError :: Maybe NavigatorUserMediaError
- gTypeNavigatorUserMediaError :: JSM GType
- newtype Node = Node {}
- class (IsEventTarget o, IsGObject o) => IsNode o
- toNode :: IsNode o => o -> Node
- noNode :: Maybe Node
- gTypeNode :: JSM GType
- newtype NodeIterator = NodeIterator {}
- noNodeIterator :: Maybe NodeIterator
- gTypeNodeIterator :: JSM GType
- newtype NodeList = NodeList {
- unNodeList :: JSVal
- class IsGObject o => IsNodeList o
- toNodeList :: IsNodeList o => o -> NodeList
- noNodeList :: Maybe NodeList
- gTypeNodeList :: JSM GType
- newtype NonDocumentTypeChildNode = NonDocumentTypeChildNode {}
- class IsGObject o => IsNonDocumentTypeChildNode o
- toNonDocumentTypeChildNode :: IsNonDocumentTypeChildNode o => o -> NonDocumentTypeChildNode
- noNonDocumentTypeChildNode :: Maybe NonDocumentTypeChildNode
- gTypeNonDocumentTypeChildNode :: JSM GType
- newtype NonElementParentNode = NonElementParentNode {}
- class IsGObject o => IsNonElementParentNode o
- toNonElementParentNode :: IsNonElementParentNode o => o -> NonElementParentNode
- noNonElementParentNode :: Maybe NonElementParentNode
- gTypeNonElementParentNode :: JSM GType
- newtype Notification = Notification {}
- noNotification :: Maybe Notification
- gTypeNotification :: JSM GType
- newtype NotificationOptions = NotificationOptions {}
- noNotificationOptions :: Maybe NotificationOptions
- gTypeNotificationOptions :: JSM GType
- newtype OESElementIndexUint = OESElementIndexUint {}
- noOESElementIndexUint :: Maybe OESElementIndexUint
- gTypeOESElementIndexUint :: JSM GType
- newtype OESStandardDerivatives = OESStandardDerivatives {}
- noOESStandardDerivatives :: Maybe OESStandardDerivatives
- gTypeOESStandardDerivatives :: JSM GType
- newtype OESTextureFloat = OESTextureFloat {}
- noOESTextureFloat :: Maybe OESTextureFloat
- gTypeOESTextureFloat :: JSM GType
- newtype OESTextureFloatLinear = OESTextureFloatLinear {}
- noOESTextureFloatLinear :: Maybe OESTextureFloatLinear
- gTypeOESTextureFloatLinear :: JSM GType
- newtype OESTextureHalfFloat = OESTextureHalfFloat {}
- noOESTextureHalfFloat :: Maybe OESTextureHalfFloat
- gTypeOESTextureHalfFloat :: JSM GType
- newtype OESTextureHalfFloatLinear = OESTextureHalfFloatLinear {}
- noOESTextureHalfFloatLinear :: Maybe OESTextureHalfFloatLinear
- gTypeOESTextureHalfFloatLinear :: JSM GType
- newtype OESVertexArrayObject = OESVertexArrayObject {}
- noOESVertexArrayObject :: Maybe OESVertexArrayObject
- gTypeOESVertexArrayObject :: JSM GType
- newtype OfflineAudioCompletionEvent = OfflineAudioCompletionEvent {}
- noOfflineAudioCompletionEvent :: Maybe OfflineAudioCompletionEvent
- gTypeOfflineAudioCompletionEvent :: JSM GType
- newtype OfflineAudioContext = OfflineAudioContext {}
- noOfflineAudioContext :: Maybe OfflineAudioContext
- gTypeOfflineAudioContext :: JSM GType
- newtype OscillatorNode = OscillatorNode {}
- noOscillatorNode :: Maybe OscillatorNode
- gTypeOscillatorNode :: JSM GType
- newtype OverconstrainedError = OverconstrainedError {}
- noOverconstrainedError :: Maybe OverconstrainedError
- gTypeOverconstrainedError :: JSM GType
- newtype OverconstrainedErrorEvent = OverconstrainedErrorEvent {}
- noOverconstrainedErrorEvent :: Maybe OverconstrainedErrorEvent
- gTypeOverconstrainedErrorEvent :: JSM GType
- newtype OverconstrainedErrorEventInit = OverconstrainedErrorEventInit {}
- noOverconstrainedErrorEventInit :: Maybe OverconstrainedErrorEventInit
- gTypeOverconstrainedErrorEventInit :: JSM GType
- newtype OverflowEvent = OverflowEvent {}
- noOverflowEvent :: Maybe OverflowEvent
- gTypeOverflowEvent :: JSM GType
- newtype OverflowEventInit = OverflowEventInit {}
- noOverflowEventInit :: Maybe OverflowEventInit
- gTypeOverflowEventInit :: JSM GType
- newtype PageTransitionEvent = PageTransitionEvent {}
- noPageTransitionEvent :: Maybe PageTransitionEvent
- gTypePageTransitionEvent :: JSM GType
- newtype PageTransitionEventInit = PageTransitionEventInit {}
- noPageTransitionEventInit :: Maybe PageTransitionEventInit
- gTypePageTransitionEventInit :: JSM GType
- newtype PannerNode = PannerNode {}
- noPannerNode :: Maybe PannerNode
- gTypePannerNode :: JSM GType
- newtype ParentNode = ParentNode {}
- class IsGObject o => IsParentNode o
- toParentNode :: IsParentNode o => o -> ParentNode
- noParentNode :: Maybe ParentNode
- gTypeParentNode :: JSM GType
- newtype PasswordCredential = PasswordCredential {}
- noPasswordCredential :: Maybe PasswordCredential
- gTypePasswordCredential :: JSM GType
- newtype PasswordCredentialData = PasswordCredentialData {}
- noPasswordCredentialData :: Maybe PasswordCredentialData
- gTypePasswordCredentialData :: JSM GType
- newtype Path2D = Path2D {}
- noPath2D :: Maybe Path2D
- gTypePath2D :: JSM GType
- newtype Pbkdf2Params = Pbkdf2Params {}
- noPbkdf2Params :: Maybe Pbkdf2Params
- gTypePbkdf2Params :: JSM GType
- newtype Performance = Performance {}
- noPerformance :: Maybe Performance
- gTypePerformance :: JSM GType
- newtype PerformanceEntry = PerformanceEntry {}
- class IsGObject o => IsPerformanceEntry o
- toPerformanceEntry :: IsPerformanceEntry o => o -> PerformanceEntry
- noPerformanceEntry :: Maybe PerformanceEntry
- gTypePerformanceEntry :: JSM GType
- newtype PerformanceMark = PerformanceMark {}
- noPerformanceMark :: Maybe PerformanceMark
- gTypePerformanceMark :: JSM GType
- newtype PerformanceMeasure = PerformanceMeasure {}
- noPerformanceMeasure :: Maybe PerformanceMeasure
- gTypePerformanceMeasure :: JSM GType
- newtype PerformanceNavigation = PerformanceNavigation {}
- noPerformanceNavigation :: Maybe PerformanceNavigation
- gTypePerformanceNavigation :: JSM GType
- newtype PerformanceObserver = PerformanceObserver {}
- noPerformanceObserver :: Maybe PerformanceObserver
- gTypePerformanceObserver :: JSM GType
- newtype PerformanceObserverEntryList = PerformanceObserverEntryList {}
- noPerformanceObserverEntryList :: Maybe PerformanceObserverEntryList
- gTypePerformanceObserverEntryList :: JSM GType
- newtype PerformanceObserverInit = PerformanceObserverInit {}
- noPerformanceObserverInit :: Maybe PerformanceObserverInit
- gTypePerformanceObserverInit :: JSM GType
- newtype PerformanceResourceTiming = PerformanceResourceTiming {}
- noPerformanceResourceTiming :: Maybe PerformanceResourceTiming
- gTypePerformanceResourceTiming :: JSM GType
- newtype PerformanceTiming = PerformanceTiming {}
- noPerformanceTiming :: Maybe PerformanceTiming
- gTypePerformanceTiming :: JSM GType
- newtype PeriodicWave = PeriodicWave {}
- noPeriodicWave :: Maybe PeriodicWave
- gTypePeriodicWave :: JSM GType
- newtype Plugin = Plugin {}
- noPlugin :: Maybe Plugin
- gTypePlugin :: JSM GType
- newtype PluginArray = PluginArray {}
- noPluginArray :: Maybe PluginArray
- gTypePluginArray :: JSM GType
- newtype PopStateEvent = PopStateEvent {}
- noPopStateEvent :: Maybe PopStateEvent
- gTypePopStateEvent :: JSM GType
- newtype PopStateEventInit = PopStateEventInit {}
- noPopStateEventInit :: Maybe PopStateEventInit
- gTypePopStateEventInit :: JSM GType
- newtype PositionError = PositionError {}
- noPositionError :: Maybe PositionError
- gTypePositionError :: JSM GType
- newtype PositionOptions = PositionOptions {}
- noPositionOptions :: Maybe PositionOptions
- gTypePositionOptions :: JSM GType
- newtype ProcessingInstruction = ProcessingInstruction {}
- noProcessingInstruction :: Maybe ProcessingInstruction
- gTypeProcessingInstruction :: JSM GType
- newtype ProgressEvent = ProgressEvent {}
- class (IsEvent o, IsGObject o) => IsProgressEvent o
- toProgressEvent :: IsProgressEvent o => o -> ProgressEvent
- noProgressEvent :: Maybe ProgressEvent
- gTypeProgressEvent :: JSM GType
- newtype ProgressEventInit = ProgressEventInit {}
- noProgressEventInit :: Maybe ProgressEventInit
- gTypeProgressEventInit :: JSM GType
- newtype PromiseRejectionEvent = PromiseRejectionEvent {}
- noPromiseRejectionEvent :: Maybe PromiseRejectionEvent
- gTypePromiseRejectionEvent :: JSM GType
- newtype PromiseRejectionEventInit = PromiseRejectionEventInit {}
- noPromiseRejectionEventInit :: Maybe PromiseRejectionEventInit
- gTypePromiseRejectionEventInit :: JSM GType
- newtype QuickTimePluginReplacement = QuickTimePluginReplacement {}
- noQuickTimePluginReplacement :: Maybe QuickTimePluginReplacement
- gTypeQuickTimePluginReplacement :: JSM GType
- newtype RGBColor = RGBColor {
- unRGBColor :: JSVal
- noRGBColor :: Maybe RGBColor
- gTypeRGBColor :: JSM GType
- newtype RTCAnswerOptions = RTCAnswerOptions {}
- noRTCAnswerOptions :: Maybe RTCAnswerOptions
- gTypeRTCAnswerOptions :: JSM GType
- newtype RTCConfiguration = RTCConfiguration {}
- noRTCConfiguration :: Maybe RTCConfiguration
- gTypeRTCConfiguration :: JSM GType
- newtype RTCDTMFSender = RTCDTMFSender {}
- noRTCDTMFSender :: Maybe RTCDTMFSender
- gTypeRTCDTMFSender :: JSM GType
- newtype RTCDTMFToneChangeEvent = RTCDTMFToneChangeEvent {}
- noRTCDTMFToneChangeEvent :: Maybe RTCDTMFToneChangeEvent
- gTypeRTCDTMFToneChangeEvent :: JSM GType
- newtype RTCDTMFToneChangeEventInit = RTCDTMFToneChangeEventInit {}
- noRTCDTMFToneChangeEventInit :: Maybe RTCDTMFToneChangeEventInit
- gTypeRTCDTMFToneChangeEventInit :: JSM GType
- newtype RTCDataChannel = RTCDataChannel {}
- noRTCDataChannel :: Maybe RTCDataChannel
- gTypeRTCDataChannel :: JSM GType
- newtype RTCDataChannelEvent = RTCDataChannelEvent {}
- noRTCDataChannelEvent :: Maybe RTCDataChannelEvent
- gTypeRTCDataChannelEvent :: JSM GType
- newtype RTCDataChannelEventInit = RTCDataChannelEventInit {}
- noRTCDataChannelEventInit :: Maybe RTCDataChannelEventInit
- gTypeRTCDataChannelEventInit :: JSM GType
- newtype RTCDataChannelInit = RTCDataChannelInit {}
- noRTCDataChannelInit :: Maybe RTCDataChannelInit
- gTypeRTCDataChannelInit :: JSM GType
- newtype RTCDataChannelStats = RTCDataChannelStats {}
- noRTCDataChannelStats :: Maybe RTCDataChannelStats
- gTypeRTCDataChannelStats :: JSM GType
- newtype RTCIceCandidate = RTCIceCandidate {}
- noRTCIceCandidate :: Maybe RTCIceCandidate
- gTypeRTCIceCandidate :: JSM GType
- newtype RTCIceCandidateEvent = RTCIceCandidateEvent {}
- noRTCIceCandidateEvent :: Maybe RTCIceCandidateEvent
- gTypeRTCIceCandidateEvent :: JSM GType
- newtype RTCIceCandidateInit = RTCIceCandidateInit {}
- noRTCIceCandidateInit :: Maybe RTCIceCandidateInit
- gTypeRTCIceCandidateInit :: JSM GType
- newtype RTCIceServer = RTCIceServer {}
- noRTCIceServer :: Maybe RTCIceServer
- gTypeRTCIceServer :: JSM GType
- newtype RTCIceTransport = RTCIceTransport {}
- noRTCIceTransport :: Maybe RTCIceTransport
- gTypeRTCIceTransport :: JSM GType
- newtype RTCInboundRTPStreamStats = RTCInboundRTPStreamStats {}
- noRTCInboundRTPStreamStats :: Maybe RTCInboundRTPStreamStats
- gTypeRTCInboundRTPStreamStats :: JSM GType
- newtype RTCMediaStreamTrackStats = RTCMediaStreamTrackStats {}
- noRTCMediaStreamTrackStats :: Maybe RTCMediaStreamTrackStats
- gTypeRTCMediaStreamTrackStats :: JSM GType
- newtype RTCOfferAnswerOptions = RTCOfferAnswerOptions {}
- class IsGObject o => IsRTCOfferAnswerOptions o
- toRTCOfferAnswerOptions :: IsRTCOfferAnswerOptions o => o -> RTCOfferAnswerOptions
- noRTCOfferAnswerOptions :: Maybe RTCOfferAnswerOptions
- gTypeRTCOfferAnswerOptions :: JSM GType
- newtype RTCOfferOptions = RTCOfferOptions {}
- noRTCOfferOptions :: Maybe RTCOfferOptions
- gTypeRTCOfferOptions :: JSM GType
- newtype RTCOutboundRTPStreamStats = RTCOutboundRTPStreamStats {}
- noRTCOutboundRTPStreamStats :: Maybe RTCOutboundRTPStreamStats
- gTypeRTCOutboundRTPStreamStats :: JSM GType
- newtype RTCPeerConnection = RTCPeerConnection {}
- noRTCPeerConnection :: Maybe RTCPeerConnection
- gTypeRTCPeerConnection :: JSM GType
- newtype RTCPeerConnectionIceEvent = RTCPeerConnectionIceEvent {}
- noRTCPeerConnectionIceEvent :: Maybe RTCPeerConnectionIceEvent
- gTypeRTCPeerConnectionIceEvent :: JSM GType
- newtype RTCRTPStreamStats = RTCRTPStreamStats {}
- class (IsRTCStats o, IsGObject o) => IsRTCRTPStreamStats o
- toRTCRTPStreamStats :: IsRTCRTPStreamStats o => o -> RTCRTPStreamStats
- noRTCRTPStreamStats :: Maybe RTCRTPStreamStats
- gTypeRTCRTPStreamStats :: JSM GType
- newtype RTCRtpCodecParameters = RTCRtpCodecParameters {}
- noRTCRtpCodecParameters :: Maybe RTCRtpCodecParameters
- gTypeRTCRtpCodecParameters :: JSM GType
- newtype RTCRtpEncodingParameters = RTCRtpEncodingParameters {}
- noRTCRtpEncodingParameters :: Maybe RTCRtpEncodingParameters
- gTypeRTCRtpEncodingParameters :: JSM GType
- newtype RTCRtpFecParameters = RTCRtpFecParameters {}
- noRTCRtpFecParameters :: Maybe RTCRtpFecParameters
- gTypeRTCRtpFecParameters :: JSM GType
- newtype RTCRtpHeaderExtensionParameters = RTCRtpHeaderExtensionParameters {}
- noRTCRtpHeaderExtensionParameters :: Maybe RTCRtpHeaderExtensionParameters
- gTypeRTCRtpHeaderExtensionParameters :: JSM GType
- newtype RTCRtpParameters = RTCRtpParameters {}
- noRTCRtpParameters :: Maybe RTCRtpParameters
- gTypeRTCRtpParameters :: JSM GType
- newtype RTCRtpReceiver = RTCRtpReceiver {}
- noRTCRtpReceiver :: Maybe RTCRtpReceiver
- gTypeRTCRtpReceiver :: JSM GType
- newtype RTCRtpRtxParameters = RTCRtpRtxParameters {}
- noRTCRtpRtxParameters :: Maybe RTCRtpRtxParameters
- gTypeRTCRtpRtxParameters :: JSM GType
- newtype RTCRtpSender = RTCRtpSender {}
- noRTCRtpSender :: Maybe RTCRtpSender
- gTypeRTCRtpSender :: JSM GType
- newtype RTCRtpTransceiver = RTCRtpTransceiver {}
- noRTCRtpTransceiver :: Maybe RTCRtpTransceiver
- gTypeRTCRtpTransceiver :: JSM GType
- newtype RTCRtpTransceiverInit = RTCRtpTransceiverInit {}
- noRTCRtpTransceiverInit :: Maybe RTCRtpTransceiverInit
- gTypeRTCRtpTransceiverInit :: JSM GType
- newtype RTCSessionDescription = RTCSessionDescription {}
- noRTCSessionDescription :: Maybe RTCSessionDescription
- gTypeRTCSessionDescription :: JSM GType
- newtype RTCSessionDescriptionInit = RTCSessionDescriptionInit {}
- noRTCSessionDescriptionInit :: Maybe RTCSessionDescriptionInit
- gTypeRTCSessionDescriptionInit :: JSM GType
- newtype RTCStats = RTCStats {
- unRTCStats :: JSVal
- class IsGObject o => IsRTCStats o
- toRTCStats :: IsRTCStats o => o -> RTCStats
- noRTCStats :: Maybe RTCStats
- gTypeRTCStats :: JSM GType
- newtype RTCStatsReport = RTCStatsReport {}
- noRTCStatsReport :: Maybe RTCStatsReport
- gTypeRTCStatsReport :: JSM GType
- newtype RTCTrackEvent = RTCTrackEvent {}
- noRTCTrackEvent :: Maybe RTCTrackEvent
- gTypeRTCTrackEvent :: JSM GType
- newtype RTCTrackEventInit = RTCTrackEventInit {}
- noRTCTrackEventInit :: Maybe RTCTrackEventInit
- gTypeRTCTrackEventInit :: JSM GType
- newtype RadioNodeList = RadioNodeList {}
- noRadioNodeList :: Maybe RadioNodeList
- gTypeRadioNodeList :: JSM GType
- newtype Range = Range {}
- noRange :: Maybe Range
- gTypeRange :: JSM GType
- newtype ReadableByteStreamController = ReadableByteStreamController {}
- noReadableByteStreamController :: Maybe ReadableByteStreamController
- gTypeReadableByteStreamController :: JSM GType
- newtype ReadableStream = ReadableStream {}
- noReadableStream :: Maybe ReadableStream
- gTypeReadableStream :: JSM GType
- newtype ReadableStreamBYOBReader = ReadableStreamBYOBReader {}
- noReadableStreamBYOBReader :: Maybe ReadableStreamBYOBReader
- gTypeReadableStreamBYOBReader :: JSM GType
- newtype ReadableStreamBYOBRequest = ReadableStreamBYOBRequest {}
- noReadableStreamBYOBRequest :: Maybe ReadableStreamBYOBRequest
- gTypeReadableStreamBYOBRequest :: JSM GType
- newtype ReadableStreamDefaultController = ReadableStreamDefaultController {}
- noReadableStreamDefaultController :: Maybe ReadableStreamDefaultController
- gTypeReadableStreamDefaultController :: JSM GType
- newtype ReadableStreamDefaultReader = ReadableStreamDefaultReader {}
- noReadableStreamDefaultReader :: Maybe ReadableStreamDefaultReader
- gTypeReadableStreamDefaultReader :: JSM GType
- newtype ReadableStreamSource = ReadableStreamSource {}
- noReadableStreamSource :: Maybe ReadableStreamSource
- gTypeReadableStreamSource :: JSM GType
- newtype Rect = Rect {}
- noRect :: Maybe Rect
- gTypeRect :: JSM GType
- newtype Request = Request {}
- noRequest :: Maybe Request
- gTypeRequest :: JSM GType
- newtype RequestInit = RequestInit {}
- noRequestInit :: Maybe RequestInit
- gTypeRequestInit :: JSM GType
- newtype Response = Response {
- unResponse :: JSVal
- noResponse :: Maybe Response
- gTypeResponse :: JSM GType
- newtype RotationRate = RotationRate {}
- noRotationRate :: Maybe RotationRate
- gTypeRotationRate :: JSM GType
- newtype RsaHashedImportParams = RsaHashedImportParams {}
- noRsaHashedImportParams :: Maybe RsaHashedImportParams
- gTypeRsaHashedImportParams :: JSM GType
- newtype RsaHashedKeyGenParams = RsaHashedKeyGenParams {}
- noRsaHashedKeyGenParams :: Maybe RsaHashedKeyGenParams
- gTypeRsaHashedKeyGenParams :: JSM GType
- newtype RsaKeyGenParams = RsaKeyGenParams {}
- class (IsCryptoAlgorithmParameters o, IsGObject o) => IsRsaKeyGenParams o
- toRsaKeyGenParams :: IsRsaKeyGenParams o => o -> RsaKeyGenParams
- noRsaKeyGenParams :: Maybe RsaKeyGenParams
- gTypeRsaKeyGenParams :: JSM GType
- newtype RsaOaepParams = RsaOaepParams {}
- noRsaOaepParams :: Maybe RsaOaepParams
- gTypeRsaOaepParams :: JSM GType
- newtype RsaOtherPrimesInfo = RsaOtherPrimesInfo {}
- noRsaOtherPrimesInfo :: Maybe RsaOtherPrimesInfo
- gTypeRsaOtherPrimesInfo :: JSM GType
- newtype SQLError = SQLError {
- unSQLError :: JSVal
- noSQLError :: Maybe SQLError
- gTypeSQLError :: JSM GType
- newtype SQLException = SQLException {}
- noSQLException :: Maybe SQLException
- gTypeSQLException :: JSM GType
- newtype SQLResultSet = SQLResultSet {}
- noSQLResultSet :: Maybe SQLResultSet
- gTypeSQLResultSet :: JSM GType
- newtype SQLResultSetRowList = SQLResultSetRowList {}
- noSQLResultSetRowList :: Maybe SQLResultSetRowList
- gTypeSQLResultSetRowList :: JSM GType
- newtype SQLTransaction = SQLTransaction {}
- noSQLTransaction :: Maybe SQLTransaction
- gTypeSQLTransaction :: JSM GType
- newtype SVGAElement = SVGAElement {}
- noSVGAElement :: Maybe SVGAElement
- gTypeSVGAElement :: JSM GType
- newtype SVGAltGlyphDefElement = SVGAltGlyphDefElement {}
- noSVGAltGlyphDefElement :: Maybe SVGAltGlyphDefElement
- gTypeSVGAltGlyphDefElement :: JSM GType
- newtype SVGAltGlyphElement = SVGAltGlyphElement {}
- noSVGAltGlyphElement :: Maybe SVGAltGlyphElement
- gTypeSVGAltGlyphElement :: JSM GType
- newtype SVGAltGlyphItemElement = SVGAltGlyphItemElement {}
- noSVGAltGlyphItemElement :: Maybe SVGAltGlyphItemElement
- gTypeSVGAltGlyphItemElement :: JSM GType
- newtype SVGAngle = SVGAngle {
- unSVGAngle :: JSVal
- noSVGAngle :: Maybe SVGAngle
- gTypeSVGAngle :: JSM GType
- newtype SVGAnimateColorElement = SVGAnimateColorElement {}
- noSVGAnimateColorElement :: Maybe SVGAnimateColorElement
- gTypeSVGAnimateColorElement :: JSM GType
- newtype SVGAnimateElement = SVGAnimateElement {}
- noSVGAnimateElement :: Maybe SVGAnimateElement
- gTypeSVGAnimateElement :: JSM GType
- newtype SVGAnimateMotionElement = SVGAnimateMotionElement {}
- noSVGAnimateMotionElement :: Maybe SVGAnimateMotionElement
- gTypeSVGAnimateMotionElement :: JSM GType
- newtype SVGAnimateTransformElement = SVGAnimateTransformElement {}
- noSVGAnimateTransformElement :: Maybe SVGAnimateTransformElement
- gTypeSVGAnimateTransformElement :: JSM GType
- newtype SVGAnimatedAngle = SVGAnimatedAngle {}
- noSVGAnimatedAngle :: Maybe SVGAnimatedAngle
- gTypeSVGAnimatedAngle :: JSM GType
- newtype SVGAnimatedBoolean = SVGAnimatedBoolean {}
- noSVGAnimatedBoolean :: Maybe SVGAnimatedBoolean
- gTypeSVGAnimatedBoolean :: JSM GType
- newtype SVGAnimatedEnumeration = SVGAnimatedEnumeration {}
- noSVGAnimatedEnumeration :: Maybe SVGAnimatedEnumeration
- gTypeSVGAnimatedEnumeration :: JSM GType
- newtype SVGAnimatedInteger = SVGAnimatedInteger {}
- noSVGAnimatedInteger :: Maybe SVGAnimatedInteger
- gTypeSVGAnimatedInteger :: JSM GType
- newtype SVGAnimatedLength = SVGAnimatedLength {}
- noSVGAnimatedLength :: Maybe SVGAnimatedLength
- gTypeSVGAnimatedLength :: JSM GType
- newtype SVGAnimatedLengthList = SVGAnimatedLengthList {}
- noSVGAnimatedLengthList :: Maybe SVGAnimatedLengthList
- gTypeSVGAnimatedLengthList :: JSM GType
- newtype SVGAnimatedNumber = SVGAnimatedNumber {}
- noSVGAnimatedNumber :: Maybe SVGAnimatedNumber
- gTypeSVGAnimatedNumber :: JSM GType
- newtype SVGAnimatedNumberList = SVGAnimatedNumberList {}
- noSVGAnimatedNumberList :: Maybe SVGAnimatedNumberList
- gTypeSVGAnimatedNumberList :: JSM GType
- newtype SVGAnimatedPreserveAspectRatio = SVGAnimatedPreserveAspectRatio {}
- noSVGAnimatedPreserveAspectRatio :: Maybe SVGAnimatedPreserveAspectRatio
- gTypeSVGAnimatedPreserveAspectRatio :: JSM GType
- newtype SVGAnimatedRect = SVGAnimatedRect {}
- noSVGAnimatedRect :: Maybe SVGAnimatedRect
- gTypeSVGAnimatedRect :: JSM GType
- newtype SVGAnimatedString = SVGAnimatedString {}
- noSVGAnimatedString :: Maybe SVGAnimatedString
- gTypeSVGAnimatedString :: JSM GType
- newtype SVGAnimatedTransformList = SVGAnimatedTransformList {}
- noSVGAnimatedTransformList :: Maybe SVGAnimatedTransformList
- gTypeSVGAnimatedTransformList :: JSM GType
- newtype SVGAnimationElement = SVGAnimationElement {}
- 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
- noSVGAnimationElement :: Maybe SVGAnimationElement
- gTypeSVGAnimationElement :: JSM GType
- newtype SVGCircleElement = SVGCircleElement {}
- noSVGCircleElement :: Maybe SVGCircleElement
- gTypeSVGCircleElement :: JSM GType
- newtype SVGClipPathElement = SVGClipPathElement {}
- noSVGClipPathElement :: Maybe SVGClipPathElement
- gTypeSVGClipPathElement :: JSM GType
- newtype SVGComponentTransferFunctionElement = SVGComponentTransferFunctionElement {}
- 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
- noSVGComponentTransferFunctionElement :: Maybe SVGComponentTransferFunctionElement
- gTypeSVGComponentTransferFunctionElement :: JSM GType
- newtype SVGCursorElement = SVGCursorElement {}
- noSVGCursorElement :: Maybe SVGCursorElement
- gTypeSVGCursorElement :: JSM GType
- newtype SVGDefsElement = SVGDefsElement {}
- noSVGDefsElement :: Maybe SVGDefsElement
- gTypeSVGDefsElement :: JSM GType
- newtype SVGDescElement = SVGDescElement {}
- noSVGDescElement :: Maybe SVGDescElement
- gTypeSVGDescElement :: JSM GType
- newtype SVGElement = SVGElement {}
- 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
- noSVGElement :: Maybe SVGElement
- gTypeSVGElement :: JSM GType
- newtype SVGEllipseElement = SVGEllipseElement {}
- noSVGEllipseElement :: Maybe SVGEllipseElement
- gTypeSVGEllipseElement :: JSM GType
- newtype SVGException = SVGException {}
- noSVGException :: Maybe SVGException
- gTypeSVGException :: JSM GType
- newtype SVGExternalResourcesRequired = SVGExternalResourcesRequired {}
- class IsGObject o => IsSVGExternalResourcesRequired o
- toSVGExternalResourcesRequired :: IsSVGExternalResourcesRequired o => o -> SVGExternalResourcesRequired
- noSVGExternalResourcesRequired :: Maybe SVGExternalResourcesRequired
- gTypeSVGExternalResourcesRequired :: JSM GType
- newtype SVGFEBlendElement = SVGFEBlendElement {}
- noSVGFEBlendElement :: Maybe SVGFEBlendElement
- gTypeSVGFEBlendElement :: JSM GType
- newtype SVGFEColorMatrixElement = SVGFEColorMatrixElement {}
- noSVGFEColorMatrixElement :: Maybe SVGFEColorMatrixElement
- gTypeSVGFEColorMatrixElement :: JSM GType
- newtype SVGFEComponentTransferElement = SVGFEComponentTransferElement {}
- noSVGFEComponentTransferElement :: Maybe SVGFEComponentTransferElement
- gTypeSVGFEComponentTransferElement :: JSM GType
- newtype SVGFECompositeElement = SVGFECompositeElement {}
- noSVGFECompositeElement :: Maybe SVGFECompositeElement
- gTypeSVGFECompositeElement :: JSM GType
- newtype SVGFEConvolveMatrixElement = SVGFEConvolveMatrixElement {}
- noSVGFEConvolveMatrixElement :: Maybe SVGFEConvolveMatrixElement
- gTypeSVGFEConvolveMatrixElement :: JSM GType
- newtype SVGFEDiffuseLightingElement = SVGFEDiffuseLightingElement {}
- noSVGFEDiffuseLightingElement :: Maybe SVGFEDiffuseLightingElement
- gTypeSVGFEDiffuseLightingElement :: JSM GType
- newtype SVGFEDisplacementMapElement = SVGFEDisplacementMapElement {}
- noSVGFEDisplacementMapElement :: Maybe SVGFEDisplacementMapElement
- gTypeSVGFEDisplacementMapElement :: JSM GType
- newtype SVGFEDistantLightElement = SVGFEDistantLightElement {}
- noSVGFEDistantLightElement :: Maybe SVGFEDistantLightElement
- gTypeSVGFEDistantLightElement :: JSM GType
- newtype SVGFEDropShadowElement = SVGFEDropShadowElement {}
- noSVGFEDropShadowElement :: Maybe SVGFEDropShadowElement
- gTypeSVGFEDropShadowElement :: JSM GType
- newtype SVGFEFloodElement = SVGFEFloodElement {}
- noSVGFEFloodElement :: Maybe SVGFEFloodElement
- gTypeSVGFEFloodElement :: JSM GType
- newtype SVGFEFuncAElement = SVGFEFuncAElement {}
- noSVGFEFuncAElement :: Maybe SVGFEFuncAElement
- gTypeSVGFEFuncAElement :: JSM GType
- newtype SVGFEFuncBElement = SVGFEFuncBElement {}
- noSVGFEFuncBElement :: Maybe SVGFEFuncBElement
- gTypeSVGFEFuncBElement :: JSM GType
- newtype SVGFEFuncGElement = SVGFEFuncGElement {}
- noSVGFEFuncGElement :: Maybe SVGFEFuncGElement
- gTypeSVGFEFuncGElement :: JSM GType
- newtype SVGFEFuncRElement = SVGFEFuncRElement {}
- noSVGFEFuncRElement :: Maybe SVGFEFuncRElement
- gTypeSVGFEFuncRElement :: JSM GType
- newtype SVGFEGaussianBlurElement = SVGFEGaussianBlurElement {}
- noSVGFEGaussianBlurElement :: Maybe SVGFEGaussianBlurElement
- gTypeSVGFEGaussianBlurElement :: JSM GType
- newtype SVGFEImageElement = SVGFEImageElement {}
- noSVGFEImageElement :: Maybe SVGFEImageElement
- gTypeSVGFEImageElement :: JSM GType
- newtype SVGFEMergeElement = SVGFEMergeElement {}
- noSVGFEMergeElement :: Maybe SVGFEMergeElement
- gTypeSVGFEMergeElement :: JSM GType
- newtype SVGFEMergeNodeElement = SVGFEMergeNodeElement {}
- noSVGFEMergeNodeElement :: Maybe SVGFEMergeNodeElement
- gTypeSVGFEMergeNodeElement :: JSM GType
- newtype SVGFEMorphologyElement = SVGFEMorphologyElement {}
- noSVGFEMorphologyElement :: Maybe SVGFEMorphologyElement
- gTypeSVGFEMorphologyElement :: JSM GType
- newtype SVGFEOffsetElement = SVGFEOffsetElement {}
- noSVGFEOffsetElement :: Maybe SVGFEOffsetElement
- gTypeSVGFEOffsetElement :: JSM GType
- newtype SVGFEPointLightElement = SVGFEPointLightElement {}
- noSVGFEPointLightElement :: Maybe SVGFEPointLightElement
- gTypeSVGFEPointLightElement :: JSM GType
- newtype SVGFESpecularLightingElement = SVGFESpecularLightingElement {}
- noSVGFESpecularLightingElement :: Maybe SVGFESpecularLightingElement
- gTypeSVGFESpecularLightingElement :: JSM GType
- newtype SVGFESpotLightElement = SVGFESpotLightElement {}
- noSVGFESpotLightElement :: Maybe SVGFESpotLightElement
- gTypeSVGFESpotLightElement :: JSM GType
- newtype SVGFETileElement = SVGFETileElement {}
- noSVGFETileElement :: Maybe SVGFETileElement
- gTypeSVGFETileElement :: JSM GType
- newtype SVGFETurbulenceElement = SVGFETurbulenceElement {}
- noSVGFETurbulenceElement :: Maybe SVGFETurbulenceElement
- gTypeSVGFETurbulenceElement :: JSM GType
- newtype SVGFilterElement = SVGFilterElement {}
- noSVGFilterElement :: Maybe SVGFilterElement
- gTypeSVGFilterElement :: JSM GType
- newtype SVGFilterPrimitiveStandardAttributes = SVGFilterPrimitiveStandardAttributes {}
- class IsGObject o => IsSVGFilterPrimitiveStandardAttributes o
- toSVGFilterPrimitiveStandardAttributes :: IsSVGFilterPrimitiveStandardAttributes o => o -> SVGFilterPrimitiveStandardAttributes
- noSVGFilterPrimitiveStandardAttributes :: Maybe SVGFilterPrimitiveStandardAttributes
- gTypeSVGFilterPrimitiveStandardAttributes :: JSM GType
- newtype SVGFitToViewBox = SVGFitToViewBox {}
- class IsGObject o => IsSVGFitToViewBox o
- toSVGFitToViewBox :: IsSVGFitToViewBox o => o -> SVGFitToViewBox
- noSVGFitToViewBox :: Maybe SVGFitToViewBox
- gTypeSVGFitToViewBox :: JSM GType
- newtype SVGFontElement = SVGFontElement {}
- noSVGFontElement :: Maybe SVGFontElement
- gTypeSVGFontElement :: JSM GType
- newtype SVGFontFaceElement = SVGFontFaceElement {}
- noSVGFontFaceElement :: Maybe SVGFontFaceElement
- gTypeSVGFontFaceElement :: JSM GType
- newtype SVGFontFaceFormatElement = SVGFontFaceFormatElement {}
- noSVGFontFaceFormatElement :: Maybe SVGFontFaceFormatElement
- gTypeSVGFontFaceFormatElement :: JSM GType
- newtype SVGFontFaceNameElement = SVGFontFaceNameElement {}
- noSVGFontFaceNameElement :: Maybe SVGFontFaceNameElement
- gTypeSVGFontFaceNameElement :: JSM GType
- newtype SVGFontFaceSrcElement = SVGFontFaceSrcElement {}
- noSVGFontFaceSrcElement :: Maybe SVGFontFaceSrcElement
- gTypeSVGFontFaceSrcElement :: JSM GType
- newtype SVGFontFaceUriElement = SVGFontFaceUriElement {}
- noSVGFontFaceUriElement :: Maybe SVGFontFaceUriElement
- gTypeSVGFontFaceUriElement :: JSM GType
- newtype SVGForeignObjectElement = SVGForeignObjectElement {}
- noSVGForeignObjectElement :: Maybe SVGForeignObjectElement
- gTypeSVGForeignObjectElement :: JSM GType
- newtype SVGGElement = SVGGElement {}
- noSVGGElement :: Maybe SVGGElement
- gTypeSVGGElement :: JSM GType
- newtype SVGGlyphElement = SVGGlyphElement {}
- noSVGGlyphElement :: Maybe SVGGlyphElement
- gTypeSVGGlyphElement :: JSM GType
- newtype SVGGlyphRefElement = SVGGlyphRefElement {}
- noSVGGlyphRefElement :: Maybe SVGGlyphRefElement
- gTypeSVGGlyphRefElement :: JSM GType
- newtype SVGGradientElement = SVGGradientElement {}
- 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
- noSVGGradientElement :: Maybe SVGGradientElement
- gTypeSVGGradientElement :: JSM GType
- newtype SVGGraphicsElement = SVGGraphicsElement {}
- 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
- noSVGGraphicsElement :: Maybe SVGGraphicsElement
- gTypeSVGGraphicsElement :: JSM GType
- newtype SVGHKernElement = SVGHKernElement {}
- noSVGHKernElement :: Maybe SVGHKernElement
- gTypeSVGHKernElement :: JSM GType
- newtype SVGImageElement = SVGImageElement {}
- noSVGImageElement :: Maybe SVGImageElement
- gTypeSVGImageElement :: JSM GType
- newtype SVGLength = SVGLength {
- unSVGLength :: JSVal
- noSVGLength :: Maybe SVGLength
- gTypeSVGLength :: JSM GType
- newtype SVGLengthList = SVGLengthList {}
- noSVGLengthList :: Maybe SVGLengthList
- gTypeSVGLengthList :: JSM GType
- newtype SVGLineElement = SVGLineElement {}
- noSVGLineElement :: Maybe SVGLineElement
- gTypeSVGLineElement :: JSM GType
- newtype SVGLinearGradientElement = SVGLinearGradientElement {}
- noSVGLinearGradientElement :: Maybe SVGLinearGradientElement
- gTypeSVGLinearGradientElement :: JSM GType
- newtype SVGMPathElement = SVGMPathElement {}
- noSVGMPathElement :: Maybe SVGMPathElement
- gTypeSVGMPathElement :: JSM GType
- newtype SVGMarkerElement = SVGMarkerElement {}
- noSVGMarkerElement :: Maybe SVGMarkerElement
- gTypeSVGMarkerElement :: JSM GType
- newtype SVGMaskElement = SVGMaskElement {}
- noSVGMaskElement :: Maybe SVGMaskElement
- gTypeSVGMaskElement :: JSM GType
- newtype SVGMatrix = SVGMatrix {
- unSVGMatrix :: JSVal
- noSVGMatrix :: Maybe SVGMatrix
- gTypeSVGMatrix :: JSM GType
- newtype SVGMetadataElement = SVGMetadataElement {}
- noSVGMetadataElement :: Maybe SVGMetadataElement
- gTypeSVGMetadataElement :: JSM GType
- newtype SVGMissingGlyphElement = SVGMissingGlyphElement {}
- noSVGMissingGlyphElement :: Maybe SVGMissingGlyphElement
- gTypeSVGMissingGlyphElement :: JSM GType
- newtype SVGNumber = SVGNumber {
- unSVGNumber :: JSVal
- noSVGNumber :: Maybe SVGNumber
- gTypeSVGNumber :: JSM GType
- newtype SVGNumberList = SVGNumberList {}
- noSVGNumberList :: Maybe SVGNumberList
- gTypeSVGNumberList :: JSM GType
- newtype SVGPathElement = SVGPathElement {}
- noSVGPathElement :: Maybe SVGPathElement
- gTypeSVGPathElement :: JSM GType
- newtype SVGPathSeg = SVGPathSeg {}
- class IsGObject o => IsSVGPathSeg o
- toSVGPathSeg :: IsSVGPathSeg o => o -> SVGPathSeg
- noSVGPathSeg :: Maybe SVGPathSeg
- gTypeSVGPathSeg :: JSM GType
- newtype SVGPathSegArcAbs = SVGPathSegArcAbs {}
- noSVGPathSegArcAbs :: Maybe SVGPathSegArcAbs
- gTypeSVGPathSegArcAbs :: JSM GType
- newtype SVGPathSegArcRel = SVGPathSegArcRel {}
- noSVGPathSegArcRel :: Maybe SVGPathSegArcRel
- gTypeSVGPathSegArcRel :: JSM GType
- newtype SVGPathSegClosePath = SVGPathSegClosePath {}
- noSVGPathSegClosePath :: Maybe SVGPathSegClosePath
- gTypeSVGPathSegClosePath :: JSM GType
- newtype SVGPathSegCurvetoCubicAbs = SVGPathSegCurvetoCubicAbs {}
- noSVGPathSegCurvetoCubicAbs :: Maybe SVGPathSegCurvetoCubicAbs
- gTypeSVGPathSegCurvetoCubicAbs :: JSM GType
- newtype SVGPathSegCurvetoCubicRel = SVGPathSegCurvetoCubicRel {}
- noSVGPathSegCurvetoCubicRel :: Maybe SVGPathSegCurvetoCubicRel
- gTypeSVGPathSegCurvetoCubicRel :: JSM GType
- newtype SVGPathSegCurvetoCubicSmoothAbs = SVGPathSegCurvetoCubicSmoothAbs {}
- noSVGPathSegCurvetoCubicSmoothAbs :: Maybe SVGPathSegCurvetoCubicSmoothAbs
- gTypeSVGPathSegCurvetoCubicSmoothAbs :: JSM GType
- newtype SVGPathSegCurvetoCubicSmoothRel = SVGPathSegCurvetoCubicSmoothRel {}
- noSVGPathSegCurvetoCubicSmoothRel :: Maybe SVGPathSegCurvetoCubicSmoothRel
- gTypeSVGPathSegCurvetoCubicSmoothRel :: JSM GType
- newtype SVGPathSegCurvetoQuadraticAbs = SVGPathSegCurvetoQuadraticAbs {}
- noSVGPathSegCurvetoQuadraticAbs :: Maybe SVGPathSegCurvetoQuadraticAbs
- gTypeSVGPathSegCurvetoQuadraticAbs :: JSM GType
- newtype SVGPathSegCurvetoQuadraticRel = SVGPathSegCurvetoQuadraticRel {}
- noSVGPathSegCurvetoQuadraticRel :: Maybe SVGPathSegCurvetoQuadraticRel
- gTypeSVGPathSegCurvetoQuadraticRel :: JSM GType
- newtype SVGPathSegCurvetoQuadraticSmoothAbs = SVGPathSegCurvetoQuadraticSmoothAbs {}
- noSVGPathSegCurvetoQuadraticSmoothAbs :: Maybe SVGPathSegCurvetoQuadraticSmoothAbs
- gTypeSVGPathSegCurvetoQuadraticSmoothAbs :: JSM GType
- newtype SVGPathSegCurvetoQuadraticSmoothRel = SVGPathSegCurvetoQuadraticSmoothRel {}
- noSVGPathSegCurvetoQuadraticSmoothRel :: Maybe SVGPathSegCurvetoQuadraticSmoothRel
- gTypeSVGPathSegCurvetoQuadraticSmoothRel :: JSM GType
- newtype SVGPathSegLinetoAbs = SVGPathSegLinetoAbs {}
- noSVGPathSegLinetoAbs :: Maybe SVGPathSegLinetoAbs
- gTypeSVGPathSegLinetoAbs :: JSM GType
- newtype SVGPathSegLinetoHorizontalAbs = SVGPathSegLinetoHorizontalAbs {}
- noSVGPathSegLinetoHorizontalAbs :: Maybe SVGPathSegLinetoHorizontalAbs
- gTypeSVGPathSegLinetoHorizontalAbs :: JSM GType
- newtype SVGPathSegLinetoHorizontalRel = SVGPathSegLinetoHorizontalRel {}
- noSVGPathSegLinetoHorizontalRel :: Maybe SVGPathSegLinetoHorizontalRel
- gTypeSVGPathSegLinetoHorizontalRel :: JSM GType
- newtype SVGPathSegLinetoRel = SVGPathSegLinetoRel {}
- noSVGPathSegLinetoRel :: Maybe SVGPathSegLinetoRel
- gTypeSVGPathSegLinetoRel :: JSM GType
- newtype SVGPathSegLinetoVerticalAbs = SVGPathSegLinetoVerticalAbs {}
- noSVGPathSegLinetoVerticalAbs :: Maybe SVGPathSegLinetoVerticalAbs
- gTypeSVGPathSegLinetoVerticalAbs :: JSM GType
- newtype SVGPathSegLinetoVerticalRel = SVGPathSegLinetoVerticalRel {}
- noSVGPathSegLinetoVerticalRel :: Maybe SVGPathSegLinetoVerticalRel
- gTypeSVGPathSegLinetoVerticalRel :: JSM GType
- newtype SVGPathSegList = SVGPathSegList {}
- noSVGPathSegList :: Maybe SVGPathSegList
- gTypeSVGPathSegList :: JSM GType
- newtype SVGPathSegMovetoAbs = SVGPathSegMovetoAbs {}
- noSVGPathSegMovetoAbs :: Maybe SVGPathSegMovetoAbs
- gTypeSVGPathSegMovetoAbs :: JSM GType
- newtype SVGPathSegMovetoRel = SVGPathSegMovetoRel {}
- noSVGPathSegMovetoRel :: Maybe SVGPathSegMovetoRel
- gTypeSVGPathSegMovetoRel :: JSM GType
- newtype SVGPatternElement = SVGPatternElement {}
- noSVGPatternElement :: Maybe SVGPatternElement
- gTypeSVGPatternElement :: JSM GType
- newtype SVGPoint = SVGPoint {
- unSVGPoint :: JSVal
- noSVGPoint :: Maybe SVGPoint
- gTypeSVGPoint :: JSM GType
- newtype SVGPointList = SVGPointList {}
- noSVGPointList :: Maybe SVGPointList
- gTypeSVGPointList :: JSM GType
- newtype SVGPolygonElement = SVGPolygonElement {}
- noSVGPolygonElement :: Maybe SVGPolygonElement
- gTypeSVGPolygonElement :: JSM GType
- newtype SVGPolylineElement = SVGPolylineElement {}
- noSVGPolylineElement :: Maybe SVGPolylineElement
- gTypeSVGPolylineElement :: JSM GType
- newtype SVGPreserveAspectRatio = SVGPreserveAspectRatio {}
- noSVGPreserveAspectRatio :: Maybe SVGPreserveAspectRatio
- gTypeSVGPreserveAspectRatio :: JSM GType
- newtype SVGRadialGradientElement = SVGRadialGradientElement {}
- noSVGRadialGradientElement :: Maybe SVGRadialGradientElement
- gTypeSVGRadialGradientElement :: JSM GType
- newtype SVGRect = SVGRect {}
- noSVGRect :: Maybe SVGRect
- gTypeSVGRect :: JSM GType
- newtype SVGRectElement = SVGRectElement {}
- noSVGRectElement :: Maybe SVGRectElement
- gTypeSVGRectElement :: JSM GType
- newtype SVGRenderingIntent = SVGRenderingIntent {}
- noSVGRenderingIntent :: Maybe SVGRenderingIntent
- gTypeSVGRenderingIntent :: JSM GType
- newtype SVGSVGElement = SVGSVGElement {}
- noSVGSVGElement :: Maybe SVGSVGElement
- gTypeSVGSVGElement :: JSM GType
- newtype SVGScriptElement = SVGScriptElement {}
- noSVGScriptElement :: Maybe SVGScriptElement
- gTypeSVGScriptElement :: JSM GType
- newtype SVGSetElement = SVGSetElement {}
- noSVGSetElement :: Maybe SVGSetElement
- gTypeSVGSetElement :: JSM GType
- newtype SVGStopElement = SVGStopElement {}
- noSVGStopElement :: Maybe SVGStopElement
- gTypeSVGStopElement :: JSM GType
- newtype SVGStringList = SVGStringList {}
- noSVGStringList :: Maybe SVGStringList
- gTypeSVGStringList :: JSM GType
- newtype SVGStyleElement = SVGStyleElement {}
- noSVGStyleElement :: Maybe SVGStyleElement
- gTypeSVGStyleElement :: JSM GType
- newtype SVGSwitchElement = SVGSwitchElement {}
- noSVGSwitchElement :: Maybe SVGSwitchElement
- gTypeSVGSwitchElement :: JSM GType
- newtype SVGSymbolElement = SVGSymbolElement {}
- noSVGSymbolElement :: Maybe SVGSymbolElement
- gTypeSVGSymbolElement :: JSM GType
- newtype SVGTRefElement = SVGTRefElement {}
- noSVGTRefElement :: Maybe SVGTRefElement
- gTypeSVGTRefElement :: JSM GType
- newtype SVGTSpanElement = SVGTSpanElement {}
- noSVGTSpanElement :: Maybe SVGTSpanElement
- gTypeSVGTSpanElement :: JSM GType
- newtype SVGTests = SVGTests {
- unSVGTests :: JSVal
- class IsGObject o => IsSVGTests o
- toSVGTests :: IsSVGTests o => o -> SVGTests
- noSVGTests :: Maybe SVGTests
- gTypeSVGTests :: JSM GType
- newtype SVGTextContentElement = SVGTextContentElement {}
- 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
- noSVGTextContentElement :: Maybe SVGTextContentElement
- gTypeSVGTextContentElement :: JSM GType
- newtype SVGTextElement = SVGTextElement {}
- noSVGTextElement :: Maybe SVGTextElement
- gTypeSVGTextElement :: JSM GType
- newtype SVGTextPathElement = SVGTextPathElement {}
- noSVGTextPathElement :: Maybe SVGTextPathElement
- gTypeSVGTextPathElement :: JSM GType
- newtype SVGTextPositioningElement = SVGTextPositioningElement {}
- 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
- noSVGTextPositioningElement :: Maybe SVGTextPositioningElement
- gTypeSVGTextPositioningElement :: JSM GType
- newtype SVGTitleElement = SVGTitleElement {}
- noSVGTitleElement :: Maybe SVGTitleElement
- gTypeSVGTitleElement :: JSM GType
- newtype SVGTransform = SVGTransform {}
- noSVGTransform :: Maybe SVGTransform
- gTypeSVGTransform :: JSM GType
- newtype SVGTransformList = SVGTransformList {}
- noSVGTransformList :: Maybe SVGTransformList
- gTypeSVGTransformList :: JSM GType
- newtype SVGURIReference = SVGURIReference {}
- class IsGObject o => IsSVGURIReference o
- toSVGURIReference :: IsSVGURIReference o => o -> SVGURIReference
- noSVGURIReference :: Maybe SVGURIReference
- gTypeSVGURIReference :: JSM GType
- newtype SVGUnitTypes = SVGUnitTypes {}
- noSVGUnitTypes :: Maybe SVGUnitTypes
- gTypeSVGUnitTypes :: JSM GType
- newtype SVGUseElement = SVGUseElement {}
- noSVGUseElement :: Maybe SVGUseElement
- gTypeSVGUseElement :: JSM GType
- newtype SVGVKernElement = SVGVKernElement {}
- noSVGVKernElement :: Maybe SVGVKernElement
- gTypeSVGVKernElement :: JSM GType
- newtype SVGViewElement = SVGViewElement {}
- noSVGViewElement :: Maybe SVGViewElement
- gTypeSVGViewElement :: JSM GType
- newtype SVGViewSpec = SVGViewSpec {}
- noSVGViewSpec :: Maybe SVGViewSpec
- gTypeSVGViewSpec :: JSM GType
- newtype SVGZoomAndPan = SVGZoomAndPan {}
- class IsGObject o => IsSVGZoomAndPan o
- toSVGZoomAndPan :: IsSVGZoomAndPan o => o -> SVGZoomAndPan
- noSVGZoomAndPan :: Maybe SVGZoomAndPan
- gTypeSVGZoomAndPan :: JSM GType
- newtype SVGZoomEvent = SVGZoomEvent {}
- noSVGZoomEvent :: Maybe SVGZoomEvent
- gTypeSVGZoomEvent :: JSM GType
- newtype Screen = Screen {}
- noScreen :: Maybe Screen
- gTypeScreen :: JSM GType
- newtype ScriptProcessorNode = ScriptProcessorNode {}
- noScriptProcessorNode :: Maybe ScriptProcessorNode
- gTypeScriptProcessorNode :: JSM GType
- newtype ScrollToOptions = ScrollToOptions {}
- noScrollToOptions :: Maybe ScrollToOptions
- gTypeScrollToOptions :: JSM GType
- newtype SecurityPolicyViolationEvent = SecurityPolicyViolationEvent {}
- noSecurityPolicyViolationEvent :: Maybe SecurityPolicyViolationEvent
- gTypeSecurityPolicyViolationEvent :: JSM GType
- newtype SecurityPolicyViolationEventInit = SecurityPolicyViolationEventInit {}
- noSecurityPolicyViolationEventInit :: Maybe SecurityPolicyViolationEventInit
- gTypeSecurityPolicyViolationEventInit :: JSM GType
- newtype Selection = Selection {
- unSelection :: JSVal
- noSelection :: Maybe Selection
- gTypeSelection :: JSM GType
- newtype ShadowRoot = ShadowRoot {}
- noShadowRoot :: Maybe ShadowRoot
- gTypeShadowRoot :: JSM GType
- newtype ShadowRootInit = ShadowRootInit {}
- noShadowRootInit :: Maybe ShadowRootInit
- gTypeShadowRootInit :: JSM GType
- newtype SiteBoundCredential = SiteBoundCredential {}
- class (IsBasicCredential o, IsGObject o) => IsSiteBoundCredential o
- toSiteBoundCredential :: IsSiteBoundCredential o => o -> SiteBoundCredential
- noSiteBoundCredential :: Maybe SiteBoundCredential
- gTypeSiteBoundCredential :: JSM GType
- newtype SiteBoundCredentialData = SiteBoundCredentialData {}
- class (IsCredentialData o, IsGObject o) => IsSiteBoundCredentialData o
- toSiteBoundCredentialData :: IsSiteBoundCredentialData o => o -> SiteBoundCredentialData
- noSiteBoundCredentialData :: Maybe SiteBoundCredentialData
- gTypeSiteBoundCredentialData :: JSM GType
- newtype Slotable = Slotable {
- unSlotable :: JSVal
- class IsGObject o => IsSlotable o
- toSlotable :: IsSlotable o => o -> Slotable
- noSlotable :: Maybe Slotable
- gTypeSlotable :: JSM GType
- newtype SourceBuffer = SourceBuffer {}
- noSourceBuffer :: Maybe SourceBuffer
- gTypeSourceBuffer :: JSM GType
- newtype SourceBufferList = SourceBufferList {}
- noSourceBufferList :: Maybe SourceBufferList
- gTypeSourceBufferList :: JSM GType
- newtype SpeechSynthesis = SpeechSynthesis {}
- noSpeechSynthesis :: Maybe SpeechSynthesis
- gTypeSpeechSynthesis :: JSM GType
- newtype SpeechSynthesisEvent = SpeechSynthesisEvent {}
- noSpeechSynthesisEvent :: Maybe SpeechSynthesisEvent
- gTypeSpeechSynthesisEvent :: JSM GType
- newtype SpeechSynthesisUtterance = SpeechSynthesisUtterance {}
- noSpeechSynthesisUtterance :: Maybe SpeechSynthesisUtterance
- gTypeSpeechSynthesisUtterance :: JSM GType
- newtype SpeechSynthesisVoice = SpeechSynthesisVoice {}
- noSpeechSynthesisVoice :: Maybe SpeechSynthesisVoice
- gTypeSpeechSynthesisVoice :: JSM GType
- newtype StaticRange = StaticRange {}
- noStaticRange :: Maybe StaticRange
- gTypeStaticRange :: JSM GType
- newtype Storage = Storage {}
- noStorage :: Maybe Storage
- gTypeStorage :: JSM GType
- newtype StorageEvent = StorageEvent {}
- noStorageEvent :: Maybe StorageEvent
- gTypeStorageEvent :: JSM GType
- newtype StorageEventInit = StorageEventInit {}
- noStorageEventInit :: Maybe StorageEventInit
- gTypeStorageEventInit :: JSM GType
- newtype StorageInfo = StorageInfo {}
- noStorageInfo :: Maybe StorageInfo
- gTypeStorageInfo :: JSM GType
- newtype StorageQuota = StorageQuota {}
- noStorageQuota :: Maybe StorageQuota
- gTypeStorageQuota :: JSM GType
- newtype StyleMedia = StyleMedia {}
- noStyleMedia :: Maybe StyleMedia
- gTypeStyleMedia :: JSM GType
- newtype StyleSheet = StyleSheet {}
- class IsGObject o => IsStyleSheet o
- toStyleSheet :: IsStyleSheet o => o -> StyleSheet
- noStyleSheet :: Maybe StyleSheet
- gTypeStyleSheet :: JSM GType
- newtype StyleSheetList = StyleSheetList {}
- noStyleSheetList :: Maybe StyleSheetList
- gTypeStyleSheetList :: JSM GType
- newtype SubtleCrypto = SubtleCrypto {}
- noSubtleCrypto :: Maybe SubtleCrypto
- gTypeSubtleCrypto :: JSM GType
- newtype Text = Text {}
- class (IsCharacterData o, IsNode o, IsEventTarget o, IsNonDocumentTypeChildNode o, IsChildNode o, IsSlotable o, IsGObject o) => IsText o
- toText :: IsText o => o -> Text
- noText :: Maybe Text
- gTypeText :: JSM GType
- newtype TextDecodeOptions = TextDecodeOptions {}
- noTextDecodeOptions :: Maybe TextDecodeOptions
- gTypeTextDecodeOptions :: JSM GType
- newtype TextDecoder = TextDecoder {}
- noTextDecoder :: Maybe TextDecoder
- gTypeTextDecoder :: JSM GType
- newtype TextDecoderOptions = TextDecoderOptions {}
- noTextDecoderOptions :: Maybe TextDecoderOptions
- gTypeTextDecoderOptions :: JSM GType
- newtype TextEncoder = TextEncoder {}
- noTextEncoder :: Maybe TextEncoder
- gTypeTextEncoder :: JSM GType
- newtype TextEvent = TextEvent {
- unTextEvent :: JSVal
- noTextEvent :: Maybe TextEvent
- gTypeTextEvent :: JSM GType
- newtype TextMetrics = TextMetrics {}
- noTextMetrics :: Maybe TextMetrics
- gTypeTextMetrics :: JSM GType
- newtype TextTrack = TextTrack {
- unTextTrack :: JSVal
- noTextTrack :: Maybe TextTrack
- gTypeTextTrack :: JSM GType
- newtype TextTrackCue = TextTrackCue {}
- class (IsEventTarget o, IsGObject o) => IsTextTrackCue o
- toTextTrackCue :: IsTextTrackCue o => o -> TextTrackCue
- noTextTrackCue :: Maybe TextTrackCue
- gTypeTextTrackCue :: JSM GType
- newtype TextTrackCueList = TextTrackCueList {}
- noTextTrackCueList :: Maybe TextTrackCueList
- gTypeTextTrackCueList :: JSM GType
- newtype TextTrackList = TextTrackList {}
- noTextTrackList :: Maybe TextTrackList
- gTypeTextTrackList :: JSM GType
- newtype TimeRanges = TimeRanges {}
- noTimeRanges :: Maybe TimeRanges
- gTypeTimeRanges :: JSM GType
- newtype Touch = Touch {}
- noTouch :: Maybe Touch
- gTypeTouch :: JSM GType
- newtype TouchEvent = TouchEvent {}
- noTouchEvent :: Maybe TouchEvent
- gTypeTouchEvent :: JSM GType
- newtype TouchEventInit = TouchEventInit {}
- noTouchEventInit :: Maybe TouchEventInit
- gTypeTouchEventInit :: JSM GType
- newtype TouchList = TouchList {
- unTouchList :: JSVal
- noTouchList :: Maybe TouchList
- gTypeTouchList :: JSM GType
- newtype TrackEvent = TrackEvent {}
- noTrackEvent :: Maybe TrackEvent
- gTypeTrackEvent :: JSM GType
- newtype TrackEventInit = TrackEventInit {}
- noTrackEventInit :: Maybe TrackEventInit
- gTypeTrackEventInit :: JSM GType
- newtype TransitionEvent = TransitionEvent {}
- noTransitionEvent :: Maybe TransitionEvent
- gTypeTransitionEvent :: JSM GType
- newtype TransitionEventInit = TransitionEventInit {}
- noTransitionEventInit :: Maybe TransitionEventInit
- gTypeTransitionEventInit :: JSM GType
- newtype TreeWalker = TreeWalker {}
- noTreeWalker :: Maybe TreeWalker
- gTypeTreeWalker :: JSM GType
- newtype UIEvent = UIEvent {}
- class (IsEvent o, IsGObject o) => IsUIEvent o
- toUIEvent :: IsUIEvent o => o -> UIEvent
- noUIEvent :: Maybe UIEvent
- gTypeUIEvent :: JSM GType
- newtype UIEventInit = UIEventInit {}
- class (IsEventInit o, IsGObject o) => IsUIEventInit o
- toUIEventInit :: IsUIEventInit o => o -> UIEventInit
- noUIEventInit :: Maybe UIEventInit
- gTypeUIEventInit :: JSM GType
- newtype URL = URL {}
- noURL :: Maybe URL
- gTypeURL :: JSM GType
- newtype URLSearchParams = URLSearchParams {}
- noURLSearchParams :: Maybe URLSearchParams
- gTypeURLSearchParams :: JSM GType
- newtype UserMessageHandler = UserMessageHandler {}
- noUserMessageHandler :: Maybe UserMessageHandler
- gTypeUserMessageHandler :: JSM GType
- newtype UserMessageHandlersNamespace = UserMessageHandlersNamespace {}
- noUserMessageHandlersNamespace :: Maybe UserMessageHandlersNamespace
- gTypeUserMessageHandlersNamespace :: JSM GType
- newtype VTTCue = VTTCue {}
- noVTTCue :: Maybe VTTCue
- gTypeVTTCue :: JSM GType
- newtype VTTRegion = VTTRegion {
- unVTTRegion :: JSVal
- noVTTRegion :: Maybe VTTRegion
- gTypeVTTRegion :: JSM GType
- newtype VTTRegionList = VTTRegionList {}
- noVTTRegionList :: Maybe VTTRegionList
- gTypeVTTRegionList :: JSM GType
- newtype ValidityState = ValidityState {}
- noValidityState :: Maybe ValidityState
- gTypeValidityState :: JSM GType
- newtype VideoPlaybackQuality = VideoPlaybackQuality {}
- noVideoPlaybackQuality :: Maybe VideoPlaybackQuality
- gTypeVideoPlaybackQuality :: JSM GType
- newtype VideoTrack = VideoTrack {}
- noVideoTrack :: Maybe VideoTrack
- gTypeVideoTrack :: JSM GType
- newtype VideoTrackList = VideoTrackList {}
- noVideoTrackList :: Maybe VideoTrackList
- gTypeVideoTrackList :: JSM GType
- newtype WaveShaperNode = WaveShaperNode {}
- noWaveShaperNode :: Maybe WaveShaperNode
- gTypeWaveShaperNode :: JSM GType
- newtype WebGL2RenderingContext = WebGL2RenderingContext {}
- noWebGL2RenderingContext :: Maybe WebGL2RenderingContext
- gTypeWebGL2RenderingContext :: JSM GType
- newtype WebGLActiveInfo = WebGLActiveInfo {}
- noWebGLActiveInfo :: Maybe WebGLActiveInfo
- gTypeWebGLActiveInfo :: JSM GType
- newtype WebGLBuffer = WebGLBuffer {}
- noWebGLBuffer :: Maybe WebGLBuffer
- gTypeWebGLBuffer :: JSM GType
- newtype WebGLCompressedTextureATC = WebGLCompressedTextureATC {}
- noWebGLCompressedTextureATC :: Maybe WebGLCompressedTextureATC
- gTypeWebGLCompressedTextureATC :: JSM GType
- newtype WebGLCompressedTexturePVRTC = WebGLCompressedTexturePVRTC {}
- noWebGLCompressedTexturePVRTC :: Maybe WebGLCompressedTexturePVRTC
- gTypeWebGLCompressedTexturePVRTC :: JSM GType
- newtype WebGLCompressedTextureS3TC = WebGLCompressedTextureS3TC {}
- noWebGLCompressedTextureS3TC :: Maybe WebGLCompressedTextureS3TC
- gTypeWebGLCompressedTextureS3TC :: JSM GType
- newtype WebGLContextAttributes = WebGLContextAttributes {}
- noWebGLContextAttributes :: Maybe WebGLContextAttributes
- gTypeWebGLContextAttributes :: JSM GType
- newtype WebGLContextEvent = WebGLContextEvent {}
- noWebGLContextEvent :: Maybe WebGLContextEvent
- gTypeWebGLContextEvent :: JSM GType
- newtype WebGLContextEventInit = WebGLContextEventInit {}
- noWebGLContextEventInit :: Maybe WebGLContextEventInit
- gTypeWebGLContextEventInit :: JSM GType
- newtype WebGLDebugRendererInfo = WebGLDebugRendererInfo {}
- noWebGLDebugRendererInfo :: Maybe WebGLDebugRendererInfo
- gTypeWebGLDebugRendererInfo :: JSM GType
- newtype WebGLDebugShaders = WebGLDebugShaders {}
- noWebGLDebugShaders :: Maybe WebGLDebugShaders
- gTypeWebGLDebugShaders :: JSM GType
- newtype WebGLDepthTexture = WebGLDepthTexture {}
- noWebGLDepthTexture :: Maybe WebGLDepthTexture
- gTypeWebGLDepthTexture :: JSM GType
- newtype WebGLDrawBuffers = WebGLDrawBuffers {}
- noWebGLDrawBuffers :: Maybe WebGLDrawBuffers
- gTypeWebGLDrawBuffers :: JSM GType
- newtype WebGLFramebuffer = WebGLFramebuffer {}
- noWebGLFramebuffer :: Maybe WebGLFramebuffer
- gTypeWebGLFramebuffer :: JSM GType
- newtype WebGLLoseContext = WebGLLoseContext {}
- noWebGLLoseContext :: Maybe WebGLLoseContext
- gTypeWebGLLoseContext :: JSM GType
- newtype WebGLProgram = WebGLProgram {}
- noWebGLProgram :: Maybe WebGLProgram
- gTypeWebGLProgram :: JSM GType
- newtype WebGLQuery = WebGLQuery {}
- noWebGLQuery :: Maybe WebGLQuery
- gTypeWebGLQuery :: JSM GType
- newtype WebGLRenderbuffer = WebGLRenderbuffer {}
- noWebGLRenderbuffer :: Maybe WebGLRenderbuffer
- gTypeWebGLRenderbuffer :: JSM GType
- newtype WebGLRenderingContext = WebGLRenderingContext {}
- noWebGLRenderingContext :: Maybe WebGLRenderingContext
- gTypeWebGLRenderingContext :: JSM GType
- newtype WebGLRenderingContextBase = WebGLRenderingContextBase {}
- class IsGObject o => IsWebGLRenderingContextBase o
- toWebGLRenderingContextBase :: IsWebGLRenderingContextBase o => o -> WebGLRenderingContextBase
- noWebGLRenderingContextBase :: Maybe WebGLRenderingContextBase
- gTypeWebGLRenderingContextBase :: JSM GType
- newtype WebGLSampler = WebGLSampler {}
- noWebGLSampler :: Maybe WebGLSampler
- gTypeWebGLSampler :: JSM GType
- newtype WebGLShader = WebGLShader {}
- noWebGLShader :: Maybe WebGLShader
- gTypeWebGLShader :: JSM GType
- newtype WebGLShaderPrecisionFormat = WebGLShaderPrecisionFormat {}
- noWebGLShaderPrecisionFormat :: Maybe WebGLShaderPrecisionFormat
- gTypeWebGLShaderPrecisionFormat :: JSM GType
- newtype WebGLSync = WebGLSync {
- unWebGLSync :: JSVal
- noWebGLSync :: Maybe WebGLSync
- gTypeWebGLSync :: JSM GType
- newtype WebGLTexture = WebGLTexture {}
- noWebGLTexture :: Maybe WebGLTexture
- gTypeWebGLTexture :: JSM GType
- newtype WebGLTransformFeedback = WebGLTransformFeedback {}
- noWebGLTransformFeedback :: Maybe WebGLTransformFeedback
- gTypeWebGLTransformFeedback :: JSM GType
- newtype WebGLUniformLocation = WebGLUniformLocation {}
- noWebGLUniformLocation :: Maybe WebGLUniformLocation
- gTypeWebGLUniformLocation :: JSM GType
- newtype WebGLVertexArrayObject = WebGLVertexArrayObject {}
- noWebGLVertexArrayObject :: Maybe WebGLVertexArrayObject
- gTypeWebGLVertexArrayObject :: JSM GType
- newtype WebGLVertexArrayObjectOES = WebGLVertexArrayObjectOES {}
- noWebGLVertexArrayObjectOES :: Maybe WebGLVertexArrayObjectOES
- gTypeWebGLVertexArrayObjectOES :: JSM GType
- newtype WebGPUBuffer = WebGPUBuffer {}
- noWebGPUBuffer :: Maybe WebGPUBuffer
- gTypeWebGPUBuffer :: JSM GType
- newtype WebGPUCommandBuffer = WebGPUCommandBuffer {}
- noWebGPUCommandBuffer :: Maybe WebGPUCommandBuffer
- gTypeWebGPUCommandBuffer :: JSM GType
- newtype WebGPUCommandQueue = WebGPUCommandQueue {}
- noWebGPUCommandQueue :: Maybe WebGPUCommandQueue
- gTypeWebGPUCommandQueue :: JSM GType
- newtype WebGPUComputeCommandEncoder = WebGPUComputeCommandEncoder {}
- noWebGPUComputeCommandEncoder :: Maybe WebGPUComputeCommandEncoder
- gTypeWebGPUComputeCommandEncoder :: JSM GType
- newtype WebGPUComputePipelineState = WebGPUComputePipelineState {}
- noWebGPUComputePipelineState :: Maybe WebGPUComputePipelineState
- gTypeWebGPUComputePipelineState :: JSM GType
- newtype WebGPUDepthStencilDescriptor = WebGPUDepthStencilDescriptor {}
- noWebGPUDepthStencilDescriptor :: Maybe WebGPUDepthStencilDescriptor
- gTypeWebGPUDepthStencilDescriptor :: JSM GType
- newtype WebGPUDepthStencilState = WebGPUDepthStencilState {}
- noWebGPUDepthStencilState :: Maybe WebGPUDepthStencilState
- gTypeWebGPUDepthStencilState :: JSM GType
- newtype WebGPUDrawable = WebGPUDrawable {}
- noWebGPUDrawable :: Maybe WebGPUDrawable
- gTypeWebGPUDrawable :: JSM GType
- newtype WebGPUFunction = WebGPUFunction {}
- noWebGPUFunction :: Maybe WebGPUFunction
- gTypeWebGPUFunction :: JSM GType
- newtype WebGPULibrary = WebGPULibrary {}
- noWebGPULibrary :: Maybe WebGPULibrary
- gTypeWebGPULibrary :: JSM GType
- newtype WebGPURenderCommandEncoder = WebGPURenderCommandEncoder {}
- noWebGPURenderCommandEncoder :: Maybe WebGPURenderCommandEncoder
- gTypeWebGPURenderCommandEncoder :: JSM GType
- newtype WebGPURenderPassAttachmentDescriptor = WebGPURenderPassAttachmentDescriptor {}
- class IsGObject o => IsWebGPURenderPassAttachmentDescriptor o
- toWebGPURenderPassAttachmentDescriptor :: IsWebGPURenderPassAttachmentDescriptor o => o -> WebGPURenderPassAttachmentDescriptor
- noWebGPURenderPassAttachmentDescriptor :: Maybe WebGPURenderPassAttachmentDescriptor
- gTypeWebGPURenderPassAttachmentDescriptor :: JSM GType
- newtype WebGPURenderPassColorAttachmentDescriptor = WebGPURenderPassColorAttachmentDescriptor {}
- noWebGPURenderPassColorAttachmentDescriptor :: Maybe WebGPURenderPassColorAttachmentDescriptor
- gTypeWebGPURenderPassColorAttachmentDescriptor :: JSM GType
- newtype WebGPURenderPassDepthAttachmentDescriptor = WebGPURenderPassDepthAttachmentDescriptor {}
- noWebGPURenderPassDepthAttachmentDescriptor :: Maybe WebGPURenderPassDepthAttachmentDescriptor
- gTypeWebGPURenderPassDepthAttachmentDescriptor :: JSM GType
- newtype WebGPURenderPassDescriptor = WebGPURenderPassDescriptor {}
- noWebGPURenderPassDescriptor :: Maybe WebGPURenderPassDescriptor
- gTypeWebGPURenderPassDescriptor :: JSM GType
- newtype WebGPURenderPipelineColorAttachmentDescriptor = WebGPURenderPipelineColorAttachmentDescriptor {}
- noWebGPURenderPipelineColorAttachmentDescriptor :: Maybe WebGPURenderPipelineColorAttachmentDescriptor
- gTypeWebGPURenderPipelineColorAttachmentDescriptor :: JSM GType
- newtype WebGPURenderPipelineDescriptor = WebGPURenderPipelineDescriptor {}
- noWebGPURenderPipelineDescriptor :: Maybe WebGPURenderPipelineDescriptor
- gTypeWebGPURenderPipelineDescriptor :: JSM GType
- newtype WebGPURenderPipelineState = WebGPURenderPipelineState {}
- noWebGPURenderPipelineState :: Maybe WebGPURenderPipelineState
- gTypeWebGPURenderPipelineState :: JSM GType
- newtype WebGPURenderingContext = WebGPURenderingContext {}
- noWebGPURenderingContext :: Maybe WebGPURenderingContext
- gTypeWebGPURenderingContext :: JSM GType
- newtype WebGPUSize = WebGPUSize {}
- noWebGPUSize :: Maybe WebGPUSize
- gTypeWebGPUSize :: JSM GType
- newtype WebGPUTexture = WebGPUTexture {}
- noWebGPUTexture :: Maybe WebGPUTexture
- gTypeWebGPUTexture :: JSM GType
- newtype WebGPUTextureDescriptor = WebGPUTextureDescriptor {}
- noWebGPUTextureDescriptor :: Maybe WebGPUTextureDescriptor
- gTypeWebGPUTextureDescriptor :: JSM GType
- newtype WebKitAnimationEvent = WebKitAnimationEvent {}
- noWebKitAnimationEvent :: Maybe WebKitAnimationEvent
- gTypeWebKitAnimationEvent :: JSM GType
- newtype WebKitAnimationEventInit = WebKitAnimationEventInit {}
- noWebKitAnimationEventInit :: Maybe WebKitAnimationEventInit
- gTypeWebKitAnimationEventInit :: JSM GType
- newtype WebKitCSSMatrix = WebKitCSSMatrix {}
- noWebKitCSSMatrix :: Maybe WebKitCSSMatrix
- gTypeWebKitCSSMatrix :: JSM GType
- newtype WebKitCSSRegionRule = WebKitCSSRegionRule {}
- noWebKitCSSRegionRule :: Maybe WebKitCSSRegionRule
- gTypeWebKitCSSRegionRule :: JSM GType
- newtype WebKitCSSViewportRule = WebKitCSSViewportRule {}
- noWebKitCSSViewportRule :: Maybe WebKitCSSViewportRule
- gTypeWebKitCSSViewportRule :: JSM GType
- newtype WebKitMediaKeyError = WebKitMediaKeyError {}
- noWebKitMediaKeyError :: Maybe WebKitMediaKeyError
- gTypeWebKitMediaKeyError :: JSM GType
- newtype WebKitMediaKeyMessageEvent = WebKitMediaKeyMessageEvent {}
- noWebKitMediaKeyMessageEvent :: Maybe WebKitMediaKeyMessageEvent
- gTypeWebKitMediaKeyMessageEvent :: JSM GType
- newtype WebKitMediaKeyMessageEventInit = WebKitMediaKeyMessageEventInit {}
- noWebKitMediaKeyMessageEventInit :: Maybe WebKitMediaKeyMessageEventInit
- gTypeWebKitMediaKeyMessageEventInit :: JSM GType
- newtype WebKitMediaKeyNeededEvent = WebKitMediaKeyNeededEvent {}
- noWebKitMediaKeyNeededEvent :: Maybe WebKitMediaKeyNeededEvent
- gTypeWebKitMediaKeyNeededEvent :: JSM GType
- newtype WebKitMediaKeyNeededEventInit = WebKitMediaKeyNeededEventInit {}
- noWebKitMediaKeyNeededEventInit :: Maybe WebKitMediaKeyNeededEventInit
- gTypeWebKitMediaKeyNeededEventInit :: JSM GType
- newtype WebKitMediaKeySession = WebKitMediaKeySession {}
- noWebKitMediaKeySession :: Maybe WebKitMediaKeySession
- gTypeWebKitMediaKeySession :: JSM GType
- newtype WebKitMediaKeys = WebKitMediaKeys {}
- noWebKitMediaKeys :: Maybe WebKitMediaKeys
- gTypeWebKitMediaKeys :: JSM GType
- newtype WebKitNamedFlow = WebKitNamedFlow {}
- noWebKitNamedFlow :: Maybe WebKitNamedFlow
- gTypeWebKitNamedFlow :: JSM GType
- newtype WebKitNamespace = WebKitNamespace {}
- noWebKitNamespace :: Maybe WebKitNamespace
- gTypeWebKitNamespace :: JSM GType
- newtype WebKitPlaybackTargetAvailabilityEvent = WebKitPlaybackTargetAvailabilityEvent {}
- noWebKitPlaybackTargetAvailabilityEvent :: Maybe WebKitPlaybackTargetAvailabilityEvent
- gTypeWebKitPlaybackTargetAvailabilityEvent :: JSM GType
- newtype WebKitPlaybackTargetAvailabilityEventInit = WebKitPlaybackTargetAvailabilityEventInit {}
- noWebKitPlaybackTargetAvailabilityEventInit :: Maybe WebKitPlaybackTargetAvailabilityEventInit
- gTypeWebKitPlaybackTargetAvailabilityEventInit :: JSM GType
- newtype WebKitPoint = WebKitPoint {}
- noWebKitPoint :: Maybe WebKitPoint
- gTypeWebKitPoint :: JSM GType
- newtype WebKitSubtleCrypto = WebKitSubtleCrypto {}
- noWebKitSubtleCrypto :: Maybe WebKitSubtleCrypto
- gTypeWebKitSubtleCrypto :: JSM GType
- newtype WebKitTransitionEvent = WebKitTransitionEvent {}
- noWebKitTransitionEvent :: Maybe WebKitTransitionEvent
- gTypeWebKitTransitionEvent :: JSM GType
- newtype WebKitTransitionEventInit = WebKitTransitionEventInit {}
- noWebKitTransitionEventInit :: Maybe WebKitTransitionEventInit
- gTypeWebKitTransitionEventInit :: JSM GType
- newtype WebSocket = WebSocket {
- unWebSocket :: JSVal
- noWebSocket :: Maybe WebSocket
- gTypeWebSocket :: JSM GType
- newtype WheelEvent = WheelEvent {}
- noWheelEvent :: Maybe WheelEvent
- gTypeWheelEvent :: JSM GType
- newtype WheelEventInit = WheelEventInit {}
- noWheelEventInit :: Maybe WheelEventInit
- gTypeWheelEventInit :: JSM GType
- newtype Window = Window {}
- noWindow :: Maybe Window
- gTypeWindow :: JSM GType
- newtype WindowEventHandlers = WindowEventHandlers {}
- class IsGObject o => IsWindowEventHandlers o
- toWindowEventHandlers :: IsWindowEventHandlers o => o -> WindowEventHandlers
- noWindowEventHandlers :: Maybe WindowEventHandlers
- gTypeWindowEventHandlers :: JSM GType
- newtype WindowOrWorkerGlobalScope = WindowOrWorkerGlobalScope {}
- class IsGObject o => IsWindowOrWorkerGlobalScope o
- toWindowOrWorkerGlobalScope :: IsWindowOrWorkerGlobalScope o => o -> WindowOrWorkerGlobalScope
- noWindowOrWorkerGlobalScope :: Maybe WindowOrWorkerGlobalScope
- gTypeWindowOrWorkerGlobalScope :: JSM GType
- newtype Worker = Worker {}
- noWorker :: Maybe Worker
- gTypeWorker :: JSM GType
- newtype WorkerGlobalScope = WorkerGlobalScope {}
- class (IsEventTarget o, IsWindowOrWorkerGlobalScope o, IsGlobalPerformance o, IsGlobalCrypto o, IsGObject o) => IsWorkerGlobalScope o
- toWorkerGlobalScope :: IsWorkerGlobalScope o => o -> WorkerGlobalScope
- noWorkerGlobalScope :: Maybe WorkerGlobalScope
- gTypeWorkerGlobalScope :: JSM GType
- newtype WorkerLocation = WorkerLocation {}
- noWorkerLocation :: Maybe WorkerLocation
- gTypeWorkerLocation :: JSM GType
- newtype WorkerNavigator = WorkerNavigator {}
- noWorkerNavigator :: Maybe WorkerNavigator
- gTypeWorkerNavigator :: JSM GType
- newtype WritableStream = WritableStream {}
- noWritableStream :: Maybe WritableStream
- gTypeWritableStream :: JSM GType
- newtype XMLDocument = XMLDocument {}
- noXMLDocument :: Maybe XMLDocument
- gTypeXMLDocument :: JSM GType
- newtype XMLHttpRequest = XMLHttpRequest {}
- noXMLHttpRequest :: Maybe XMLHttpRequest
- gTypeXMLHttpRequest :: JSM GType
- newtype XMLHttpRequestEventTarget = XMLHttpRequestEventTarget {}
- class (IsEventTarget o, IsGObject o) => IsXMLHttpRequestEventTarget o
- toXMLHttpRequestEventTarget :: IsXMLHttpRequestEventTarget o => o -> XMLHttpRequestEventTarget
- noXMLHttpRequestEventTarget :: Maybe XMLHttpRequestEventTarget
- gTypeXMLHttpRequestEventTarget :: JSM GType
- newtype XMLHttpRequestProgressEvent = XMLHttpRequestProgressEvent {}
- noXMLHttpRequestProgressEvent :: Maybe XMLHttpRequestProgressEvent
- gTypeXMLHttpRequestProgressEvent :: JSM GType
- newtype XMLHttpRequestUpload = XMLHttpRequestUpload {}
- noXMLHttpRequestUpload :: Maybe XMLHttpRequestUpload
- gTypeXMLHttpRequestUpload :: JSM GType
- newtype XMLSerializer = XMLSerializer {}
- noXMLSerializer :: Maybe XMLSerializer
- gTypeXMLSerializer :: JSM GType
- newtype XPathEvaluator = XPathEvaluator {}
- noXPathEvaluator :: Maybe XPathEvaluator
- gTypeXPathEvaluator :: JSM GType
- newtype XPathException = XPathException {}
- noXPathException :: Maybe XPathException
- gTypeXPathException :: JSM GType
- newtype XPathExpression = XPathExpression {}
- noXPathExpression :: Maybe XPathExpression
- gTypeXPathExpression :: JSM GType
- newtype XPathNSResolver = XPathNSResolver {}
- noXPathNSResolver :: Maybe XPathNSResolver
- gTypeXPathNSResolver :: JSM GType
- newtype XPathResult = XPathResult {}
- noXPathResult :: Maybe XPathResult
- gTypeXPathResult :: JSM GType
- newtype XSLTProcessor = XSLTProcessor {}
- noXSLTProcessor :: Maybe XSLTProcessor
- gTypeXSLTProcessor :: JSM GType
JavaScript Context and Monad
data JSContextRef :: * #
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.
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
askJSM :: MonadJSM m => m JSContextRef #
Gets the JavaScript context from the monad
runJSM :: MonadIO m => JSM a -> JSContextRef -> m a #
Runs a JSM
JavaScript function in a given JavaScript context.
class (Applicative m, MonadIO m) => MonadJSM m where #
Instances
MonadJSM JSM | |
MonadJSM m => MonadJSM (ListT m) | |
MonadJSM m => MonadJSM (MaybeT m) | |
MonadJSM m => MonadJSM (IdentityT * m) | |
(Error e, MonadJSM m) => MonadJSM (ErrorT e m) | |
MonadJSM m => MonadJSM (ExceptT e m) | |
MonadJSM m => MonadJSM (StateT s m) | |
MonadJSM m => MonadJSM (StateT s m) | |
(Monoid w, MonadJSM m) => MonadJSM (WriterT w m) | |
(Monoid w, MonadJSM m) => MonadJSM (WriterT w m) | |
MonadJSM m => MonadJSM (ContT * r m) | |
MonadJSM m => MonadJSM (ReaderT * r m) | |
(Monoid w, MonadJSM m) => MonadJSM (RWST r w s m) | |
(Monoid w, MonadJSM m) => MonadJSM (RWST r w s m) | |
DOM Context and Monad
type DOMContext = JSContextRef Source #
This is the same as JSContextRef
except when using ghcjs-dom-webkit with GHC (instead of ghcjs-dom-jsaddle)
This is the same as JSM
except when using ghcjs-dom-webkit with GHC (instead of ghcjs-dom-jsaddle)
askDOM :: MonadDOM m => m DOMContext Source #
This is the same as askJSM
except when using ghcjs-dom-webkit with GHC (instead of ghcjs-dom-jsaddle)
runDOM :: MonadIO m => DOM a -> DOMContext -> m a Source #
This is the same as runJSM
except when using ghcjs-dom-webkit with GHC (instead of ghcjs-dom-jsaddle)
type MonadDOM = MonadJSM Source #
This is the same as MonadJSM
except when using ghcjs-dom-webkit with GHC (instead of ghcjs-dom-jsaddle)
liftDOM :: MonadDOM m => DOM a -> m a Source #
This is the same as liftJSM
except when using ghcjs-dom-webkit with GHC (instead of ghcjs-dom-jsaddle)
JavaScript Value
Instances
Methods
fromJSVal :: JSVal -> JSM (Maybe a) #
fromJSValUnchecked :: JSVal -> JSM a #
fromJSValListOf :: JSVal -> JSM (Maybe [a]) #
fromJSValUncheckedListOf :: JSVal -> JSM [a] #
Instances
Minimal complete definition
Instances
class PFromJSVal a where #
Minimal complete definition
Methods
pFromJSVal :: JSVal -> a #
Instances
JavaScript String
A wrapper around a JavaScript string
Instances
class ToJSVal a => ToJSString a where #
Anything that can be used to make a JavaScript string
Minimal complete definition
Methods
toJSString :: a -> JSString #
class FromJSVal a => FromJSString a where #
Anything that can be constructed from a JavaScript string
Minimal complete definition
Methods
fromJSString :: JSString -> a #
toMaybeJSString :: ToJSString a => Maybe a -> JSM JSVal Source #
fromMaybeJSString :: FromJSString a => JSVal -> JSM (Maybe a) Source #
JavaScript Array
JavaScript Object
See Object
Instances
MakeObject Object | If we already have a Object we are fine |
Nullable
DOM String
type DOMString = JSString Source #
Fastest string type to use when you just want to take a string from the DOM then give it back as is.
type ToDOMString s = ToJSString s Source #
type FromDOMString s = FromJSString s Source #
type IsDOMString s = (ToDOMString s, FromDOMString s) Source #
type IsUSVString s = (ToDOMString s, FromDOMString s) Source #
type ByteString = JSString Source #
type IsByteString s = (ToDOMString s, FromDOMString s) Source #
type CSSOMString = JSString Source #
type IsCSSOMString s = (ToDOMString s, FromDOMString s) Source #
Object
maybeNullOrUndefined :: ToJSVal value => value -> JSM (Maybe JSVal) #
Convert a JSVal to a Maybe JSVal (converting null and undefined to Nothing)
class (ToJSVal o, FromJSVal o, Coercible o JSVal) => IsGObject o Source #
Minimal complete definition
typeGType
Instances
gTypeGObject :: JSM GType Source #
isA :: IsGObject o => o -> GType -> JSM Bool Source #
Determine if this is an instance of a particular type
objectToString :: (IsGObject self, FromJSString result) => self -> JSM result Source #
castTo :: forall obj obj' m. (Coercible obj JSVal, IsGObject obj', MonadJSM m) => (JSVal -> obj') -> obj -> m (Maybe obj') Source #
Safe but slow way to cast
castTo Element x >>= \case Nothing -> error "Was not an element" Just element -> ...
unsafeCastTo :: forall obj obj' m. (HasCallStack, Coercible obj JSVal, IsGObject obj', MonadJSM m) => (JSVal -> obj') -> obj -> m obj' Source #
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
uncheckedCastTo :: (Coercible obj JSVal, IsGObject obj') => (JSVal -> obj') -> obj -> obj' Source #
Unsafe way to cast. Fast but if it fails you program will probably crash later on in some unpredictable way.
element <- uncheckedCastTo Element x
TypedArray
newtype RawTypedArray Source #
Constructors
RawTypedArray | |
Fields |
class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsRawTypedArray o Source #
toRawTypedArray :: IsRawTypedArray o => o -> RawTypedArray Source #
Constructors
Function | |
Fields
|
class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsFunction o Source #
Instances
toFunction :: IsFunction o => o -> Function Source #
Promise
Callbacks
newtype AudioBufferCallback Source #
Constructors
AudioBufferCallback (Callback (JSVal -> IO ())) |
Instances
newtype IntersectionObserverCallback Source #
Constructors
IntersectionObserverCallback (Callback (JSVal -> JSVal -> IO ())) |
Instances
newtype MediaQueryListListener Source #
Constructors
MediaQueryListListener (Callback (JSVal -> IO ())) |
Instances
newtype MediaStreamTrackSourcesCallback Source #
Constructors
MediaStreamTrackSourcesCallback (Callback (JSVal -> IO ())) |
Instances
newtype NavigatorUserMediaErrorCallback Source #
Constructors
NavigatorUserMediaErrorCallback (Callback (JSVal -> IO ())) |
newtype NavigatorUserMediaSuccessCallback Source #
Constructors
NavigatorUserMediaSuccessCallback (Callback (JSVal -> IO ())) |
newtype NotificationPermissionCallback permissions Source #
Constructors
NotificationPermissionCallback (Callback (JSVal -> IO ())) |
Instances
ToJSVal (NotificationPermissionCallback permissions) Source # | |
newtype PositionErrorCallback Source #
Constructors
PositionErrorCallback (Callback (JSVal -> IO ())) |
Instances
newtype PerformanceObserverCallback Source #
Constructors
PerformanceObserverCallback (Callback (JSVal -> JSVal -> IO ())) |
Instances
newtype RequestAnimationFrameCallback Source #
Constructors
RequestAnimationFrameCallback (Callback (JSVal -> IO ())) |
Instances
newtype RTCPeerConnectionErrorCallback Source #
Constructors
RTCPeerConnectionErrorCallback (Callback (JSVal -> IO ())) |
Instances
newtype RTCSessionDescriptionCallback Source #
Constructors
RTCSessionDescriptionCallback (Callback (JSVal -> IO ())) |
Instances
newtype SQLStatementCallback Source #
Constructors
SQLStatementCallback (Callback (JSVal -> JSVal -> IO ())) |
Instances
newtype SQLStatementErrorCallback Source #
Constructors
SQLStatementErrorCallback (Callback (JSVal -> JSVal -> IO ())) |
Instances
newtype SQLTransactionCallback Source #
Constructors
SQLTransactionCallback (Callback (JSVal -> IO ())) |
Instances
newtype SQLTransactionErrorCallback Source #
Constructors
SQLTransactionErrorCallback (Callback (JSVal -> IO ())) |
Instances
newtype StorageErrorCallback Source #
Constructors
StorageErrorCallback (Callback (JSVal -> IO ())) |
Instances
newtype StorageQuotaCallback Source #
Constructors
StorageQuotaCallback (Callback (JSVal -> IO ())) |
Instances
newtype StorageUsageCallback Source #
Constructors
StorageUsageCallback (Callback (JSVal -> JSVal -> IO ())) |
Instances
newtype StringCallback s Source #
Constructors
StringCallback (Callback (JSVal -> IO ())) |
Instances
ToJSVal (StringCallback s) Source # | |
Custom Types
type DOMHighResTimeStamp = Double Source #
type PerformanceEntryList = [PerformanceEntry] Source #
Record Type
Dictionaries
newtype Dictionary Source #
Constructors
Dictionary | |
Fields |
class IsGObject o => IsDictionary o Source #
Instances
toDictionary :: IsDictionary o => o -> Dictionary Source #
Mutation Callback
newtype MutationCallback Source #
Constructors
MutationCallback | |
Fields |
class IsGObject o => IsMutationCallback o Source #
Instances
toMutationCallback :: IsMutationCallback o => o -> MutationCallback Source #
Date
Arrays
gTypeArray :: JSM GType Source #
newtype ObjectArray Source #
Constructors
ObjectArray | |
Fields |
class IsGObject o => IsObjectArray o Source #
Instances
toObjectArray :: IsObjectArray o => o -> ObjectArray Source #
newtype ArrayBuffer Source #
Constructors
ArrayBuffer | |
Fields |
Instances
class IsGObject o => IsArrayBuffer o Source #
Instances
toArrayBuffer :: IsArrayBuffer o => o -> ArrayBuffer Source #
newtype ArrayBufferView Source #
Constructors
ArrayBufferView | |
Fields |
Instances
class IsGObject o => IsArrayBufferView o Source #
Instances
toArrayBufferView :: IsArrayBufferView o => o -> ArrayBufferView Source #
newtype Float32Array Source #
Constructors
Float32Array | |
Fields |
class IsGObject o => IsFloat32Array o Source #
Instances
toFloat32Array :: IsFloat32Array o => o -> Float32Array Source #
newtype Float64Array Source #
Constructors
Float64Array | |
Fields |
class IsGObject o => IsFloat64Array o Source #
Instances
toFloat64Array :: IsFloat64Array o => o -> Float64Array Source #
newtype Uint8Array Source #
Constructors
Uint8Array | |
Fields |
class IsGObject o => IsUint8Array o Source #
Instances
toUint8Array :: IsUint8Array o => o -> Uint8Array Source #
newtype Uint8ClampedArray Source #
Constructors
Uint8ClampedArray | |
Fields |
class IsGObject o => IsUint8ClampedArray o Source #
Instances
toUint8ClampedArray :: IsUint8ClampedArray o => o -> Uint8ClampedArray Source #
newtype Uint16Array Source #
Constructors
Uint16Array | |
Fields |
class IsGObject o => IsUint16Array o Source #
Instances
toUint16Array :: IsUint16Array o => o -> Uint16Array Source #
newtype Uint32Array Source #
Constructors
Uint32Array | |
Fields |
class IsGObject o => IsUint32Array o Source #
Instances
toUint32Array :: IsUint32Array o => o -> Uint32Array Source #
Constructors
Int8Array | |
Fields
|
class IsGObject o => IsInt8Array o Source #
Instances
toInt8Array :: IsInt8Array o => o -> Int8Array Source #
newtype Int16Array Source #
Constructors
Int16Array | |
Fields |
class IsGObject o => IsInt16Array o Source #
Instances
toInt16Array :: IsInt16Array o => o -> Int16Array Source #
newtype Int32Array Source #
Constructors
Int32Array | |
Fields |
class IsGObject o => IsInt32Array o Source #
Instances
toInt32Array :: IsInt32Array o => o -> Int32Array Source #
Geolocation
newtype SerializedScriptValue Source #
Constructors
SerializedScriptValue | |
Fields |
class IsGObject o => IsSerializedScriptValue o Source #
Instances
Crypto
Constructors
Algorithm | |
Fields
|
class IsGObject o => IsAlgorithm o Source #
Instances
toAlgorithm :: IsAlgorithm o => o -> Algorithm Source #
newtype CryptoOperationData Source #
Constructors
CryptoOperationData | |
Fields |
class IsGObject o => IsCryptoOperationData o Source #
toCryptoOperationData :: IsCryptoOperationData o => o -> CryptoOperationData Source #
WebGL typedefs
type GLbitfield = Word32 Source #
type GLsizeiptr = Int64 Source #
Used for better error messages
type HasCallStack = ?callStack :: CallStack #
Request a CallStack.
NOTE: The implicit parameter ?callStack :: CallStack
is an
implementation detail and should not be considered part of the
CallStack
API, we may decide to change the implementation in the
future.
Since: 4.9.0.0
Interface types from IDL files
newtype AddEventListenerOptionsOrBool Source #
Constructors
AddEventListenerOptionsOrBool | |
Fields |
Instances
toAddEventListenerOptionsOrBool :: IsAddEventListenerOptionsOrBool o => o -> AddEventListenerOptionsOrBool Source #
newtype BinaryData Source #
Constructors
BinaryData | |
Fields |
Instances
class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsBinaryData o Source #
toBinaryData :: IsBinaryData o => o -> BinaryData Source #
Constructors
BlobPart | |
Fields
|
class (FromJSVal o, ToJSVal o) => IsBlobPart o Source #
Instances
Constructors
BodyInit | |
Fields
|
class (FromJSVal o, ToJSVal o) => IsBodyInit o Source #
Instances
newtype BufferDataSource Source #
Constructors
BufferDataSource | |
Fields |
class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsBufferDataSource o Source #
toBufferDataSource :: IsBufferDataSource o => o -> BufferDataSource Source #
newtype BufferSource Source #
Constructors
BufferSource | |
Fields |
Instances
class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsBufferSource o Source #
toBufferSource :: IsBufferSource o => o -> BufferSource Source #
newtype CanvasImageSource Source #
Constructors
CanvasImageSource | |
Fields |
class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsCanvasImageSource o Source #
toCanvasImageSource :: IsCanvasImageSource o => o -> CanvasImageSource Source #
newtype CanvasStyle Source #
Constructors
CanvasStyle | |
Fields |
class (FromJSVal o, ToJSVal o) => IsCanvasStyle o Source #
newtype CredentialBodyType Source #
Constructors
CredentialBodyType | |
Fields |
class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsCredentialBodyType o Source #
toCredentialBodyType :: IsCredentialBodyType o => o -> CredentialBodyType Source #
newtype CryptoKeyOrKeyPair Source #
Constructors
CryptoKeyOrKeyPair | |
Fields |
class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsCryptoKeyOrKeyPair o Source #
toCryptoKeyOrKeyPair :: IsCryptoKeyOrKeyPair o => o -> CryptoKeyOrKeyPair Source #
toEventListenerOptionsOrBool :: IsEventListenerOptionsOrBool o => o -> EventListenerOptionsOrBool Source #
newtype Float32List Source #
Constructors
Float32List | |
Fields |
class (FromJSVal o, ToJSVal o) => IsFloat32List o Source #
Instances
newtype HTMLCollectionOrElement Source #
Constructors
HTMLCollectionOrElement | |
Fields |
class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsHTMLCollectionOrElement o Source #
Instances
newtype HTMLElementOrLong Source #
Constructors
HTMLElementOrLong | |
Fields |
class (FromJSVal o, ToJSVal o) => IsHTMLElementOrLong o Source #
Instances
newtype HTMLOptionElementOrGroup Source #
Constructors
HTMLOptionElementOrGroup | |
Fields |
class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsHTMLOptionElementOrGroup o Source #
toHTMLOptionElementOrGroup :: IsHTMLOptionElementOrGroup o => o -> HTMLOptionElementOrGroup Source #
newtype IDBCursorSource Source #
Constructors
IDBCursorSource | |
Fields |
class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsIDBCursorSource o Source #
toIDBCursorSource :: IsIDBCursorSource o => o -> IDBCursorSource Source #
newtype IDBKeyPath Source #
Constructors
IDBKeyPath | |
Fields |
class (FromJSVal o, ToJSVal o) => IsIDBKeyPath o Source #
newtype IDBRequestResult Source #
Constructors
IDBRequestResult | |
Fields |
class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsIDBRequestResult o Source #
toIDBRequestResult :: IsIDBRequestResult o => o -> IDBRequestResult Source #
newtype IDBRequestSource Source #
Constructors
IDBRequestSource | |
Fields |
class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsIDBRequestSource o Source #
toIDBRequestSource :: IsIDBRequestSource o => o -> IDBRequestSource Source #
Constructors
Int32List | |
Fields
|
class (FromJSVal o, ToJSVal o) => IsInt32List o Source #
Instances
newtype MediaProvider Source #
Constructors
MediaProvider | |
Fields |
class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsMediaProvider o Source #
toMediaProvider :: IsMediaProvider o => o -> MediaProvider Source #
newtype MediaStreamTrackOrKind Source #
Constructors
MediaStreamTrackOrKind | |
Fields |
class (FromJSVal o, ToJSVal o) => IsMediaStreamTrackOrKind o Source #
Instances
newtype MessageEventSource Source #
Constructors
MessageEventSource | |
Fields |
class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsMessageEventSource o Source #
toMessageEventSource :: IsMessageEventSource o => o -> MessageEventSource Source #
newtype NodeOrString Source #
Constructors
NodeOrString | |
Fields |
class (FromJSVal o, ToJSVal o) => IsNodeOrString o Source #
Instances
newtype RTCIceCandidateOrInit Source #
Constructors
RTCIceCandidateOrInit | |
Fields |
class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsRTCIceCandidateOrInit o Source #
newtype RadioNodeListOrElement Source #
Constructors
RadioNodeListOrElement | |
Fields |
class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsRadioNodeListOrElement o Source #
Instances
newtype RenderingContext Source #
Constructors
RenderingContext | |
Fields |
class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsRenderingContext o Source #
toRenderingContext :: IsRenderingContext o => o -> RenderingContext Source #
Constructors
SQLValue | |
Fields
|
class (FromJSVal o, ToJSVal o) => IsSQLValue o Source #
Instances
newtype StringOrArrayBuffer Source #
Constructors
StringOrArrayBuffer | |
Fields |
class (FromJSVal o, ToJSVal o) => IsStringOrArrayBuffer o Source #
newtype StringOrBinaryData Source #
Constructors
StringOrBinaryData | |
Fields |
class (FromJSVal o, ToJSVal o) => IsStringOrBinaryData o Source #
Instances
newtype StringOrStrings Source #
Constructors
StringOrStrings | |
Fields |
class (FromJSVal o, ToJSVal o) => IsStringOrStrings o Source #
newtype TexImageSource Source #
Constructors
TexImageSource | |
Fields |
class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsTexImageSource o Source #
toTexImageSource :: IsTexImageSource o => o -> TexImageSource Source #
newtype URLSearchParamsInit Source #
Constructors
URLSearchParamsInit | |
Fields |
class (FromJSVal o, ToJSVal o) => IsURLSearchParamsInit o Source #
Instances
newtype XMLHttpRequestBody Source #
Constructors
XMLHttpRequestBody | |
Fields |
class (FromJSVal o, ToJSVal o) => IsXMLHttpRequestBody o Source #
Instances
newtype ANGLEInstancedArrays Source #
Functions for this inteface are in JSDOM.ANGLEInstancedArrays.
Constructors
ANGLEInstancedArrays | |
Fields |
newtype AbstractWorker Source #
Functions for this inteface are in JSDOM.AbstractWorker.
Constructors
AbstractWorker | |
Fields |
class IsGObject o => IsAbstractWorker o Source #
Instances
toAbstractWorker :: IsAbstractWorker o => o -> AbstractWorker Source #
newtype Acceleration Source #
Functions for this inteface are in JSDOM.Acceleration.
Constructors
Acceleration | |
Fields |
newtype AddEventListenerOptions Source #
Functions for this inteface are in JSDOM.AddEventListenerOptions. Base interface functions are in:
Constructors
AddEventListenerOptions | |
Fields |
Instances
newtype AesCbcCfbParams Source #
Functions for this inteface are in JSDOM.AesCbcCfbParams. Base interface functions are in:
Constructors
AesCbcCfbParams | |
Fields |
newtype AesCtrParams Source #
Functions for this inteface are in JSDOM.AesCtrParams. Base interface functions are in:
Constructors
AesCtrParams | |
Fields |
newtype AesGcmParams Source #
Functions for this inteface are in JSDOM.AesGcmParams. Base interface functions are in:
Constructors
AesGcmParams | |
Fields |
newtype AesKeyParams Source #
Functions for this inteface are in JSDOM.AesKeyParams. Base interface functions are in:
Constructors
AesKeyParams | |
Fields |
newtype AnalyserNode Source #
Functions for this inteface are in JSDOM.AnalyserNode. Base interface functions are in:
Constructors
AnalyserNode | |
Fields |
newtype Animatable Source #
Functions for this inteface are in JSDOM.Animatable.
Constructors
Animatable | |
Fields |
class IsGObject o => IsAnimatable o Source #
Instances
toAnimatable :: IsAnimatable o => o -> Animatable Source #
Functions for this inteface are in JSDOM.Animation.
Constructors
Animation | |
Fields
|
newtype AnimationEffect Source #
Functions for this inteface are in JSDOM.AnimationEffect.
Constructors
AnimationEffect | |
Fields |
class IsGObject o => IsAnimationEffect o Source #
toAnimationEffect :: IsAnimationEffect o => o -> AnimationEffect Source #
newtype AnimationEvent Source #
Functions for this inteface are in JSDOM.AnimationEvent. Base interface functions are in:
Constructors
AnimationEvent | |
Fields |
newtype AnimationEventInit Source #
Functions for this inteface are in JSDOM.AnimationEventInit. Base interface functions are in:
Constructors
AnimationEventInit | |
Fields |
newtype AnimationTimeline Source #
Functions for this inteface are in JSDOM.AnimationTimeline.
Constructors
AnimationTimeline | |
Fields |
class IsGObject o => IsAnimationTimeline o Source #
toAnimationTimeline :: IsAnimationTimeline o => o -> AnimationTimeline Source #
newtype ApplePayError Source #
Functions for this inteface are in JSDOM.ApplePayError.
Constructors
ApplePayError | |
Fields |
newtype ApplePayLineItem Source #
Functions for this inteface are in JSDOM.ApplePayLineItem.
Constructors
ApplePayLineItem | |
Fields |
newtype ApplePayPayment Source #
Functions for this inteface are in JSDOM.ApplePayPayment.
Constructors
ApplePayPayment | |
Fields |
newtype ApplePayPaymentAuthorizationResult Source #
Functions for this inteface are in JSDOM.ApplePayPaymentAuthorizationResult.
Constructors
ApplePayPaymentAuthorizationResult | |
Instances
newtype ApplePayPaymentAuthorizedEvent Source #
Functions for this inteface are in JSDOM.ApplePayPaymentAuthorizedEvent. Base interface functions are in:
Constructors
ApplePayPaymentAuthorizedEvent | |
Fields |
Instances
newtype ApplePayPaymentContact Source #
Functions for this inteface are in JSDOM.ApplePayPaymentContact.
Constructors
ApplePayPaymentContact | |
Fields |
newtype ApplePayPaymentMethod Source #
Functions for this inteface are in JSDOM.ApplePayPaymentMethod.
Constructors
ApplePayPaymentMethod | |
Fields |
newtype ApplePayPaymentMethodSelectedEvent Source #
Functions for this inteface are in JSDOM.ApplePayPaymentMethodSelectedEvent. Base interface functions are in:
Constructors
ApplePayPaymentMethodSelectedEvent | |
Instances
newtype ApplePayPaymentMethodUpdate Source #
Functions for this inteface are in JSDOM.ApplePayPaymentMethodUpdate.
Constructors
ApplePayPaymentMethodUpdate | |
Fields |
newtype ApplePayPaymentPass Source #
Functions for this inteface are in JSDOM.ApplePayPaymentPass.
Constructors
ApplePayPaymentPass | |
Fields |
newtype ApplePayPaymentRequest Source #
Functions for this inteface are in JSDOM.ApplePayPaymentRequest.
Constructors
ApplePayPaymentRequest | |
Fields |
newtype ApplePayPaymentToken Source #
Functions for this inteface are in JSDOM.ApplePayPaymentToken.
Constructors
ApplePayPaymentToken | |
Fields |
newtype ApplePaySession Source #
Functions for this inteface are in JSDOM.ApplePaySession. Base interface functions are in:
Constructors
ApplePaySession | |
Fields |
newtype ApplePayShippingContactSelectedEvent Source #
Functions for this inteface are in JSDOM.ApplePayShippingContactSelectedEvent. Base interface functions are in:
Constructors
ApplePayShippingContactSelectedEvent | |
Instances
newtype ApplePayShippingContactUpdate Source #
Functions for this inteface are in JSDOM.ApplePayShippingContactUpdate.
Constructors
ApplePayShippingContactUpdate | |
Fields |
Instances
newtype ApplePayShippingMethod Source #
Functions for this inteface are in JSDOM.ApplePayShippingMethod.
Constructors
ApplePayShippingMethod | |
Fields |
newtype ApplePayShippingMethodSelectedEvent Source #
Functions for this inteface are in JSDOM.ApplePayShippingMethodSelectedEvent. Base interface functions are in:
Constructors
ApplePayShippingMethodSelectedEvent | |
Instances
newtype ApplePayShippingMethodUpdate Source #
Functions for this inteface are in JSDOM.ApplePayShippingMethodUpdate.
Constructors
ApplePayShippingMethodUpdate | |
Fields |
newtype ApplePayValidateMerchantEvent Source #
Functions for this inteface are in JSDOM.ApplePayValidateMerchantEvent. Base interface functions are in:
Constructors
ApplePayValidateMerchantEvent | |
Fields |
Instances
newtype ApplicationCache Source #
Functions for this inteface are in JSDOM.ApplicationCache. Base interface functions are in:
Constructors
ApplicationCache | |
Fields |
newtype AssignedNodesOptions Source #
Functions for this inteface are in JSDOM.AssignedNodesOptions.
Constructors
AssignedNodesOptions | |
Fields |
Functions for this inteface are in JSDOM.Attr. Base interface functions are in:
newtype AudioBuffer Source #
Functions for this inteface are in JSDOM.AudioBuffer.
Constructors
AudioBuffer | |
Fields |
newtype AudioBufferSourceNode Source #
Functions for this inteface are in JSDOM.AudioBufferSourceNode. Base interface functions are in:
Constructors
AudioBufferSourceNode | |
Fields |
Instances
newtype AudioContext Source #
Functions for this inteface are in JSDOM.AudioContext. Base interface functions are in:
Constructors
AudioContext | |
Fields |
class (IsEventTarget o, IsGObject o) => IsAudioContext o Source #
toAudioContext :: IsAudioContext o => o -> AudioContext Source #
newtype AudioDestinationNode Source #
Functions for this inteface are in JSDOM.AudioDestinationNode. Base interface functions are in:
Constructors
AudioDestinationNode | |
Fields |
Instances
newtype AudioListener Source #
Functions for this inteface are in JSDOM.AudioListener.
Constructors
AudioListener | |
Fields |
Functions for this inteface are in JSDOM.AudioNode. Base interface functions are in:
Constructors
AudioNode | |
Fields
|
class (IsEventTarget o, IsGObject o) => IsAudioNode o Source #
Instances
toAudioNode :: IsAudioNode o => o -> AudioNode Source #
newtype AudioParam Source #
Functions for this inteface are in JSDOM.AudioParam.
Constructors
AudioParam | |
Fields |
newtype AudioProcessingEvent Source #
Functions for this inteface are in JSDOM.AudioProcessingEvent. Base interface functions are in:
Constructors
AudioProcessingEvent | |
Fields |
newtype AudioTrack Source #
Functions for this inteface are in JSDOM.AudioTrack.
Constructors
AudioTrack | |
Fields |
newtype AudioTrackList Source #
Functions for this inteface are in JSDOM.AudioTrackList. Base interface functions are in:
Constructors
AudioTrackList | |
Fields |
newtype AutocompleteErrorEvent Source #
Functions for this inteface are in JSDOM.AutocompleteErrorEvent. Base interface functions are in:
Constructors
AutocompleteErrorEvent | |
Fields |
Instances
newtype AutocompleteErrorEventInit Source #
Functions for this inteface are in JSDOM.AutocompleteErrorEventInit. Base interface functions are in:
Constructors
AutocompleteErrorEventInit | |
Fields |
Instances
Functions for this inteface are in JSDOM.BarProp.
gTypeBarProp :: JSM GType Source #
newtype BasicCredential Source #
Functions for this inteface are in JSDOM.BasicCredential.
Constructors
BasicCredential | |
Fields |
class IsGObject o => IsBasicCredential o Source #
toBasicCredential :: IsBasicCredential o => o -> BasicCredential Source #
newtype BeforeLoadEvent Source #
Functions for this inteface are in JSDOM.BeforeLoadEvent. Base interface functions are in:
Constructors
BeforeLoadEvent | |
Fields |
newtype BeforeLoadEventInit Source #
Functions for this inteface are in JSDOM.BeforeLoadEventInit. Base interface functions are in:
Constructors
BeforeLoadEventInit | |
Fields |
newtype BeforeUnloadEvent Source #
Functions for this inteface are in JSDOM.BeforeUnloadEvent. Base interface functions are in:
Constructors
BeforeUnloadEvent | |
Fields |
newtype BiquadFilterNode Source #
Functions for this inteface are in JSDOM.BiquadFilterNode. Base interface functions are in:
Constructors
BiquadFilterNode | |
Fields |
Instances
Functions for this inteface are in JSDOM.Blob.
newtype BlobPropertyBag Source #
Functions for this inteface are in JSDOM.BlobPropertyBag.
Constructors
BlobPropertyBag | |
Fields |
class IsGObject o => IsBlobPropertyBag o Source #
toBlobPropertyBag :: IsBlobPropertyBag o => o -> BlobPropertyBag Source #
Functions for this inteface are in JSDOM.Body.
newtype ByteLengthQueuingStrategy Source #
Functions for this inteface are in JSDOM.ByteLengthQueuingStrategy.
Constructors
ByteLengthQueuingStrategy | |
Fields |
newtype CDATASection Source #
Functions for this inteface are in JSDOM.CDATASection. Base interface functions are in:
Constructors
CDATASection | |
Fields |
Instances
Functions for this inteface are in JSDOM.CSS.
newtype CSSFontFaceLoadEvent Source #
Functions for this inteface are in JSDOM.CSSFontFaceLoadEvent. Base interface functions are in:
Constructors
CSSFontFaceLoadEvent | |
Fields |
newtype CSSFontFaceLoadEventInit Source #
Functions for this inteface are in JSDOM.CSSFontFaceLoadEventInit. Base interface functions are in:
Constructors
CSSFontFaceLoadEventInit | |
Fields |
Instances
newtype CSSFontFaceRule Source #
Functions for this inteface are in JSDOM.CSSFontFaceRule. Base interface functions are in:
Constructors
CSSFontFaceRule | |
Fields |
newtype CSSImportRule Source #
Functions for this inteface are in JSDOM.CSSImportRule. Base interface functions are in:
Constructors
CSSImportRule | |
Fields |
newtype CSSKeyframeRule Source #
Functions for this inteface are in JSDOM.CSSKeyframeRule. Base interface functions are in:
Constructors
CSSKeyframeRule | |
Fields |
newtype CSSKeyframesRule Source #
Functions for this inteface are in JSDOM.CSSKeyframesRule. Base interface functions are in:
Constructors
CSSKeyframesRule | |
Fields |
newtype CSSMediaRule Source #
Functions for this inteface are in JSDOM.CSSMediaRule. Base interface functions are in:
Constructors
CSSMediaRule | |
Fields |
newtype CSSNamespaceRule Source #
Functions for this inteface are in JSDOM.CSSNamespaceRule. Base interface functions are in:
Constructors
CSSNamespaceRule | |
Fields |
newtype CSSPageRule Source #
Functions for this inteface are in JSDOM.CSSPageRule. Base interface functions are in:
Constructors
CSSPageRule | |
Fields |
newtype CSSPrimitiveValue Source #
Functions for this inteface are in JSDOM.CSSPrimitiveValue. Base interface functions are in:
Constructors
CSSPrimitiveValue | |
Fields |
Functions for this inteface are in JSDOM.CSSRule.
class IsGObject o => IsCSSRule o Source #
Instances
gTypeCSSRule :: JSM GType Source #
newtype CSSRuleList Source #
Functions for this inteface are in JSDOM.CSSRuleList.
Constructors
CSSRuleList | |
Fields |
newtype CSSStyleDeclaration Source #
Functions for this inteface are in JSDOM.CSSStyleDeclaration.
Constructors
CSSStyleDeclaration | |
Fields |
newtype CSSStyleRule Source #
Functions for this inteface are in JSDOM.CSSStyleRule. Base interface functions are in:
Constructors
CSSStyleRule | |
Fields |
newtype CSSStyleSheet Source #
Functions for this inteface are in JSDOM.CSSStyleSheet. Base interface functions are in:
Constructors
CSSStyleSheet | |
Fields |
newtype CSSSupportsRule Source #
Functions for this inteface are in JSDOM.CSSSupportsRule. Base interface functions are in:
Constructors
CSSSupportsRule | |
Fields |
newtype CSSUnknownRule Source #
Functions for this inteface are in JSDOM.CSSUnknownRule. Base interface functions are in:
Constructors
CSSUnknownRule | |
Fields |
Functions for this inteface are in JSDOM.CSSValue.
Constructors
CSSValue | |
Fields
|
class IsGObject o => IsCSSValue o Source #
toCSSValue :: IsCSSValue o => o -> CSSValue Source #
gTypeCSSValue :: JSM GType Source #
newtype CSSValueList Source #
Functions for this inteface are in JSDOM.CSSValueList. Base interface functions are in:
Constructors
CSSValueList | |
Fields |
newtype CanvasCaptureMediaStreamTrack Source #
Functions for this inteface are in JSDOM.CanvasCaptureMediaStreamTrack. Base interface functions are in:
Constructors
CanvasCaptureMediaStreamTrack | |
Fields |
Instances
newtype CanvasGradient Source #
Functions for this inteface are in JSDOM.CanvasGradient.
Constructors
CanvasGradient | |
Fields |
newtype CanvasPath Source #
Functions for this inteface are in JSDOM.CanvasPath.
Constructors
CanvasPath | |
Fields |
class IsGObject o => IsCanvasPath o Source #
toCanvasPath :: IsCanvasPath o => o -> CanvasPath Source #
newtype CanvasPattern Source #
Functions for this inteface are in JSDOM.CanvasPattern.
Constructors
CanvasPattern | |
Fields |
newtype CanvasProxy Source #
Functions for this inteface are in JSDOM.CanvasProxy.
Constructors
CanvasProxy | |
Fields |
newtype CanvasRenderingContext2D Source #
Functions for this inteface are in JSDOM.CanvasRenderingContext2D. Base interface functions are in:
Constructors
CanvasRenderingContext2D | |
Fields |
Instances
newtype ChannelMergerNode Source #
Functions for this inteface are in JSDOM.ChannelMergerNode. Base interface functions are in:
Constructors
ChannelMergerNode | |
Fields |
Instances
newtype ChannelSplitterNode Source #
Functions for this inteface are in JSDOM.ChannelSplitterNode. Base interface functions are in:
Constructors
ChannelSplitterNode | |
Fields |
Instances
newtype CharacterData Source #
Functions for this inteface are in JSDOM.CharacterData. Base interface functions are in:
Constructors
CharacterData | |
Fields |
Instances
class (IsNode o, IsEventTarget o, IsNonDocumentTypeChildNode o, IsChildNode o, IsGObject o) => IsCharacterData o Source #
toCharacterData :: IsCharacterData o => o -> CharacterData Source #
Functions for this inteface are in JSDOM.ChildNode.
Constructors
ChildNode | |
Fields
|
class IsGObject o => IsChildNode o Source #
Instances
toChildNode :: IsChildNode o => o -> ChildNode Source #
newtype ClipboardEvent Source #
Functions for this inteface are in JSDOM.ClipboardEvent. Base interface functions are in:
Constructors
ClipboardEvent | |
Fields |
newtype ClipboardEventInit Source #
Functions for this inteface are in JSDOM.ClipboardEventInit. Base interface functions are in:
Constructors
ClipboardEventInit | |
Fields |
newtype CloseEvent Source #
Functions for this inteface are in JSDOM.CloseEvent. Base interface functions are in:
Constructors
CloseEvent | |
Fields |
newtype CloseEventInit Source #
Functions for this inteface are in JSDOM.CloseEventInit. Base interface functions are in:
Constructors
CloseEventInit | |
Fields |
newtype CommandLineAPIHost Source #
Functions for this inteface are in JSDOM.CommandLineAPIHost.
Constructors
CommandLineAPIHost | |
Fields |
Functions for this inteface are in JSDOM.Comment. Base interface functions are in:
Instances
gTypeComment :: JSM GType Source #
newtype CompositionEvent Source #
Functions for this inteface are in JSDOM.CompositionEvent. Base interface functions are in:
Constructors
CompositionEvent | |
Fields |
newtype CompositionEventInit Source #
Functions for this inteface are in JSDOM.CompositionEventInit. Base interface functions are in:
Constructors
CompositionEventInit | |
Fields |
Instances
newtype ConstrainBooleanParameters Source #
Functions for this inteface are in JSDOM.ConstrainBooleanParameters.
Constructors
ConstrainBooleanParameters | |
Fields |
newtype ConstrainDOMStringParameters Source #
Functions for this inteface are in JSDOM.ConstrainDOMStringParameters.
Constructors
ConstrainDOMStringParameters | |
Fields |
newtype ConstrainDoubleRange Source #
Functions for this inteface are in JSDOM.ConstrainDoubleRange. Base interface functions are in:
Constructors
ConstrainDoubleRange | |
Fields |
newtype ConstrainLongRange Source #
Functions for this inteface are in JSDOM.ConstrainLongRange. Base interface functions are in:
Constructors
ConstrainLongRange | |
Fields |
newtype ConvolverNode Source #
Functions for this inteface are in JSDOM.ConvolverNode. Base interface functions are in:
Constructors
ConvolverNode | |
Fields |
newtype Coordinates Source #
Functions for this inteface are in JSDOM.Coordinates.
Constructors
Coordinates | |
Fields |
newtype CountQueuingStrategy Source #
Functions for this inteface are in JSDOM.CountQueuingStrategy.
Constructors
CountQueuingStrategy | |
Fields |
Functions for this inteface are in JSDOM.Counter.
gTypeCounter :: JSM GType Source #
newtype CredentialData Source #
Functions for this inteface are in JSDOM.CredentialData.
Constructors
CredentialData | |
Fields |
class IsGObject o => IsCredentialData o Source #
toCredentialData :: IsCredentialData o => o -> CredentialData Source #
Functions for this inteface are in JSDOM.Crypto.
gTypeCrypto :: JSM GType Source #
newtype CryptoAlgorithmParameters Source #
Functions for this inteface are in JSDOM.CryptoAlgorithmParameters.
Constructors
CryptoAlgorithmParameters | |
Fields |
Instances
class IsGObject o => IsCryptoAlgorithmParameters o Source #
Instances
toCryptoAlgorithmParameters :: IsCryptoAlgorithmParameters o => o -> CryptoAlgorithmParameters Source #
Functions for this inteface are in JSDOM.CryptoKey.
Constructors
CryptoKey | |
Fields
|
newtype CryptoKeyPair Source #
Functions for this inteface are in JSDOM.CryptoKeyPair.
Constructors
CryptoKeyPair | |
Fields |
newtype CustomElementRegistry Source #
Functions for this inteface are in JSDOM.CustomElementRegistry.
Constructors
CustomElementRegistry | |
Fields |
newtype CustomEvent Source #
Functions for this inteface are in JSDOM.CustomEvent. Base interface functions are in:
Constructors
CustomEvent | |
Fields |
newtype CustomEventInit Source #
Functions for this inteface are in JSDOM.CustomEventInit. Base interface functions are in:
Constructors
CustomEventInit | |
Fields |
Functions for this inteface are in JSDOM.DOMError.
Constructors
DOMError | |
Fields
|
class IsGObject o => IsDOMError o Source #
Instances
toDOMError :: IsDOMError o => o -> DOMError Source #
gTypeDOMError :: JSM GType Source #
newtype DOMException Source #
Functions for this inteface are in JSDOM.DOMException.
Constructors
DOMException | |
Fields |
newtype DOMImplementation Source #
Functions for this inteface are in JSDOM.DOMImplementation.
Constructors
DOMImplementation | |
Fields |
newtype DOMNamedFlowCollection Source #
Functions for this inteface are in JSDOM.DOMNamedFlowCollection.
Constructors
DOMNamedFlowCollection | |
Fields |
Functions for this inteface are in JSDOM.DOMParser.
Constructors
DOMParser | |
Fields
|
Functions for this inteface are in JSDOM.DOMPoint. Base interface functions are in:
Constructors
DOMPoint | |
Fields
|
gTypeDOMPoint :: JSM GType Source #
newtype DOMPointInit Source #
Functions for this inteface are in JSDOM.DOMPointInit.
Constructors
DOMPointInit | |
Fields |
newtype DOMPointReadOnly Source #
Functions for this inteface are in JSDOM.DOMPointReadOnly.
Constructors
DOMPointReadOnly | |
Fields |
class IsGObject o => IsDOMPointReadOnly o Source #
toDOMPointReadOnly :: IsDOMPointReadOnly o => o -> DOMPointReadOnly Source #
Functions for this inteface are in JSDOM.DOMRect. Base interface functions are in:
gTypeDOMRect :: JSM GType Source #
newtype DOMRectInit Source #
Functions for this inteface are in JSDOM.DOMRectInit.
Constructors
DOMRectInit | |
Fields |
newtype DOMRectReadOnly Source #
Functions for this inteface are in JSDOM.DOMRectReadOnly.
Constructors
DOMRectReadOnly | |
Fields |
class IsGObject o => IsDOMRectReadOnly o Source #
toDOMRectReadOnly :: IsDOMRectReadOnly o => o -> DOMRectReadOnly Source #
newtype DOMStringList Source #
Functions for this inteface are in JSDOM.DOMStringList.
Constructors
DOMStringList | |
Fields |
newtype DOMStringMap Source #
Functions for this inteface are in JSDOM.DOMStringMap.
Constructors
DOMStringMap | |
Fields |
newtype DOMTokenList Source #
Functions for this inteface are in JSDOM.DOMTokenList.
Constructors
DOMTokenList | |
Fields |
Functions for this inteface are in JSDOM.DataCue. Base interface functions are in:
gTypeDataCue :: JSM GType Source #
newtype DataTransfer Source #
Functions for this inteface are in JSDOM.DataTransfer.
Constructors
DataTransfer | |
Fields |
newtype DataTransferItem Source #
Functions for this inteface are in JSDOM.DataTransferItem.
Constructors
DataTransferItem | |
Fields |
newtype DataTransferItemList Source #
Functions for this inteface are in JSDOM.DataTransferItemList.
Constructors
DataTransferItemList | |
Fields |
Functions for this inteface are in JSDOM.Database.
Constructors
Database | |
Fields
|
gTypeDatabase :: JSM GType Source #
newtype DedicatedWorkerGlobalScope Source #
Functions for this inteface are in JSDOM.DedicatedWorkerGlobalScope. Base interface functions are in:
Constructors
DedicatedWorkerGlobalScope | |
Fields |
Instances
Functions for this inteface are in JSDOM.DelayNode. Base interface functions are in:
Constructors
DelayNode | |
Fields
|
newtype DeviceMotionEvent Source #
Functions for this inteface are in JSDOM.DeviceMotionEvent. Base interface functions are in:
Constructors
DeviceMotionEvent | |
Fields |
newtype DeviceOrientationEvent Source #
Functions for this inteface are in JSDOM.DeviceOrientationEvent. Base interface functions are in:
Constructors
DeviceOrientationEvent | |
Fields |
Instances
newtype DeviceProximityEvent Source #
Functions for this inteface are in JSDOM.DeviceProximityEvent. Base interface functions are in:
Constructors
DeviceProximityEvent | |
Fields |
newtype DeviceProximityEventInit Source #
Functions for this inteface are in JSDOM.DeviceProximityEventInit. Base interface functions are in:
Constructors
DeviceProximityEventInit | |
Fields |
Instances
Functions for this inteface are in JSDOM.Document. Base interface functions are in:
Constructors
Document | |
Fields
|
Instances
class (IsNode o, IsEventTarget o, IsGlobalEventHandlers o, IsDocumentOrShadowRoot o, IsNonElementParentNode o, IsParentNode o, IsDocumentAndElementEventHandlers o, IsGObject o) => IsDocument o Source #
Instances
toDocument :: IsDocument o => o -> Document Source #
gTypeDocument :: JSM GType Source #
newtype DocumentAndElementEventHandlers Source #
Functions for this inteface are in JSDOM.DocumentAndElementEventHandlers.
Constructors
DocumentAndElementEventHandlers | |
Fields |
Instances
class IsGObject o => IsDocumentAndElementEventHandlers o Source #
Instances
toDocumentAndElementEventHandlers :: IsDocumentAndElementEventHandlers o => o -> DocumentAndElementEventHandlers Source #
newtype DocumentFragment Source #
Functions for this inteface are in JSDOM.DocumentFragment. Base interface functions are in:
Constructors
DocumentFragment | |
Fields |
Instances
class (IsNode o, IsEventTarget o, IsNonElementParentNode o, IsParentNode o, IsGObject o) => IsDocumentFragment o Source #
toDocumentFragment :: IsDocumentFragment o => o -> DocumentFragment Source #
newtype DocumentOrShadowRoot Source #
Functions for this inteface are in JSDOM.DocumentOrShadowRoot.
Constructors
DocumentOrShadowRoot | |
Fields |
Instances
class IsGObject o => IsDocumentOrShadowRoot o Source #
newtype DocumentTimeline Source #
Functions for this inteface are in JSDOM.DocumentTimeline. Base interface functions are in:
Constructors
DocumentTimeline | |
Fields |
newtype DocumentType Source #
Functions for this inteface are in JSDOM.DocumentType. Base interface functions are in:
Constructors
DocumentType | |
Fields |
Instances
newtype DoubleRange Source #
Functions for this inteface are in JSDOM.DoubleRange.
Constructors
DoubleRange | |
Fields |
class IsGObject o => IsDoubleRange o Source #
toDoubleRange :: IsDoubleRange o => o -> DoubleRange Source #
newtype DynamicsCompressorNode Source #
Functions for this inteface are in JSDOM.DynamicsCompressorNode. Base interface functions are in:
Constructors
DynamicsCompressorNode | |
Fields |
Instances
newtype EXTBlendMinMax Source #
Functions for this inteface are in JSDOM.EXTBlendMinMax.
Constructors
EXTBlendMinMax | |
Fields |
newtype EXTFragDepth Source #
Functions for this inteface are in JSDOM.EXTFragDepth.
Constructors
EXTFragDepth | |
Fields |
newtype EXTShaderTextureLOD Source #
Functions for this inteface are in JSDOM.EXTShaderTextureLOD.
Constructors
EXTShaderTextureLOD | |
Fields |
newtype EXTTextureFilterAnisotropic Source #
Functions for this inteface are in JSDOM.EXTTextureFilterAnisotropic.
Constructors
EXTTextureFilterAnisotropic | |
Fields |
Functions for this inteface are in JSDOM.EXTsRGB.
gTypeEXTsRGB :: JSM GType Source #
newtype EcKeyParams Source #
Functions for this inteface are in JSDOM.EcKeyParams. Base interface functions are in:
Constructors
EcKeyParams | |
Fields |
newtype EcdhKeyDeriveParams Source #
Functions for this inteface are in JSDOM.EcdhKeyDeriveParams. Base interface functions are in:
Constructors
EcdhKeyDeriveParams | |
Fields |
newtype EcdsaParams Source #
Functions for this inteface are in JSDOM.EcdsaParams. Base interface functions are in:
Constructors
EcdsaParams | |
Fields |
Functions for this inteface are in JSDOM.Element. Base interface functions are in:
Instances
class (IsNode o, IsEventTarget o, IsSlotable o, IsParentNode o, IsNonDocumentTypeChildNode o, IsDocumentAndElementEventHandlers o, IsChildNode o, IsAnimatable o, IsGObject o) => IsElement o Source #
Instances
gTypeElement :: JSM GType Source #
newtype ElementCSSInlineStyle Source #
Functions for this inteface are in JSDOM.ElementCSSInlineStyle.
Constructors
ElementCSSInlineStyle | |
Fields |
Instances
class IsGObject o => IsElementCSSInlineStyle o Source #
Instances
newtype ErrorEvent Source #
Functions for this inteface are in JSDOM.ErrorEvent. Base interface functions are in:
Constructors
ErrorEvent | |
Fields |
newtype ErrorEventInit Source #
Functions for this inteface are in JSDOM.ErrorEventInit. Base interface functions are in:
Constructors
ErrorEventInit | |
Fields |
Functions for this inteface are in JSDOM.Event.
class IsGObject o => IsEvent o Source #
Instances
gTypeEvent :: JSM GType Source #
Functions for this inteface are in JSDOM.EventInit.
Constructors
EventInit | |
Fields
|
class IsGObject o => IsEventInit o Source #
Instances
toEventInit :: IsEventInit o => o -> EventInit Source #
newtype EventListener Source #
Functions for this inteface are in JSDOM.EventListener.
Constructors
EventListener | |
Fields |
newtype EventListenerOptions Source #
Functions for this inteface are in JSDOM.EventListenerOptions.
Constructors
EventListenerOptions | |
Fields |
Instances
class IsGObject o => IsEventListenerOptions o Source #
newtype EventModifierInit Source #
Functions for this inteface are in JSDOM.EventModifierInit. Base interface functions are in:
Constructors
EventModifierInit | |
Fields |
Instances
class (IsUIEventInit o, IsEventInit o, IsGObject o) => IsEventModifierInit o Source #
toEventModifierInit :: IsEventModifierInit o => o -> EventModifierInit Source #
newtype EventSource Source #
Functions for this inteface are in JSDOM.EventSource. Base interface functions are in:
Constructors
EventSource | |
Fields |
newtype EventSourceInit Source #
Functions for this inteface are in JSDOM.EventSourceInit.
Constructors
EventSourceInit | |
Fields |
newtype EventTarget Source #
Functions for this inteface are in JSDOM.EventTarget.
Constructors
EventTarget | |
Fields |
class IsGObject o => IsEventTarget o Source #
Instances
toEventTarget :: IsEventTarget o => o -> EventTarget Source #
Functions for this inteface are in JSDOM.File. Base interface functions are in:
Functions for this inteface are in JSDOM.FileError.
Constructors
FileError | |
Fields
|
newtype FileException Source #
Functions for this inteface are in JSDOM.FileException.
Constructors
FileException | |
Fields |
Functions for this inteface are in JSDOM.FileList.
Constructors
FileList | |
Fields
|
gTypeFileList :: JSM GType Source #
newtype FilePropertyBag Source #
Functions for this inteface are in JSDOM.FilePropertyBag. Base interface functions are in:
Constructors
FilePropertyBag | |
Fields |
newtype FileReader Source #
Functions for this inteface are in JSDOM.FileReader. Base interface functions are in:
Constructors
FileReader | |
Fields |
newtype FileReaderSync Source #
Functions for this inteface are in JSDOM.FileReaderSync.
Constructors
FileReaderSync | |
Fields |
newtype FocusEvent Source #
Functions for this inteface are in JSDOM.FocusEvent. Base interface functions are in:
Constructors
FocusEvent | |
Fields |
newtype FocusEventInit Source #
Functions for this inteface are in JSDOM.FocusEventInit. Base interface functions are in:
Constructors
FocusEventInit | |
Fields |
Functions for this inteface are in JSDOM.FontFace.
Constructors
FontFace | |
Fields
|
gTypeFontFace :: JSM GType Source #
newtype FontFaceDescriptors Source #
Functions for this inteface are in JSDOM.FontFaceDescriptors.
Constructors
FontFaceDescriptors | |
Fields |
newtype FontFaceSet Source #
Functions for this inteface are in JSDOM.FontFaceSet. Base interface functions are in:
Constructors
FontFaceSet | |
Fields |
Functions for this inteface are in JSDOM.FormData.
Constructors
FormData | |
Fields
|
gTypeFormData :: JSM GType Source #
Functions for this inteface are in JSDOM.GainNode. Base interface functions are in:
Constructors
GainNode | |
Fields
|
gTypeGainNode :: JSM GType Source #
Functions for this inteface are in JSDOM.Gamepad.
gTypeGamepad :: JSM GType Source #
newtype GamepadButton Source #
Functions for this inteface are in JSDOM.GamepadButton.
Constructors
GamepadButton | |
Fields |
newtype GamepadEvent Source #
Functions for this inteface are in JSDOM.GamepadEvent. Base interface functions are in:
Constructors
GamepadEvent | |
Fields |
newtype GamepadEventInit Source #
Functions for this inteface are in JSDOM.GamepadEventInit. Base interface functions are in:
Constructors
GamepadEventInit | |
Fields |
newtype Geolocation Source #
Functions for this inteface are in JSDOM.Geolocation.
Constructors
Geolocation | |
Fields |
newtype Geoposition Source #
Functions for this inteface are in JSDOM.Geoposition.
Constructors
Geoposition | |
Fields |
newtype GetRootNodeOptions Source #
Functions for this inteface are in JSDOM.GetRootNodeOptions.
Constructors
GetRootNodeOptions | |
Fields |
newtype GlobalCrypto Source #
Functions for this inteface are in JSDOM.GlobalCrypto.
Constructors
GlobalCrypto | |
Fields |
class IsGObject o => IsGlobalCrypto o Source #
toGlobalCrypto :: IsGlobalCrypto o => o -> GlobalCrypto Source #
newtype GlobalEventHandlers Source #
Functions for this inteface are in JSDOM.GlobalEventHandlers.
Constructors
GlobalEventHandlers | |
Fields |
class IsGObject o => IsGlobalEventHandlers o Source #
Instances
toGlobalEventHandlers :: IsGlobalEventHandlers o => o -> GlobalEventHandlers Source #
newtype GlobalPerformance Source #
Functions for this inteface are in JSDOM.GlobalPerformance.
Constructors
GlobalPerformance | |
Fields |
class IsGObject o => IsGlobalPerformance o Source #
toGlobalPerformance :: IsGlobalPerformance o => o -> GlobalPerformance Source #
newtype HTMLAllCollection Source #
Functions for this inteface are in JSDOM.HTMLAllCollection.
Constructors
HTMLAllCollection | |
Fields |
newtype HTMLAnchorElement Source #
Functions for this inteface are in JSDOM.HTMLAnchorElement. Base interface functions are in:
Constructors
HTMLAnchorElement | |
Fields |
Instances
newtype HTMLAppletElement Source #
Functions for this inteface are in JSDOM.HTMLAppletElement. Base interface functions are in:
Constructors
HTMLAppletElement | |
Fields |
Instances
newtype HTMLAreaElement Source #
Functions for this inteface are in JSDOM.HTMLAreaElement. Base interface functions are in:
Constructors
HTMLAreaElement | |
Fields |
Instances
newtype HTMLAttachmentElement Source #
Functions for this inteface are in JSDOM.HTMLAttachmentElement. Base interface functions are in:
Constructors
HTMLAttachmentElement | |
Fields |
Instances
newtype HTMLAudioElement Source #
Functions for this inteface are in JSDOM.HTMLAudioElement. Base interface functions are in:
Constructors
HTMLAudioElement | |
Fields |
Instances
newtype HTMLBRElement Source #
Functions for this inteface are in JSDOM.HTMLBRElement. Base interface functions are in:
Constructors
HTMLBRElement | |
Fields |
Instances
newtype HTMLBaseElement Source #
Functions for this inteface are in JSDOM.HTMLBaseElement. Base interface functions are in:
Constructors
HTMLBaseElement | |
Fields |
Instances
newtype HTMLBodyElement Source #
Functions for this inteface are in JSDOM.HTMLBodyElement. Base interface functions are in:
Constructors
HTMLBodyElement | |
Fields |
Instances
newtype HTMLButtonElement Source #
Functions for this inteface are in JSDOM.HTMLButtonElement. Base interface functions are in:
Constructors
HTMLButtonElement | |
Fields |
Instances
newtype HTMLCanvasElement Source #
Functions for this inteface are in JSDOM.HTMLCanvasElement. Base interface functions are in:
Constructors
HTMLCanvasElement | |
Fields |
Instances
newtype HTMLCollection Source #
Functions for this inteface are in JSDOM.HTMLCollection.
Constructors
HTMLCollection | |
Fields |
Instances
class IsGObject o => IsHTMLCollection o Source #
toHTMLCollection :: IsHTMLCollection o => o -> HTMLCollection Source #
newtype HTMLDListElement Source #
Functions for this inteface are in JSDOM.HTMLDListElement. Base interface functions are in:
Constructors
HTMLDListElement | |
Fields |
Instances
newtype HTMLDataElement Source #
Functions for this inteface are in JSDOM.HTMLDataElement. Base interface functions are in:
Constructors
HTMLDataElement | |
Fields |
Instances
newtype HTMLDataListElement Source #
Functions for this inteface are in JSDOM.HTMLDataListElement. Base interface functions are in:
Constructors
HTMLDataListElement | |
Fields |
Instances
newtype HTMLDetailsElement Source #
Functions for this inteface are in JSDOM.HTMLDetailsElement. Base interface functions are in:
Constructors
HTMLDetailsElement | |
Fields |
Instances
newtype HTMLDirectoryElement Source #
Functions for this inteface are in JSDOM.HTMLDirectoryElement. Base interface functions are in:
Constructors
HTMLDirectoryElement | |
Fields |
Instances
newtype HTMLDivElement Source #
Functions for this inteface are in JSDOM.HTMLDivElement. Base interface functions are in:
Constructors
HTMLDivElement | |
Fields |
Instances
newtype HTMLDocument Source #
Functions for this inteface are in JSDOM.HTMLDocument. Base interface functions are in:
Constructors
HTMLDocument | |
Fields |
Instances
newtype HTMLElement Source #
Functions for this inteface are in JSDOM.HTMLElement. Base interface functions are in:
Constructors
HTMLElement | |
Fields |
Instances
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 Source #
Instances
toHTMLElement :: IsHTMLElement o => o -> HTMLElement Source #
newtype HTMLEmbedElement Source #
Functions for this inteface are in JSDOM.HTMLEmbedElement. Base interface functions are in:
Constructors
HTMLEmbedElement | |
Fields |
Instances
newtype HTMLFieldSetElement Source #
Functions for this inteface are in JSDOM.HTMLFieldSetElement. Base interface functions are in:
Constructors
HTMLFieldSetElement | |
Fields |
Instances
newtype HTMLFontElement Source #
Functions for this inteface are in JSDOM.HTMLFontElement. Base interface functions are in:
Constructors
HTMLFontElement | |
Fields |
Instances
newtype HTMLFormControlsCollection Source #
Functions for this inteface are in JSDOM.HTMLFormControlsCollection. Base interface functions are in:
Constructors
HTMLFormControlsCollection | |
Fields |
Instances
newtype HTMLFormElement Source #
Functions for this inteface are in JSDOM.HTMLFormElement. Base interface functions are in:
Constructors
HTMLFormElement | |
Fields |
Instances
newtype HTMLFrameElement Source #
Functions for this inteface are in JSDOM.HTMLFrameElement. Base interface functions are in:
Constructors
HTMLFrameElement | |
Fields |
Instances
newtype HTMLFrameSetElement Source #
Functions for this inteface are in JSDOM.HTMLFrameSetElement. Base interface functions are in:
Constructors
HTMLFrameSetElement | |
Fields |
Instances
newtype HTMLHRElement Source #
Functions for this inteface are in JSDOM.HTMLHRElement. Base interface functions are in:
Constructors
HTMLHRElement | |
Fields |
Instances
newtype HTMLHeadElement Source #
Functions for this inteface are in JSDOM.HTMLHeadElement. Base interface functions are in:
Constructors
HTMLHeadElement | |
Fields |
Instances
newtype HTMLHeadingElement Source #
Functions for this inteface are in JSDOM.HTMLHeadingElement. Base interface functions are in:
Constructors
HTMLHeadingElement | |
Fields |
Instances
newtype HTMLHtmlElement Source #
Functions for this inteface are in JSDOM.HTMLHtmlElement. Base interface functions are in:
Constructors
HTMLHtmlElement | |
Fields |
Instances
newtype HTMLHyperlinkElementUtils Source #
Functions for this inteface are in JSDOM.HTMLHyperlinkElementUtils.
Constructors
HTMLHyperlinkElementUtils | |
Fields |
Instances
class IsGObject o => IsHTMLHyperlinkElementUtils o Source #
toHTMLHyperlinkElementUtils :: IsHTMLHyperlinkElementUtils o => o -> HTMLHyperlinkElementUtils Source #
newtype HTMLIFrameElement Source #
Functions for this inteface are in JSDOM.HTMLIFrameElement. Base interface functions are in:
Constructors
HTMLIFrameElement | |
Fields |
Instances
newtype HTMLImageElement Source #
Functions for this inteface are in JSDOM.HTMLImageElement. Base interface functions are in:
Constructors
HTMLImageElement | |
Fields |
Instances
newtype HTMLInputElement Source #
Functions for this inteface are in JSDOM.HTMLInputElement. Base interface functions are in:
Constructors
HTMLInputElement | |
Fields |
Instances
newtype HTMLKeygenElement Source #
Functions for this inteface are in JSDOM.HTMLKeygenElement. Base interface functions are in:
Constructors
HTMLKeygenElement | |
Fields |
Instances
newtype HTMLLIElement Source #
Functions for this inteface are in JSDOM.HTMLLIElement. Base interface functions are in:
Constructors
HTMLLIElement | |
Fields |
Instances
newtype HTMLLabelElement Source #
Functions for this inteface are in JSDOM.HTMLLabelElement. Base interface functions are in:
Constructors
HTMLLabelElement | |
Fields |
Instances
newtype HTMLLegendElement Source #
Functions for this inteface are in JSDOM.HTMLLegendElement. Base interface functions are in:
Constructors
HTMLLegendElement | |
Fields |
Instances
newtype HTMLLinkElement Source #
Functions for this inteface are in JSDOM.HTMLLinkElement. Base interface functions are in:
Constructors
HTMLLinkElement | |
Fields |
Instances
newtype HTMLMapElement Source #
Functions for this inteface are in JSDOM.HTMLMapElement. Base interface functions are in:
Constructors
HTMLMapElement | |
Fields |
Instances
newtype HTMLMarqueeElement Source #
Functions for this inteface are in JSDOM.HTMLMarqueeElement. Base interface functions are in:
Constructors
HTMLMarqueeElement | |
Fields |
Instances
newtype HTMLMediaElement Source #
Functions for this inteface are in JSDOM.HTMLMediaElement. Base interface functions are in:
Constructors
HTMLMediaElement | |
Fields |
Instances
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 Source #
toHTMLMediaElement :: IsHTMLMediaElement o => o -> HTMLMediaElement Source #
newtype HTMLMenuElement Source #
Functions for this inteface are in JSDOM.HTMLMenuElement. Base interface functions are in:
Constructors
HTMLMenuElement | |
Fields |
Instances
newtype HTMLMetaElement Source #
Functions for this inteface are in JSDOM.HTMLMetaElement. Base interface functions are in:
Constructors
HTMLMetaElement | |
Fields |
Instances
newtype HTMLMeterElement Source #
Functions for this inteface are in JSDOM.HTMLMeterElement. Base interface functions are in:
Constructors
HTMLMeterElement | |
Fields |
Instances
newtype HTMLModElement Source #
Functions for this inteface are in JSDOM.HTMLModElement. Base interface functions are in:
Constructors
HTMLModElement | |
Fields |
Instances
newtype HTMLOListElement Source #
Functions for this inteface are in JSDOM.HTMLOListElement. Base interface functions are in:
Constructors
HTMLOListElement | |
Fields |
Instances
newtype HTMLObjectElement Source #
Functions for this inteface are in JSDOM.HTMLObjectElement. Base interface functions are in:
Constructors
HTMLObjectElement | |
Fields |
Instances
newtype HTMLOptGroupElement Source #
Functions for this inteface are in JSDOM.HTMLOptGroupElement. Base interface functions are in:
Constructors
HTMLOptGroupElement | |
Fields |
Instances
newtype HTMLOptionElement Source #
Functions for this inteface are in JSDOM.HTMLOptionElement. Base interface functions are in:
Constructors
HTMLOptionElement | |
Fields |
Instances
newtype HTMLOptionsCollection Source #
Functions for this inteface are in JSDOM.HTMLOptionsCollection. Base interface functions are in:
Constructors
HTMLOptionsCollection | |
Fields |
Instances
newtype HTMLOutputElement Source #
Functions for this inteface are in JSDOM.HTMLOutputElement. Base interface functions are in:
Constructors
HTMLOutputElement | |
Fields |
Instances
newtype HTMLParagraphElement Source #
Functions for this inteface are in JSDOM.HTMLParagraphElement. Base interface functions are in:
Constructors
HTMLParagraphElement | |
Fields |
Instances
newtype HTMLParamElement Source #
Functions for this inteface are in JSDOM.HTMLParamElement. Base interface functions are in:
Constructors
HTMLParamElement | |
Fields |
Instances
newtype HTMLPictureElement Source #
Functions for this inteface are in JSDOM.HTMLPictureElement. Base interface functions are in:
Constructors
HTMLPictureElement | |
Fields |
Instances
newtype HTMLPreElement Source #
Functions for this inteface are in JSDOM.HTMLPreElement. Base interface functions are in:
Constructors
HTMLPreElement | |
Fields |
Instances
newtype HTMLProgressElement Source #
Functions for this inteface are in JSDOM.HTMLProgressElement. Base interface functions are in:
Constructors
HTMLProgressElement | |
Fields |
Instances
newtype HTMLQuoteElement Source #
Functions for this inteface are in JSDOM.HTMLQuoteElement. Base interface functions are in:
Constructors
HTMLQuoteElement | |
Fields |
Instances
newtype HTMLScriptElement Source #
Functions for this inteface are in JSDOM.HTMLScriptElement. Base interface functions are in:
Constructors
HTMLScriptElement | |
Fields |
Instances
newtype HTMLSelectElement Source #
Functions for this inteface are in JSDOM.HTMLSelectElement. Base interface functions are in:
Constructors
HTMLSelectElement | |
Fields |
Instances
newtype HTMLSlotElement Source #
Functions for this inteface are in JSDOM.HTMLSlotElement. Base interface functions are in:
Constructors
HTMLSlotElement | |
Fields |
Instances
newtype HTMLSourceElement Source #
Functions for this inteface are in JSDOM.HTMLSourceElement. Base interface functions are in:
Constructors
HTMLSourceElement | |
Fields |
Instances
newtype HTMLSpanElement Source #
Functions for this inteface are in JSDOM.HTMLSpanElement. Base interface functions are in:
Constructors
HTMLSpanElement | |
Fields |
Instances
newtype HTMLStyleElement Source #
Functions for this inteface are in JSDOM.HTMLStyleElement. Base interface functions are in:
Constructors
HTMLStyleElement | |
Fields |
Instances
newtype HTMLTableCaptionElement Source #
Functions for this inteface are in JSDOM.HTMLTableCaptionElement. Base interface functions are in:
Constructors
HTMLTableCaptionElement | |
Fields |
Instances
newtype HTMLTableCellElement Source #
Functions for this inteface are in JSDOM.HTMLTableCellElement. Base interface functions are in:
Constructors
HTMLTableCellElement | |
Fields |
Instances
newtype HTMLTableColElement Source #
Functions for this inteface are in JSDOM.HTMLTableColElement. Base interface functions are in:
Constructors
HTMLTableColElement | |
Fields |
Instances
newtype HTMLTableElement Source #
Functions for this inteface are in JSDOM.HTMLTableElement. Base interface functions are in:
Constructors
HTMLTableElement | |
Fields |
Instances
newtype HTMLTableRowElement Source #
Functions for this inteface are in JSDOM.HTMLTableRowElement. Base interface functions are in:
Constructors
HTMLTableRowElement | |
Fields |
Instances
newtype HTMLTableSectionElement Source #
Functions for this inteface are in JSDOM.HTMLTableSectionElement. Base interface functions are in:
Constructors
HTMLTableSectionElement | |
Fields |
Instances
newtype HTMLTemplateElement Source #
Functions for this inteface are in JSDOM.HTMLTemplateElement. Base interface functions are in:
Constructors
HTMLTemplateElement | |
Fields |
Instances
newtype HTMLTextAreaElement Source #
Functions for this inteface are in JSDOM.HTMLTextAreaElement. Base interface functions are in:
Constructors
HTMLTextAreaElement | |
Fields |
Instances
newtype HTMLTimeElement Source #
Functions for this inteface are in JSDOM.HTMLTimeElement. Base interface functions are in:
Constructors
HTMLTimeElement | |
Fields |
Instances
newtype HTMLTitleElement Source #
Functions for this inteface are in JSDOM.HTMLTitleElement. Base interface functions are in:
Constructors
HTMLTitleElement | |
Fields |
Instances
newtype HTMLTrackElement Source #
Functions for this inteface are in JSDOM.HTMLTrackElement. Base interface functions are in:
Constructors
HTMLTrackElement | |
Fields |
Instances
newtype HTMLUListElement Source #
Functions for this inteface are in JSDOM.HTMLUListElement. Base interface functions are in:
Constructors
HTMLUListElement | |
Fields |
Instances
newtype HTMLUnknownElement Source #
Functions for this inteface are in JSDOM.HTMLUnknownElement. Base interface functions are in:
Constructors
HTMLUnknownElement | |
Fields |
Instances
newtype HTMLVideoElement Source #
Functions for this inteface are in JSDOM.HTMLVideoElement. Base interface functions are in:
Constructors
HTMLVideoElement | |
Fields |
Instances
newtype HashChangeEvent Source #
Functions for this inteface are in JSDOM.HashChangeEvent. Base interface functions are in:
Constructors
HashChangeEvent | |
Fields |
newtype HashChangeEventInit Source #
Functions for this inteface are in JSDOM.HashChangeEventInit. Base interface functions are in:
Constructors
HashChangeEventInit | |
Fields |
Functions for this inteface are in JSDOM.Headers.
gTypeHeaders :: JSM GType Source #
Functions for this inteface are in JSDOM.History.
gTypeHistory :: JSM GType Source #
newtype HkdfParams Source #
Functions for this inteface are in JSDOM.HkdfParams. Base interface functions are in:
Constructors
HkdfParams | |
Fields |
newtype HmacKeyParams Source #
Functions for this inteface are in JSDOM.HmacKeyParams. Base interface functions are in:
Constructors
HmacKeyParams | |
Fields |
Functions for this inteface are in JSDOM.IDBCursor.
Constructors
IDBCursor | |
Fields
|
class IsGObject o => IsIDBCursor o Source #
Instances
toIDBCursor :: IsIDBCursor o => o -> IDBCursor Source #
newtype IDBCursorWithValue Source #
Functions for this inteface are in JSDOM.IDBCursorWithValue. Base interface functions are in:
Constructors
IDBCursorWithValue | |
Fields |
Instances
newtype IDBDatabase Source #
Functions for this inteface are in JSDOM.IDBDatabase. Base interface functions are in:
Constructors
IDBDatabase | |
Fields |
newtype IDBFactory Source #
Functions for this inteface are in JSDOM.IDBFactory.
Constructors
IDBFactory | |
Fields |
Functions for this inteface are in JSDOM.IDBIndex.
Constructors
IDBIndex | |
Fields
|
gTypeIDBIndex :: JSM GType Source #
newtype IDBIndexParameters Source #
Functions for this inteface are in JSDOM.IDBIndexParameters.
Constructors
IDBIndexParameters | |
Fields |
newtype IDBKeyRange Source #
Functions for this inteface are in JSDOM.IDBKeyRange.
Constructors
IDBKeyRange | |
Fields |
newtype IDBObjectStore Source #
Functions for this inteface are in JSDOM.IDBObjectStore.
Constructors
IDBObjectStore | |
Fields |
newtype IDBObjectStoreParameters Source #
Functions for this inteface are in JSDOM.IDBObjectStoreParameters.
Constructors
IDBObjectStoreParameters | |
Fields |
newtype IDBOpenDBRequest Source #
Functions for this inteface are in JSDOM.IDBOpenDBRequest. Base interface functions are in:
Constructors
IDBOpenDBRequest | |
Fields |
Instances
newtype IDBRequest Source #
Functions for this inteface are in JSDOM.IDBRequest. Base interface functions are in:
Constructors
IDBRequest | |
Fields |
class (IsEventTarget o, IsGObject o) => IsIDBRequest o Source #
Instances
toIDBRequest :: IsIDBRequest o => o -> IDBRequest Source #
newtype IDBTransaction Source #
Functions for this inteface are in JSDOM.IDBTransaction. Base interface functions are in:
Constructors
IDBTransaction | |
Fields |
newtype IDBVersionChangeEvent Source #
Functions for this inteface are in JSDOM.IDBVersionChangeEvent. Base interface functions are in:
Constructors
IDBVersionChangeEvent | |
Fields |
newtype IDBVersionChangeEventInit Source #
Functions for this inteface are in JSDOM.IDBVersionChangeEventInit. Base interface functions are in:
Constructors
IDBVersionChangeEventInit | |
Fields |
Instances
Functions for this inteface are in JSDOM.ImageData.
Constructors
ImageData | |
Fields
|
newtype InputEvent Source #
Functions for this inteface are in JSDOM.InputEvent. Base interface functions are in:
Constructors
InputEvent | |
Fields |
newtype InputEventInit Source #
Functions for this inteface are in JSDOM.InputEventInit. Base interface functions are in:
Constructors
InputEventInit | |
Fields |
newtype InspectorFrontendHost Source #
Functions for this inteface are in JSDOM.InspectorFrontendHost.
Constructors
InspectorFrontendHost | |
Fields |
newtype IntersectionObserver Source #
Functions for this inteface are in JSDOM.IntersectionObserver.
Constructors
IntersectionObserver | |
Fields |
newtype IntersectionObserverEntry Source #
Functions for this inteface are in JSDOM.IntersectionObserverEntry.
Constructors
IntersectionObserverEntry | |
Fields |
newtype IntersectionObserverEntryInit Source #
Functions for this inteface are in JSDOM.IntersectionObserverEntryInit.
Constructors
IntersectionObserverEntryInit | |
Fields |
Instances
newtype IntersectionObserverInit Source #
Functions for this inteface are in JSDOM.IntersectionObserverInit.
Constructors
IntersectionObserverInit | |
Fields |
newtype JsonWebKey Source #
Functions for this inteface are in JSDOM.JsonWebKey.
Constructors
JsonWebKey | |
Fields |
newtype KeyboardEvent Source #
Functions for this inteface are in JSDOM.KeyboardEvent. Base interface functions are in:
Constructors
KeyboardEvent | |
Fields |
newtype KeyboardEventInit Source #
Functions for this inteface are in JSDOM.KeyboardEventInit. Base interface functions are in:
Constructors
KeyboardEventInit | |
Fields |
Instances
newtype KeyframeEffect Source #
Functions for this inteface are in JSDOM.KeyframeEffect. Base interface functions are in:
Constructors
KeyframeEffect | |
Fields |
Functions for this inteface are in JSDOM.Location.
Constructors
Location | |
Fields
|
gTypeLocation :: JSM GType Source #
Functions for this inteface are in JSDOM.LongRange.
Constructors
LongRange | |
Fields
|
class IsGObject o => IsLongRange o Source #
Instances
toLongRange :: IsLongRange o => o -> LongRange Source #
newtype MediaController Source #
Functions for this inteface are in JSDOM.MediaController. Base interface functions are in:
Constructors
MediaController | |
Fields |
newtype MediaControlsHost Source #
Functions for this inteface are in JSDOM.MediaControlsHost.
Constructors
MediaControlsHost | |
Fields |
newtype MediaDeviceInfo Source #
Functions for this inteface are in JSDOM.MediaDeviceInfo.
Constructors
MediaDeviceInfo | |
Fields |
newtype MediaDevices Source #
Functions for this inteface are in JSDOM.MediaDevices.
Constructors
MediaDevices | |
Fields |
newtype MediaElementAudioSourceNode Source #
Functions for this inteface are in JSDOM.MediaElementAudioSourceNode. Base interface functions are in:
Constructors
MediaElementAudioSourceNode | |
Fields |
Instances
newtype MediaEncryptedEvent Source #
Functions for this inteface are in JSDOM.MediaEncryptedEvent. Base interface functions are in:
Constructors
MediaEncryptedEvent | |
Fields |
newtype MediaEncryptedEventInit Source #
Functions for this inteface are in JSDOM.MediaEncryptedEventInit. Base interface functions are in:
Constructors
MediaEncryptedEventInit | |
Fields |
Instances
newtype MediaError Source #
Functions for this inteface are in JSDOM.MediaError.
Constructors
MediaError | |
Fields |
newtype MediaKeyMessageEvent Source #
Functions for this inteface are in JSDOM.MediaKeyMessageEvent. Base interface functions are in:
Constructors
MediaKeyMessageEvent | |
Fields |
newtype MediaKeyMessageEventInit Source #
Functions for this inteface are in JSDOM.MediaKeyMessageEventInit. Base interface functions are in:
Constructors
MediaKeyMessageEventInit | |
Fields |
Instances
newtype MediaKeySession Source #
Functions for this inteface are in JSDOM.MediaKeySession. Base interface functions are in:
Constructors
MediaKeySession | |
Fields |
newtype MediaKeyStatusMap Source #
Functions for this inteface are in JSDOM.MediaKeyStatusMap.
Constructors
MediaKeyStatusMap | |
Fields |
newtype MediaKeySystemAccess Source #
Functions for this inteface are in JSDOM.MediaKeySystemAccess.
Constructors
MediaKeySystemAccess | |
Fields |
newtype MediaKeySystemConfiguration Source #
Functions for this inteface are in JSDOM.MediaKeySystemConfiguration.
Constructors
MediaKeySystemConfiguration | |
Fields |
newtype MediaKeySystemMediaCapability Source #
Functions for this inteface are in JSDOM.MediaKeySystemMediaCapability.
Constructors
MediaKeySystemMediaCapability | |
Fields |
Instances
Functions for this inteface are in JSDOM.MediaKeys.
Constructors
MediaKeys | |
Fields
|
Functions for this inteface are in JSDOM.MediaList.
Constructors
MediaList | |
Fields
|
newtype MediaMetadata Source #
Functions for this inteface are in JSDOM.MediaMetadata.
Constructors
MediaMetadata | |
Fields |
newtype MediaQueryList Source #
Functions for this inteface are in JSDOM.MediaQueryList.
Constructors
MediaQueryList | |
Fields |
newtype MediaRemoteControls Source #
Functions for this inteface are in JSDOM.MediaRemoteControls. Base interface functions are in:
Constructors
MediaRemoteControls | |
Fields |
newtype MediaSession Source #
Functions for this inteface are in JSDOM.MediaSession.
Constructors
MediaSession | |
Fields |
newtype MediaSource Source #
Functions for this inteface are in JSDOM.MediaSource. Base interface functions are in:
Constructors
MediaSource | |
Fields |
newtype MediaStream Source #
Functions for this inteface are in JSDOM.MediaStream. Base interface functions are in:
Constructors
MediaStream | |
Fields |
newtype MediaStreamAudioDestinationNode Source #
Functions for this inteface are in JSDOM.MediaStreamAudioDestinationNode. Base interface functions are in:
Constructors
MediaStreamAudioDestinationNode | |
Fields |
Instances
newtype MediaStreamAudioSourceNode Source #
Functions for this inteface are in JSDOM.MediaStreamAudioSourceNode. Base interface functions are in:
Constructors
MediaStreamAudioSourceNode | |
Fields |
Instances
newtype MediaStreamConstraints Source #
Functions for this inteface are in JSDOM.MediaStreamConstraints.
Constructors
MediaStreamConstraints | |
Fields |
newtype MediaStreamEvent Source #
Functions for this inteface are in JSDOM.MediaStreamEvent. Base interface functions are in:
Constructors
MediaStreamEvent | |
Fields |
newtype MediaStreamEventInit Source #
Functions for this inteface are in JSDOM.MediaStreamEventInit. Base interface functions are in:
Constructors
MediaStreamEventInit | |
Fields |
newtype MediaStreamTrack Source #
Functions for this inteface are in JSDOM.MediaStreamTrack. Base interface functions are in:
Constructors
MediaStreamTrack | |
Fields |
Instances
class (IsEventTarget o, IsGObject o) => IsMediaStreamTrack o Source #
toMediaStreamTrack :: IsMediaStreamTrack o => o -> MediaStreamTrack Source #
newtype MediaStreamTrackEvent Source #
Functions for this inteface are in JSDOM.MediaStreamTrackEvent. Base interface functions are in:
Constructors
MediaStreamTrackEvent | |
Fields |
newtype MediaStreamTrackEventInit Source #
Functions for this inteface are in JSDOM.MediaStreamTrackEventInit. Base interface functions are in:
Constructors
MediaStreamTrackEventInit | |
Fields |
Instances
newtype MediaTrackCapabilities Source #
Functions for this inteface are in JSDOM.MediaTrackCapabilities.
Constructors
MediaTrackCapabilities | |
Fields |
newtype MediaTrackConstraintSet Source #
Functions for this inteface are in JSDOM.MediaTrackConstraintSet.
Constructors
MediaTrackConstraintSet | |
Fields |
Instances
class IsGObject o => IsMediaTrackConstraintSet o Source #
newtype MediaTrackConstraints Source #
Functions for this inteface are in JSDOM.MediaTrackConstraints. Base interface functions are in:
Constructors
MediaTrackConstraints | |
Fields |
Instances
newtype MediaTrackSettings Source #
Functions for this inteface are in JSDOM.MediaTrackSettings.
Constructors
MediaTrackSettings | |
Fields |
newtype MediaTrackSupportedConstraints Source #
Functions for this inteface are in JSDOM.MediaTrackSupportedConstraints.
Constructors
MediaTrackSupportedConstraints | |
Fields |
Instances
newtype MessageChannel Source #
Functions for this inteface are in JSDOM.MessageChannel.
Constructors
MessageChannel | |
Fields |
newtype MessageEvent Source #
Functions for this inteface are in JSDOM.MessageEvent. Base interface functions are in:
Constructors
MessageEvent | |
Fields |
newtype MessageEventInit Source #
Functions for this inteface are in JSDOM.MessageEventInit. Base interface functions are in:
Constructors
MessageEventInit | |
Fields |
newtype MessagePort Source #
Functions for this inteface are in JSDOM.MessagePort. Base interface functions are in:
Constructors
MessagePort | |
Fields |
Functions for this inteface are in JSDOM.MimeType.
Constructors
MimeType | |
Fields
|
gTypeMimeType :: JSM GType Source #
newtype MimeTypeArray Source #
Functions for this inteface are in JSDOM.MimeTypeArray.
Constructors
MimeTypeArray | |
Fields |
newtype MouseEvent Source #
Functions for this inteface are in JSDOM.MouseEvent. Base interface functions are in:
Constructors
MouseEvent | |
Fields |
toMouseEvent :: IsMouseEvent o => o -> MouseEvent Source #
newtype MouseEventInit Source #
Functions for this inteface are in JSDOM.MouseEventInit. Base interface functions are in:
Constructors
MouseEventInit | |
Fields |
Instances
class (IsEventModifierInit o, IsUIEventInit o, IsEventInit o, IsGObject o) => IsMouseEventInit o Source #
toMouseEventInit :: IsMouseEventInit o => o -> MouseEventInit Source #
newtype MutationEvent Source #
Functions for this inteface are in JSDOM.MutationEvent. Base interface functions are in:
Constructors
MutationEvent | |
Fields |
newtype MutationObserver Source #
Functions for this inteface are in JSDOM.MutationObserver.
Constructors
MutationObserver | |
Fields |
newtype MutationObserverInit Source #
Functions for this inteface are in JSDOM.MutationObserverInit.
Constructors
MutationObserverInit | |
Fields |
newtype MutationRecord Source #
Functions for this inteface are in JSDOM.MutationRecord.
Constructors
MutationRecord | |
Fields |
newtype NamedNodeMap Source #
Functions for this inteface are in JSDOM.NamedNodeMap.
Constructors
NamedNodeMap | |
Fields |
Functions for this inteface are in JSDOM.Navigator. Base interface functions are in:
Constructors
Navigator | |
Fields
|
newtype NavigatorConcurrentHardware Source #
Functions for this inteface are in JSDOM.NavigatorConcurrentHardware.
Constructors
NavigatorConcurrentHardware | |
Fields |
class IsGObject o => IsNavigatorConcurrentHardware o Source #
toNavigatorConcurrentHardware :: IsNavigatorConcurrentHardware o => o -> NavigatorConcurrentHardware Source #
newtype NavigatorID Source #
Functions for this inteface are in JSDOM.NavigatorID.
Constructors
NavigatorID | |
Fields |
class IsGObject o => IsNavigatorID o Source #
toNavigatorID :: IsNavigatorID o => o -> NavigatorID Source #
newtype NavigatorLanguage Source #
Functions for this inteface are in JSDOM.NavigatorLanguage.
Constructors
NavigatorLanguage | |
Fields |
class IsGObject o => IsNavigatorLanguage o Source #
toNavigatorLanguage :: IsNavigatorLanguage o => o -> NavigatorLanguage Source #
newtype NavigatorOnLine Source #
Functions for this inteface are in JSDOM.NavigatorOnLine.
Constructors
NavigatorOnLine | |
Fields |
class IsGObject o => IsNavigatorOnLine o Source #
toNavigatorOnLine :: IsNavigatorOnLine o => o -> NavigatorOnLine Source #
newtype NavigatorUserMediaError Source #
Functions for this inteface are in JSDOM.NavigatorUserMediaError. Base interface functions are in:
Constructors
NavigatorUserMediaError | |
Fields |
Functions for this inteface are in JSDOM.Node. Base interface functions are in:
class (IsEventTarget o, IsGObject o) => IsNode o Source #
Instances
newtype NodeIterator Source #
Functions for this inteface are in JSDOM.NodeIterator.
Constructors
NodeIterator | |
Fields |
Functions for this inteface are in JSDOM.NodeList.
Constructors
NodeList | |
Fields
|
class IsGObject o => IsNodeList o Source #
Instances
toNodeList :: IsNodeList o => o -> NodeList Source #
gTypeNodeList :: JSM GType Source #
newtype NonDocumentTypeChildNode Source #
Functions for this inteface are in JSDOM.NonDocumentTypeChildNode.
Constructors
NonDocumentTypeChildNode | |
Fields |
Instances
class IsGObject o => IsNonDocumentTypeChildNode o Source #
Instances
toNonDocumentTypeChildNode :: IsNonDocumentTypeChildNode o => o -> NonDocumentTypeChildNode Source #
newtype NonElementParentNode Source #
Functions for this inteface are in JSDOM.NonElementParentNode.
Constructors
NonElementParentNode | |
Fields |
Instances
class IsGObject o => IsNonElementParentNode o Source #
newtype Notification Source #
Functions for this inteface are in JSDOM.Notification. Base interface functions are in:
Constructors
Notification | |
Fields |
newtype NotificationOptions Source #
Functions for this inteface are in JSDOM.NotificationOptions.
Constructors
NotificationOptions | |
Fields |
newtype OESElementIndexUint Source #
Functions for this inteface are in JSDOM.OESElementIndexUint.
Constructors
OESElementIndexUint | |
Fields |
newtype OESStandardDerivatives Source #
Functions for this inteface are in JSDOM.OESStandardDerivatives.
Constructors
OESStandardDerivatives | |
Fields |
newtype OESTextureFloat Source #
Functions for this inteface are in JSDOM.OESTextureFloat.
Constructors
OESTextureFloat | |
Fields |
newtype OESTextureFloatLinear Source #
Functions for this inteface are in JSDOM.OESTextureFloatLinear.
Constructors
OESTextureFloatLinear | |
Fields |
newtype OESTextureHalfFloat Source #
Functions for this inteface are in JSDOM.OESTextureHalfFloat.
Constructors
OESTextureHalfFloat | |
Fields |
newtype OESTextureHalfFloatLinear Source #
Functions for this inteface are in JSDOM.OESTextureHalfFloatLinear.
Constructors
OESTextureHalfFloatLinear | |
Fields |
newtype OESVertexArrayObject Source #
Functions for this inteface are in JSDOM.OESVertexArrayObject.
Constructors
OESVertexArrayObject | |
Fields |
newtype OfflineAudioCompletionEvent Source #
Functions for this inteface are in JSDOM.OfflineAudioCompletionEvent. Base interface functions are in:
Constructors
OfflineAudioCompletionEvent | |
Fields |
Instances
newtype OfflineAudioContext Source #
Functions for this inteface are in JSDOM.OfflineAudioContext. Base interface functions are in:
Constructors
OfflineAudioContext | |
Fields |
Instances
newtype OscillatorNode Source #
Functions for this inteface are in JSDOM.OscillatorNode. Base interface functions are in:
Constructors
OscillatorNode | |
Fields |
newtype OverconstrainedError Source #
Functions for this inteface are in JSDOM.OverconstrainedError.
Constructors
OverconstrainedError | |
Fields |
newtype OverconstrainedErrorEvent Source #
Functions for this inteface are in JSDOM.OverconstrainedErrorEvent. Base interface functions are in:
Constructors
OverconstrainedErrorEvent | |
Fields |
Instances
newtype OverconstrainedErrorEventInit Source #
Functions for this inteface are in JSDOM.OverconstrainedErrorEventInit. Base interface functions are in:
Constructors
OverconstrainedErrorEventInit | |
Fields |
Instances
newtype OverflowEvent Source #
Functions for this inteface are in JSDOM.OverflowEvent. Base interface functions are in:
Constructors
OverflowEvent | |
Fields |
newtype OverflowEventInit Source #
Functions for this inteface are in JSDOM.OverflowEventInit. Base interface functions are in:
Constructors
OverflowEventInit | |
Fields |
newtype PageTransitionEvent Source #
Functions for this inteface are in JSDOM.PageTransitionEvent. Base interface functions are in:
Constructors
PageTransitionEvent | |
Fields |
newtype PageTransitionEventInit Source #
Functions for this inteface are in JSDOM.PageTransitionEventInit. Base interface functions are in:
Constructors
PageTransitionEventInit | |
Fields |
Instances
newtype PannerNode Source #
Functions for this inteface are in JSDOM.PannerNode. Base interface functions are in:
Constructors
PannerNode | |
Fields |
newtype ParentNode Source #
Functions for this inteface are in JSDOM.ParentNode.
Constructors
ParentNode | |
Fields |
class IsGObject o => IsParentNode o Source #
Instances
toParentNode :: IsParentNode o => o -> ParentNode Source #
newtype PasswordCredential Source #
Functions for this inteface are in JSDOM.PasswordCredential. Base interface functions are in:
Constructors
PasswordCredential | |
Fields |
Instances
newtype PasswordCredentialData Source #
Functions for this inteface are in JSDOM.PasswordCredentialData. Base interface functions are in:
Constructors
PasswordCredentialData | |
Fields |
Instances
Functions for this inteface are in JSDOM.Path2D. Base interface functions are in:
gTypePath2D :: JSM GType Source #
newtype Pbkdf2Params Source #
Functions for this inteface are in JSDOM.Pbkdf2Params. Base interface functions are in:
Constructors
Pbkdf2Params | |
Fields |
newtype Performance Source #
Functions for this inteface are in JSDOM.Performance. Base interface functions are in:
Constructors
Performance | |
Fields |
newtype PerformanceEntry Source #
Functions for this inteface are in JSDOM.PerformanceEntry.
Constructors
PerformanceEntry | |
Fields |
class IsGObject o => IsPerformanceEntry o Source #
toPerformanceEntry :: IsPerformanceEntry o => o -> PerformanceEntry Source #
newtype PerformanceMark Source #
Functions for this inteface are in JSDOM.PerformanceMark. Base interface functions are in:
Constructors
PerformanceMark | |
Fields |
newtype PerformanceMeasure Source #
Functions for this inteface are in JSDOM.PerformanceMeasure. Base interface functions are in:
Constructors
PerformanceMeasure | |
Fields |
newtype PerformanceNavigation Source #
Functions for this inteface are in JSDOM.PerformanceNavigation.
Constructors
PerformanceNavigation | |
Fields |
newtype PerformanceObserver Source #
Functions for this inteface are in JSDOM.PerformanceObserver.
Constructors
PerformanceObserver | |
Fields |
newtype PerformanceObserverEntryList Source #
Functions for this inteface are in JSDOM.PerformanceObserverEntryList.
Constructors
PerformanceObserverEntryList | |
Fields |
newtype PerformanceObserverInit Source #
Functions for this inteface are in JSDOM.PerformanceObserverInit.
Constructors
PerformanceObserverInit | |
Fields |
newtype PerformanceResourceTiming Source #
Functions for this inteface are in JSDOM.PerformanceResourceTiming. Base interface functions are in:
Constructors
PerformanceResourceTiming | |
Fields |
Instances
newtype PerformanceTiming Source #
Functions for this inteface are in JSDOM.PerformanceTiming.
Constructors
PerformanceTiming | |
Fields |
newtype PeriodicWave Source #
Functions for this inteface are in JSDOM.PeriodicWave.
Constructors
PeriodicWave | |
Fields |
Functions for this inteface are in JSDOM.Plugin.
gTypePlugin :: JSM GType Source #
newtype PluginArray Source #
Functions for this inteface are in JSDOM.PluginArray.
Constructors
PluginArray | |
Fields |
newtype PopStateEvent Source #
Functions for this inteface are in JSDOM.PopStateEvent. Base interface functions are in:
Constructors
PopStateEvent | |
Fields |
newtype PopStateEventInit Source #
Functions for this inteface are in JSDOM.PopStateEventInit. Base interface functions are in:
Constructors
PopStateEventInit | |
Fields |
newtype PositionError Source #
Functions for this inteface are in JSDOM.PositionError.
Constructors
PositionError | |
Fields |
newtype PositionOptions Source #
Functions for this inteface are in JSDOM.PositionOptions.
Constructors
PositionOptions | |
Fields |
newtype ProcessingInstruction Source #
Functions for this inteface are in JSDOM.ProcessingInstruction. Base interface functions are in:
Constructors
ProcessingInstruction | |
Fields |
Instances
newtype ProgressEvent Source #
Functions for this inteface are in JSDOM.ProgressEvent. Base interface functions are in:
Constructors
ProgressEvent | |
Fields |
class (IsEvent o, IsGObject o) => IsProgressEvent o Source #
toProgressEvent :: IsProgressEvent o => o -> ProgressEvent Source #
newtype ProgressEventInit Source #
Functions for this inteface are in JSDOM.ProgressEventInit. Base interface functions are in:
Constructors
ProgressEventInit | |
Fields |
newtype PromiseRejectionEvent Source #
Functions for this inteface are in JSDOM.PromiseRejectionEvent. Base interface functions are in:
Constructors
PromiseRejectionEvent | |
Fields |
newtype PromiseRejectionEventInit Source #
Functions for this inteface are in JSDOM.PromiseRejectionEventInit. Base interface functions are in:
Constructors
PromiseRejectionEventInit | |
Fields |
Instances
newtype QuickTimePluginReplacement Source #
Functions for this inteface are in JSDOM.QuickTimePluginReplacement.
Constructors
QuickTimePluginReplacement | |
Fields |
Functions for this inteface are in JSDOM.RGBColor.
Constructors
RGBColor | |
Fields
|
gTypeRGBColor :: JSM GType Source #
newtype RTCAnswerOptions Source #
Functions for this inteface are in JSDOM.RTCAnswerOptions. Base interface functions are in:
Constructors
RTCAnswerOptions | |
Fields |
newtype RTCConfiguration Source #
Functions for this inteface are in JSDOM.RTCConfiguration.
Constructors
RTCConfiguration | |
Fields |
newtype RTCDTMFSender Source #
Functions for this inteface are in JSDOM.RTCDTMFSender. Base interface functions are in:
Constructors
RTCDTMFSender | |
Fields |
newtype RTCDTMFToneChangeEvent Source #
Functions for this inteface are in JSDOM.RTCDTMFToneChangeEvent. Base interface functions are in:
Constructors
RTCDTMFToneChangeEvent | |
Fields |
Instances
newtype RTCDTMFToneChangeEventInit Source #
Functions for this inteface are in JSDOM.RTCDTMFToneChangeEventInit. Base interface functions are in:
Constructors
RTCDTMFToneChangeEventInit | |
Fields |
Instances
newtype RTCDataChannel Source #
Functions for this inteface are in JSDOM.RTCDataChannel. Base interface functions are in:
Constructors
RTCDataChannel | |
Fields |
newtype RTCDataChannelEvent Source #
Functions for this inteface are in JSDOM.RTCDataChannelEvent. Base interface functions are in:
Constructors
RTCDataChannelEvent | |
Fields |
newtype RTCDataChannelEventInit Source #
Functions for this inteface are in JSDOM.RTCDataChannelEventInit. Base interface functions are in:
Constructors
RTCDataChannelEventInit | |
Fields |
Instances
newtype RTCDataChannelInit Source #
Functions for this inteface are in JSDOM.RTCDataChannelInit.
Constructors
RTCDataChannelInit | |
Fields |
newtype RTCDataChannelStats Source #
Functions for this inteface are in JSDOM.RTCDataChannelStats. Base interface functions are in:
Constructors
RTCDataChannelStats | |
Fields |
newtype RTCIceCandidate Source #
Functions for this inteface are in JSDOM.RTCIceCandidate.
Constructors
RTCIceCandidate | |
Fields |
newtype RTCIceCandidateEvent Source #
Functions for this inteface are in JSDOM.RTCIceCandidateEvent. Base interface functions are in:
Constructors
RTCIceCandidateEvent | |
Fields |
newtype RTCIceCandidateInit Source #
Functions for this inteface are in JSDOM.RTCIceCandidateInit.
Constructors
RTCIceCandidateInit | |
Fields |
newtype RTCIceServer Source #
Functions for this inteface are in JSDOM.RTCIceServer.
Constructors
RTCIceServer | |
Fields |
newtype RTCIceTransport Source #
Functions for this inteface are in JSDOM.RTCIceTransport.
Constructors
RTCIceTransport | |
Fields |
newtype RTCInboundRTPStreamStats Source #
Functions for this inteface are in JSDOM.RTCInboundRTPStreamStats. Base interface functions are in:
Constructors
RTCInboundRTPStreamStats | |
Fields |
Instances
newtype RTCMediaStreamTrackStats Source #
Functions for this inteface are in JSDOM.RTCMediaStreamTrackStats. Base interface functions are in:
Constructors
RTCMediaStreamTrackStats | |
Fields |
Instances
newtype RTCOfferAnswerOptions Source #
Functions for this inteface are in JSDOM.RTCOfferAnswerOptions.
Constructors
RTCOfferAnswerOptions | |
Fields |
Instances
class IsGObject o => IsRTCOfferAnswerOptions o Source #
newtype RTCOfferOptions Source #
Functions for this inteface are in JSDOM.RTCOfferOptions. Base interface functions are in:
Constructors
RTCOfferOptions | |
Fields |
newtype RTCOutboundRTPStreamStats Source #
Functions for this inteface are in JSDOM.RTCOutboundRTPStreamStats. Base interface functions are in:
Constructors
RTCOutboundRTPStreamStats | |
Fields |
Instances
newtype RTCPeerConnection Source #
Functions for this inteface are in JSDOM.RTCPeerConnection. Base interface functions are in:
Constructors
RTCPeerConnection | |
Fields |
newtype RTCPeerConnectionIceEvent Source #
Functions for this inteface are in JSDOM.RTCPeerConnectionIceEvent. Base interface functions are in:
Constructors
RTCPeerConnectionIceEvent | |
Fields |
Instances
newtype RTCRTPStreamStats Source #
Functions for this inteface are in JSDOM.RTCRTPStreamStats. Base interface functions are in:
Constructors
RTCRTPStreamStats | |
Fields |
Instances
class (IsRTCStats o, IsGObject o) => IsRTCRTPStreamStats o Source #
toRTCRTPStreamStats :: IsRTCRTPStreamStats o => o -> RTCRTPStreamStats Source #
newtype RTCRtpCodecParameters Source #
Functions for this inteface are in JSDOM.RTCRtpCodecParameters.
Constructors
RTCRtpCodecParameters | |
Fields |
newtype RTCRtpEncodingParameters Source #
Functions for this inteface are in JSDOM.RTCRtpEncodingParameters.
Constructors
RTCRtpEncodingParameters | |
Fields |
newtype RTCRtpFecParameters Source #
Functions for this inteface are in JSDOM.RTCRtpFecParameters.
Constructors
RTCRtpFecParameters | |
Fields |
newtype RTCRtpHeaderExtensionParameters Source #
Functions for this inteface are in JSDOM.RTCRtpHeaderExtensionParameters.
Constructors
RTCRtpHeaderExtensionParameters | |
Fields |
Instances
newtype RTCRtpParameters Source #
Functions for this inteface are in JSDOM.RTCRtpParameters.
Constructors
RTCRtpParameters | |
Fields |
newtype RTCRtpReceiver Source #
Functions for this inteface are in JSDOM.RTCRtpReceiver.
Constructors
RTCRtpReceiver | |
Fields |
newtype RTCRtpRtxParameters Source #
Functions for this inteface are in JSDOM.RTCRtpRtxParameters.
Constructors
RTCRtpRtxParameters | |
Fields |
newtype RTCRtpSender Source #
Functions for this inteface are in JSDOM.RTCRtpSender.
Constructors
RTCRtpSender | |
Fields |
newtype RTCRtpTransceiver Source #
Functions for this inteface are in JSDOM.RTCRtpTransceiver.
Constructors
RTCRtpTransceiver | |
Fields |
newtype RTCRtpTransceiverInit Source #
Functions for this inteface are in JSDOM.RTCRtpTransceiverInit.
Constructors
RTCRtpTransceiverInit | |
Fields |
newtype RTCSessionDescription Source #
Functions for this inteface are in JSDOM.RTCSessionDescription.
Constructors
RTCSessionDescription | |
Fields |
newtype RTCSessionDescriptionInit Source #
Functions for this inteface are in JSDOM.RTCSessionDescriptionInit.
Constructors
RTCSessionDescriptionInit | |
Fields |
Functions for this inteface are in JSDOM.RTCStats.
Constructors
RTCStats | |
Fields
|
class IsGObject o => IsRTCStats o Source #
toRTCStats :: IsRTCStats o => o -> RTCStats Source #
gTypeRTCStats :: JSM GType Source #
newtype RTCStatsReport Source #
Functions for this inteface are in JSDOM.RTCStatsReport.
Constructors
RTCStatsReport | |
Fields |
newtype RTCTrackEvent Source #
Functions for this inteface are in JSDOM.RTCTrackEvent. Base interface functions are in:
Constructors
RTCTrackEvent | |
Fields |
newtype RTCTrackEventInit Source #
Functions for this inteface are in JSDOM.RTCTrackEventInit. Base interface functions are in:
Constructors
RTCTrackEventInit | |
Fields |
newtype RadioNodeList Source #
Functions for this inteface are in JSDOM.RadioNodeList. Base interface functions are in:
Constructors
RadioNodeList | |
Fields |
Functions for this inteface are in JSDOM.Range.
gTypeRange :: JSM GType Source #
newtype ReadableByteStreamController Source #
Functions for this inteface are in JSDOM.ReadableByteStreamController.
Constructors
ReadableByteStreamController | |
Fields |
newtype ReadableStream Source #
Functions for this inteface are in JSDOM.ReadableStream.
Constructors
ReadableStream | |
Fields |
newtype ReadableStreamBYOBReader Source #
Functions for this inteface are in JSDOM.ReadableStreamBYOBReader.
Constructors
ReadableStreamBYOBReader | |
Fields |
newtype ReadableStreamBYOBRequest Source #
Functions for this inteface are in JSDOM.ReadableStreamBYOBRequest.
Constructors
ReadableStreamBYOBRequest | |
Fields |
newtype ReadableStreamDefaultController Source #
Functions for this inteface are in JSDOM.ReadableStreamDefaultController.
Constructors
ReadableStreamDefaultController | |
Fields |
Instances
newtype ReadableStreamDefaultReader Source #
Functions for this inteface are in JSDOM.ReadableStreamDefaultReader.
Constructors
ReadableStreamDefaultReader | |
Fields |
newtype ReadableStreamSource Source #
Functions for this inteface are in JSDOM.ReadableStreamSource.
Constructors
ReadableStreamSource | |
Fields |
Functions for this inteface are in JSDOM.Rect.
Functions for this inteface are in JSDOM.Request. Base interface functions are in:
gTypeRequest :: JSM GType Source #
newtype RequestInit Source #
Functions for this inteface are in JSDOM.RequestInit.
Constructors
RequestInit | |
Fields |
Functions for this inteface are in JSDOM.Response.
Constructors
Response | |
Fields
|
gTypeResponse :: JSM GType Source #
newtype RotationRate Source #
Functions for this inteface are in JSDOM.RotationRate.
Constructors
RotationRate | |
Fields |
newtype RsaHashedImportParams Source #
Functions for this inteface are in JSDOM.RsaHashedImportParams. Base interface functions are in:
Constructors
RsaHashedImportParams | |
Fields |
Instances
newtype RsaHashedKeyGenParams Source #
Functions for this inteface are in JSDOM.RsaHashedKeyGenParams. Base interface functions are in:
Constructors
RsaHashedKeyGenParams | |
Fields |
Instances
newtype RsaKeyGenParams Source #
Functions for this inteface are in JSDOM.RsaKeyGenParams. Base interface functions are in:
Constructors
RsaKeyGenParams | |
Fields |
Instances
class (IsCryptoAlgorithmParameters o, IsGObject o) => IsRsaKeyGenParams o Source #
toRsaKeyGenParams :: IsRsaKeyGenParams o => o -> RsaKeyGenParams Source #
newtype RsaOaepParams Source #
Functions for this inteface are in JSDOM.RsaOaepParams. Base interface functions are in:
Constructors
RsaOaepParams | |
Fields |
newtype RsaOtherPrimesInfo Source #
Functions for this inteface are in JSDOM.RsaOtherPrimesInfo.
Constructors
RsaOtherPrimesInfo | |
Fields |
Functions for this inteface are in JSDOM.SQLError.
Constructors
SQLError | |
Fields
|
gTypeSQLError :: JSM GType Source #
newtype SQLException Source #
Functions for this inteface are in JSDOM.SQLException.
Constructors
SQLException | |
Fields |
newtype SQLResultSet Source #
Functions for this inteface are in JSDOM.SQLResultSet.
Constructors
SQLResultSet | |
Fields |
newtype SQLResultSetRowList Source #
Functions for this inteface are in JSDOM.SQLResultSetRowList.
Constructors
SQLResultSetRowList | |
Fields |
newtype SQLTransaction Source #
Functions for this inteface are in JSDOM.SQLTransaction.
Constructors
SQLTransaction | |
Fields |
newtype SVGAElement Source #
Functions for this inteface are in JSDOM.SVGAElement. Base interface functions are in:
- JSDOM.SVGGraphicsElement
- JSDOM.SVGElement
- JSDOM.Element
- JSDOM.Node
- JSDOM.EventTarget
- JSDOM.Slotable
- JSDOM.ParentNode
- JSDOM.NonDocumentTypeChildNode
- JSDOM.DocumentAndElementEventHandlers
- JSDOM.ChildNode
- JSDOM.Animatable
- JSDOM.GlobalEventHandlers
- JSDOM.ElementCSSInlineStyle
- JSDOM.SVGTests
- JSDOM.SVGURIReference
- JSDOM.SVGExternalResourcesRequired
Constructors
SVGAElement | |
Fields |
Instances
newtype SVGAltGlyphDefElement Source #
Functions for this inteface are in JSDOM.SVGAltGlyphDefElement. Base interface functions are in:
Constructors
SVGAltGlyphDefElement | |
Fields |
Instances
newtype SVGAltGlyphElement Source #
Functions for this inteface are in JSDOM.SVGAltGlyphElement. Base interface functions are in:
- JSDOM.SVGTextPositioningElement
- JSDOM.SVGTextContentElement
- JSDOM.SVGGraphicsElement
- JSDOM.SVGElement
- JSDOM.Element
- JSDOM.Node
- JSDOM.EventTarget
- JSDOM.Slotable
- JSDOM.ParentNode
- JSDOM.NonDocumentTypeChildNode
- JSDOM.DocumentAndElementEventHandlers
- JSDOM.ChildNode
- JSDOM.Animatable
- JSDOM.GlobalEventHandlers
- JSDOM.ElementCSSInlineStyle
- JSDOM.SVGTests
- JSDOM.SVGExternalResourcesRequired
- JSDOM.SVGURIReference
Constructors
SVGAltGlyphElement | |
Fields |
Instances
newtype SVGAltGlyphItemElement Source #
Functions for this inteface are in JSDOM.SVGAltGlyphItemElement. Base interface functions are in:
Constructors
SVGAltGlyphItemElement | |
Fields |
Instances
Functions for this inteface are in JSDOM.SVGAngle.
Constructors
SVGAngle | |
Fields
|
gTypeSVGAngle :: JSM GType Source #
newtype SVGAnimateColorElement Source #
Functions for this inteface are in JSDOM.SVGAnimateColorElement. Base interface functions are in:
- JSDOM.SVGAnimationElement
- JSDOM.SVGElement
- JSDOM.Element
- JSDOM.Node
- JSDOM.EventTarget
- JSDOM.Slotable
- JSDOM.ParentNode
- JSDOM.NonDocumentTypeChildNode
- JSDOM.DocumentAndElementEventHandlers
- JSDOM.ChildNode
- JSDOM.Animatable
- JSDOM.GlobalEventHandlers
- JSDOM.ElementCSSInlineStyle
- JSDOM.SVGTests
- JSDOM.SVGExternalResourcesRequired
Constructors
SVGAnimateColorElement | |
Fields |
Instances
newtype SVGAnimateElement Source #
Functions for this inteface are in JSDOM.SVGAnimateElement. Base interface functions are in:
- JSDOM.SVGAnimationElement
- JSDOM.SVGElement
- JSDOM.Element
- JSDOM.Node
- JSDOM.EventTarget
- JSDOM.Slotable
- JSDOM.ParentNode
- JSDOM.NonDocumentTypeChildNode
- JSDOM.DocumentAndElementEventHandlers
- JSDOM.ChildNode
- JSDOM.Animatable
- JSDOM.GlobalEventHandlers
- JSDOM.ElementCSSInlineStyle
- JSDOM.SVGTests
- JSDOM.SVGExternalResourcesRequired
Constructors
SVGAnimateElement | |
Fields |
Instances
newtype SVGAnimateMotionElement Source #
Functions for this inteface are in JSDOM.SVGAnimateMotionElement. Base interface functions are in:
- JSDOM.SVGAnimationElement
- JSDOM.SVGElement
- JSDOM.Element
- JSDOM.Node
- JSDOM.EventTarget
- JSDOM.Slotable
- JSDOM.ParentNode
- JSDOM.NonDocumentTypeChildNode
- JSDOM.DocumentAndElementEventHandlers
- JSDOM.ChildNode
- JSDOM.Animatable
- JSDOM.GlobalEventHandlers
- JSDOM.ElementCSSInlineStyle
- JSDOM.SVGTests
- JSDOM.SVGExternalResourcesRequired
Constructors
SVGAnimateMotionElement | |
Fields |
Instances
newtype SVGAnimateTransformElement Source #
Functions for this inteface are in JSDOM.SVGAnimateTransformElement. Base interface functions are in:
- JSDOM.SVGAnimationElement
- JSDOM.SVGElement
- JSDOM.Element
- JSDOM.Node
- JSDOM.EventTarget
- JSDOM.Slotable
- JSDOM.ParentNode
- JSDOM.NonDocumentTypeChildNode
- JSDOM.DocumentAndElementEventHandlers
- JSDOM.ChildNode
- JSDOM.Animatable
- JSDOM.GlobalEventHandlers
- JSDOM.ElementCSSInlineStyle
- JSDOM.SVGTests
- JSDOM.SVGExternalResourcesRequired
Constructors
SVGAnimateTransformElement | |
Fields |
Instances
newtype SVGAnimatedAngle Source #
Functions for this inteface are in JSDOM.SVGAnimatedAngle.
Constructors
SVGAnimatedAngle | |
Fields |
newtype SVGAnimatedBoolean Source #
Functions for this inteface are in JSDOM.SVGAnimatedBoolean.
Constructors
SVGAnimatedBoolean | |
Fields |
newtype SVGAnimatedEnumeration Source #
Functions for this inteface are in JSDOM.SVGAnimatedEnumeration.
Constructors
SVGAnimatedEnumeration | |
Fields |
newtype SVGAnimatedInteger Source #
Functions for this inteface are in JSDOM.SVGAnimatedInteger.
Constructors
SVGAnimatedInteger | |
Fields |
newtype SVGAnimatedLength Source #
Functions for this inteface are in JSDOM.SVGAnimatedLength.
Constructors
SVGAnimatedLength | |
Fields |
newtype SVGAnimatedLengthList Source #
Functions for this inteface are in JSDOM.SVGAnimatedLengthList.
Constructors
SVGAnimatedLengthList | |
Fields |
newtype SVGAnimatedNumber Source #
Functions for this inteface are in JSDOM.SVGAnimatedNumber.
Constructors
SVGAnimatedNumber | |
Fields |
newtype SVGAnimatedNumberList Source #
Functions for this inteface are in JSDOM.SVGAnimatedNumberList.
Constructors
SVGAnimatedNumberList | |
Fields |
newtype SVGAnimatedPreserveAspectRatio Source #
Functions for this inteface are in JSDOM.SVGAnimatedPreserveAspectRatio.
Constructors
SVGAnimatedPreserveAspectRatio | |
Fields |
Instances
newtype SVGAnimatedRect Source #
Functions for this inteface are in JSDOM.SVGAnimatedRect.
Constructors
SVGAnimatedRect | |
Fields |
newtype SVGAnimatedString Source #
Functions for this inteface are in JSDOM.SVGAnimatedString.
Constructors
SVGAnimatedString | |
Fields |
newtype SVGAnimatedTransformList Source #
Functions for this inteface are in JSDOM.SVGAnimatedTransformList.
Constructors
SVGAnimatedTransformList | |
Fields |
newtype SVGAnimationElement Source #
Functions for this inteface are in JSDOM.SVGAnimationElement. Base interface functions are in:
Constructors
SVGAnimationElement | |
Fields |
Instances
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 Source #
Instances
toSVGAnimationElement :: IsSVGAnimationElement o => o -> SVGAnimationElement Source #
newtype SVGCircleElement Source #
Functions for this inteface are in JSDOM.SVGCircleElement. Base interface functions are in:
- JSDOM.SVGGraphicsElement
- JSDOM.SVGElement
- JSDOM.Element
- JSDOM.Node
- JSDOM.EventTarget
- JSDOM.Slotable
- JSDOM.ParentNode
- JSDOM.NonDocumentTypeChildNode
- JSDOM.DocumentAndElementEventHandlers
- JSDOM.ChildNode
- JSDOM.Animatable
- JSDOM.GlobalEventHandlers
- JSDOM.ElementCSSInlineStyle
- JSDOM.SVGTests
- JSDOM.SVGExternalResourcesRequired
Constructors
SVGCircleElement | |
Fields |
Instances
newtype SVGClipPathElement Source #
Functions for this inteface are in JSDOM.SVGClipPathElement. Base interface functions are in:
- JSDOM.SVGGraphicsElement
- JSDOM.SVGElement
- JSDOM.Element
- JSDOM.Node
- JSDOM.EventTarget
- JSDOM.Slotable
- JSDOM.ParentNode
- JSDOM.NonDocumentTypeChildNode
- JSDOM.DocumentAndElementEventHandlers
- JSDOM.ChildNode
- JSDOM.Animatable
- JSDOM.GlobalEventHandlers
- JSDOM.ElementCSSInlineStyle
- JSDOM.SVGTests
- JSDOM.SVGExternalResourcesRequired
Constructors
SVGClipPathElement | |
Fields |
Instances
newtype SVGComponentTransferFunctionElement Source #
Functions for this inteface are in JSDOM.SVGComponentTransferFunctionElement. Base interface functions are in:
Constructors
SVGComponentTransferFunctionElement | |
Instances
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 Source #
Instances
toSVGComponentTransferFunctionElement :: IsSVGComponentTransferFunctionElement o => o -> SVGComponentTransferFunctionElement Source #
newtype SVGCursorElement Source #
Functions for this inteface are in JSDOM.SVGCursorElement. Base interface functions are in:
- JSDOM.SVGElement
- JSDOM.Element
- JSDOM.Node
- JSDOM.EventTarget
- JSDOM.Slotable
- JSDOM.ParentNode
- JSDOM.NonDocumentTypeChildNode
- JSDOM.DocumentAndElementEventHandlers
- JSDOM.ChildNode
- JSDOM.Animatable
- JSDOM.GlobalEventHandlers
- JSDOM.ElementCSSInlineStyle
- JSDOM.SVGURIReference
- JSDOM.SVGTests
- JSDOM.SVGExternalResourcesRequired
Constructors
SVGCursorElement | |
Fields |
Instances
newtype SVGDefsElement Source #
Functions for this inteface are in JSDOM.SVGDefsElement. Base interface functions are in:
- JSDOM.SVGGraphicsElement
- JSDOM.SVGElement
- JSDOM.Element
- JSDOM.Node
- JSDOM.EventTarget
- JSDOM.Slotable
- JSDOM.ParentNode
- JSDOM.NonDocumentTypeChildNode
- JSDOM.DocumentAndElementEventHandlers
- JSDOM.ChildNode
- JSDOM.Animatable
- JSDOM.GlobalEventHandlers
- JSDOM.ElementCSSInlineStyle
- JSDOM.SVGTests
- JSDOM.SVGExternalResourcesRequired
Constructors
SVGDefsElement | |
Fields |
Instances
newtype SVGDescElement Source #
Functions for this inteface are in JSDOM.SVGDescElement. Base interface functions are in:
Constructors
SVGDescElement | |
Fields |
Instances
newtype SVGElement Source #
Functions for this inteface are in JSDOM.SVGElement. Base interface functions are in:
Constructors
SVGElement | |
Fields |
Instances
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 Source #
Instances
toSVGElement :: IsSVGElement o => o -> SVGElement Source #
newtype SVGEllipseElement Source #
Functions for this inteface are in JSDOM.SVGEllipseElement. Base interface functions are in:
- JSDOM.SVGGraphicsElement
- JSDOM.SVGElement
- JSDOM.Element
- JSDOM.Node
- JSDOM.EventTarget
- JSDOM.Slotable
- JSDOM.ParentNode
- JSDOM.NonDocumentTypeChildNode
- JSDOM.DocumentAndElementEventHandlers
- JSDOM.ChildNode
- JSDOM.Animatable
- JSDOM.GlobalEventHandlers
- JSDOM.ElementCSSInlineStyle
- JSDOM.SVGTests
- JSDOM.SVGExternalResourcesRequired
Constructors
SVGEllipseElement | |
Fields |
Instances
newtype SVGException Source #
Functions for this inteface are in JSDOM.SVGException.
Constructors
SVGException | |
Fields |
newtype SVGExternalResourcesRequired Source #
Functions for this inteface are in JSDOM.SVGExternalResourcesRequired.
Constructors
SVGExternalResourcesRequired | |
Fields |
Instances
class IsGObject o => IsSVGExternalResourcesRequired o Source #
Instances
toSVGExternalResourcesRequired :: IsSVGExternalResourcesRequired o => o -> SVGExternalResourcesRequired Source #
newtype SVGFEBlendElement Source #
Functions for this inteface are in JSDOM.SVGFEBlendElement. Base interface functions are in:
Constructors
SVGFEBlendElement | |
Fields |
Instances
newtype SVGFEColorMatrixElement Source #
Functions for this inteface are in JSDOM.SVGFEColorMatrixElement. Base interface functions are in:
Constructors
SVGFEColorMatrixElement | |
Fields |
Instances
newtype SVGFEComponentTransferElement Source #
Functions for this inteface are in JSDOM.SVGFEComponentTransferElement. Base interface functions are in:
Constructors
SVGFEComponentTransferElement | |
Fields |
Instances
newtype SVGFECompositeElement Source #
Functions for this inteface are in JSDOM.SVGFECompositeElement. Base interface functions are in:
Constructors
SVGFECompositeElement | |
Fields |
Instances
newtype SVGFEConvolveMatrixElement Source #
Functions for this inteface are in JSDOM.SVGFEConvolveMatrixElement. Base interface functions are in:
Constructors
SVGFEConvolveMatrixElement | |
Fields |
Instances
newtype SVGFEDiffuseLightingElement Source #
Functions for this inteface are in JSDOM.SVGFEDiffuseLightingElement. Base interface functions are in:
Constructors
SVGFEDiffuseLightingElement | |
Fields |
Instances
newtype SVGFEDisplacementMapElement Source #
Functions for this inteface are in JSDOM.SVGFEDisplacementMapElement. Base interface functions are in:
Constructors
SVGFEDisplacementMapElement | |
Fields |
Instances
newtype SVGFEDistantLightElement Source #
Functions for this inteface are in JSDOM.SVGFEDistantLightElement. Base interface functions are in:
Constructors
SVGFEDistantLightElement | |
Fields |
Instances
newtype SVGFEDropShadowElement Source #
Functions for this inteface are in JSDOM.SVGFEDropShadowElement. Base interface functions are in:
Constructors
SVGFEDropShadowElement | |
Fields |
Instances
newtype SVGFEFloodElement Source #
Functions for this inteface are in JSDOM.SVGFEFloodElement. Base interface functions are in:
Constructors
SVGFEFloodElement | |
Fields |
Instances
newtype SVGFEFuncAElement Source #
Functions for this inteface are in JSDOM.SVGFEFuncAElement. Base interface functions are in:
Constructors
SVGFEFuncAElement | |
Fields |
Instances
newtype SVGFEFuncBElement Source #
Functions for this inteface are in JSDOM.SVGFEFuncBElement. Base interface functions are in:
Constructors
SVGFEFuncBElement | |
Fields |
Instances
newtype SVGFEFuncGElement Source #
Functions for this inteface are in JSDOM.SVGFEFuncGElement. Base interface functions are in:
Constructors
SVGFEFuncGElement | |
Fields |
Instances
newtype SVGFEFuncRElement Source #
Functions for this inteface are in JSDOM.SVGFEFuncRElement. Base interface functions are in:
Constructors
SVGFEFuncRElement | |
Fields |
Instances
newtype SVGFEGaussianBlurElement Source #
Functions for this inteface are in JSDOM.SVGFEGaussianBlurElement. Base interface functions are in:
Constructors
SVGFEGaussianBlurElement | |
Fields |
Instances
newtype SVGFEImageElement Source #
Functions for this inteface are in JSDOM.SVGFEImageElement. Base interface functions are in:
- JSDOM.SVGElement
- JSDOM.Element
- JSDOM.Node
- JSDOM.EventTarget
- JSDOM.Slotable
- JSDOM.ParentNode
- JSDOM.NonDocumentTypeChildNode
- JSDOM.DocumentAndElementEventHandlers
- JSDOM.ChildNode
- JSDOM.Animatable
- JSDOM.GlobalEventHandlers
- JSDOM.ElementCSSInlineStyle
- JSDOM.SVGURIReference
- JSDOM.SVGFilterPrimitiveStandardAttributes
- JSDOM.SVGExternalResourcesRequired
Constructors
SVGFEImageElement | |
Fields |
Instances
newtype SVGFEMergeElement Source #
Functions for this inteface are in JSDOM.SVGFEMergeElement. Base interface functions are in:
Constructors
SVGFEMergeElement | |
Fields |
Instances
newtype SVGFEMergeNodeElement Source #
Functions for this inteface are in JSDOM.SVGFEMergeNodeElement. Base interface functions are in:
Constructors
SVGFEMergeNodeElement | |
Fields |
Instances
newtype SVGFEMorphologyElement Source #
Functions for this inteface are in JSDOM.SVGFEMorphologyElement. Base interface functions are in:
Constructors
SVGFEMorphologyElement | |
Fields |
Instances
newtype SVGFEOffsetElement Source #
Functions for this inteface are in JSDOM.SVGFEOffsetElement. Base interface functions are in:
Constructors
SVGFEOffsetElement | |
Fields |
Instances
newtype SVGFEPointLightElement Source #
Functions for this inteface are in JSDOM.SVGFEPointLightElement. Base interface functions are in:
Constructors
SVGFEPointLightElement | |
Fields |
Instances
newtype SVGFESpecularLightingElement Source #
Functions for this inteface are in JSDOM.SVGFESpecularLightingElement. Base interface functions are in:
Constructors
SVGFESpecularLightingElement | |
Fields |
Instances
newtype SVGFESpotLightElement Source #
Functions for this inteface are in JSDOM.SVGFESpotLightElement. Base interface functions are in:
Constructors
SVGFESpotLightElement | |
Fields |
Instances
newtype SVGFETileElement Source #
Functions for this inteface are in JSDOM.SVGFETileElement. Base interface functions are in:
Constructors
SVGFETileElement | |
Fields |
Instances
newtype SVGFETurbulenceElement Source #
Functions for this inteface are in JSDOM.SVGFETurbulenceElement. Base interface functions are in:
Constructors
SVGFETurbulenceElement | |
Fields |
Instances
newtype SVGFilterElement Source #
Functions for this inteface are in JSDOM.SVGFilterElement. Base interface functions are in:
Constructors
SVGFilterElement | |
Fields |
Instances
newtype SVGFilterPrimitiveStandardAttributes Source #
Functions for this inteface are in JSDOM.SVGFilterPrimitiveStandardAttributes.
Constructors
SVGFilterPrimitiveStandardAttributes | |
Instances
class IsGObject o => IsSVGFilterPrimitiveStandardAttributes o Source #
Instances
toSVGFilterPrimitiveStandardAttributes :: IsSVGFilterPrimitiveStandardAttributes o => o -> SVGFilterPrimitiveStandardAttributes Source #
newtype SVGFitToViewBox Source #
Functions for this inteface are in JSDOM.SVGFitToViewBox.
Constructors
SVGFitToViewBox | |
Fields |
class IsGObject o => IsSVGFitToViewBox o Source #
Instances
toSVGFitToViewBox :: IsSVGFitToViewBox o => o -> SVGFitToViewBox Source #
newtype SVGFontElement Source #
Functions for this inteface are in JSDOM.SVGFontElement. Base interface functions are in:
Constructors
SVGFontElement | |
Fields |
Instances
newtype SVGFontFaceElement Source #
Functions for this inteface are in JSDOM.SVGFontFaceElement. Base interface functions are in:
Constructors
SVGFontFaceElement | |
Fields |
Instances
newtype SVGFontFaceFormatElement Source #
Functions for this inteface are in JSDOM.SVGFontFaceFormatElement. Base interface functions are in:
Constructors
SVGFontFaceFormatElement | |
Fields |
Instances
newtype SVGFontFaceNameElement Source #
Functions for this inteface are in JSDOM.SVGFontFaceNameElement. Base interface functions are in:
Constructors
SVGFontFaceNameElement | |
Fields |
Instances
newtype SVGFontFaceSrcElement Source #
Functions for this inteface are in JSDOM.SVGFontFaceSrcElement. Base interface functions are in:
Constructors
SVGFontFaceSrcElement | |
Fields |
Instances
newtype SVGFontFaceUriElement Source #
Functions for this inteface are in JSDOM.SVGFontFaceUriElement. Base interface functions are in:
Constructors
SVGFontFaceUriElement | |
Fields |
Instances
newtype SVGForeignObjectElement Source #
Functions for this inteface are in JSDOM.SVGForeignObjectElement. Base interface functions are in:
- JSDOM.SVGGraphicsElement
- JSDOM.SVGElement
- JSDOM.Element
- JSDOM.Node
- JSDOM.EventTarget
- JSDOM.Slotable
- JSDOM.ParentNode
- JSDOM.NonDocumentTypeChildNode
- JSDOM.DocumentAndElementEventHandlers
- JSDOM.ChildNode
- JSDOM.Animatable
- JSDOM.GlobalEventHandlers
- JSDOM.ElementCSSInlineStyle
- JSDOM.SVGTests
- JSDOM.SVGExternalResourcesRequired
Constructors
SVGForeignObjectElement | |
Fields |
Instances
newtype SVGGElement Source #
Functions for this inteface are in JSDOM.SVGGElement. Base interface functions are in:
- JSDOM.SVGGraphicsElement
- JSDOM.SVGElement
- JSDOM.Element
- JSDOM.Node
- JSDOM.EventTarget
- JSDOM.Slotable
- JSDOM.ParentNode
- JSDOM.NonDocumentTypeChildNode
- JSDOM.DocumentAndElementEventHandlers
- JSDOM.ChildNode
- JSDOM.Animatable
- JSDOM.GlobalEventHandlers
- JSDOM.ElementCSSInlineStyle
- JSDOM.SVGTests
- JSDOM.SVGExternalResourcesRequired
Constructors
SVGGElement | |
Fields |
Instances
newtype SVGGlyphElement Source #
Functions for this inteface are in JSDOM.SVGGlyphElement. Base interface functions are in:
Constructors
SVGGlyphElement | |
Fields |
Instances
newtype SVGGlyphRefElement Source #
Functions for this inteface are in JSDOM.SVGGlyphRefElement. Base interface functions are in:
Constructors
SVGGlyphRefElement | |
Fields |
Instances
newtype SVGGradientElement Source #
Functions for this inteface are in JSDOM.SVGGradientElement. Base interface functions are in:
Constructors
SVGGradientElement | |
Fields |
Instances
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 Source #
toSVGGradientElement :: IsSVGGradientElement o => o -> SVGGradientElement Source #
newtype SVGGraphicsElement Source #
Functions for this inteface are in JSDOM.SVGGraphicsElement. Base interface functions are in:
Constructors
SVGGraphicsElement | |
Fields |
Instances
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 Source #
Instances
toSVGGraphicsElement :: IsSVGGraphicsElement o => o -> SVGGraphicsElement Source #
newtype SVGHKernElement Source #
Functions for this inteface are in JSDOM.SVGHKernElement. Base interface functions are in:
Constructors
SVGHKernElement | |
Fields |
Instances
newtype SVGImageElement Source #
Functions for this inteface are in JSDOM.SVGImageElement. Base interface functions are in:
- JSDOM.SVGGraphicsElement
- JSDOM.SVGElement
- JSDOM.Element
- JSDOM.Node
- JSDOM.EventTarget
- JSDOM.Slotable
- JSDOM.ParentNode
- JSDOM.NonDocumentTypeChildNode
- JSDOM.DocumentAndElementEventHandlers
- JSDOM.ChildNode
- JSDOM.Animatable
- JSDOM.GlobalEventHandlers
- JSDOM.ElementCSSInlineStyle
- JSDOM.SVGTests
- JSDOM.SVGURIReference
- JSDOM.SVGExternalResourcesRequired
Constructors
SVGImageElement | |
Fields |
Instances
Functions for this inteface are in JSDOM.SVGLength.
Constructors
SVGLength | |
Fields
|
newtype SVGLengthList Source #
Functions for this inteface are in JSDOM.SVGLengthList.
Constructors
SVGLengthList | |
Fields |
newtype SVGLineElement Source #
Functions for this inteface are in JSDOM.SVGLineElement. Base interface functions are in:
- JSDOM.SVGGraphicsElement
- JSDOM.SVGElement
- JSDOM.Element
- JSDOM.Node
- JSDOM.EventTarget
- JSDOM.Slotable
- JSDOM.ParentNode
- JSDOM.NonDocumentTypeChildNode
- JSDOM.DocumentAndElementEventHandlers
- JSDOM.ChildNode
- JSDOM.Animatable
- JSDOM.GlobalEventHandlers
- JSDOM.ElementCSSInlineStyle
- JSDOM.SVGTests
- JSDOM.SVGExternalResourcesRequired
Constructors
SVGLineElement | |
Fields |
Instances
newtype SVGLinearGradientElement Source #
Functions for this inteface are in JSDOM.SVGLinearGradientElement. Base interface functions are in:
- JSDOM.SVGGradientElement
- JSDOM.SVGElement
- JSDOM.Element
- JSDOM.Node
- JSDOM.EventTarget
- JSDOM.Slotable
- JSDOM.ParentNode
- JSDOM.NonDocumentTypeChildNode
- JSDOM.DocumentAndElementEventHandlers
- JSDOM.ChildNode
- JSDOM.Animatable
- JSDOM.GlobalEventHandlers
- JSDOM.ElementCSSInlineStyle
- JSDOM.SVGURIReference
- JSDOM.SVGExternalResourcesRequired
Constructors
SVGLinearGradientElement | |
Fields |
Instances
newtype SVGMPathElement Source #
Functions for this inteface are in JSDOM.SVGMPathElement. Base interface functions are in:
Constructors
SVGMPathElement | |
Fields |
Instances
newtype SVGMarkerElement Source #
Functions for this inteface are in JSDOM.SVGMarkerElement. Base interface functions are in:
Constructors
SVGMarkerElement | |
Fields |
Instances
newtype SVGMaskElement Source #
Functions for this inteface are in JSDOM.SVGMaskElement. Base interface functions are in:
Constructors
SVGMaskElement | |
Fields |
Instances
Functions for this inteface are in JSDOM.SVGMatrix.
Constructors
SVGMatrix | |
Fields
|
newtype SVGMetadataElement Source #
Functions for this inteface are in JSDOM.SVGMetadataElement. Base interface functions are in:
Constructors
SVGMetadataElement | |
Fields |
Instances
newtype SVGMissingGlyphElement Source #
Functions for this inteface are in JSDOM.SVGMissingGlyphElement. Base interface functions are in:
Constructors
SVGMissingGlyphElement | |
Fields |
Instances
Functions for this inteface are in JSDOM.SVGNumber.
Constructors
SVGNumber | |
Fields
|
newtype SVGNumberList Source #
Functions for this inteface are in JSDOM.SVGNumberList.
Constructors
SVGNumberList | |
Fields |
newtype SVGPathElement Source #
Functions for this inteface are in JSDOM.SVGPathElement. Base interface functions are in:
- JSDOM.SVGGraphicsElement
- JSDOM.SVGElement
- JSDOM.Element
- JSDOM.Node
- JSDOM.EventTarget
- JSDOM.Slotable
- JSDOM.ParentNode
- JSDOM.NonDocumentTypeChildNode
- JSDOM.DocumentAndElementEventHandlers
- JSDOM.ChildNode
- JSDOM.Animatable
- JSDOM.GlobalEventHandlers
- JSDOM.ElementCSSInlineStyle
- JSDOM.SVGTests
- JSDOM.SVGExternalResourcesRequired
Constructors
SVGPathElement | |
Fields |
Instances
newtype SVGPathSeg Source #
Functions for this inteface are in JSDOM.SVGPathSeg.
Constructors
SVGPathSeg | |
Fields |
class IsGObject o => IsSVGPathSeg o Source #
Instances
toSVGPathSeg :: IsSVGPathSeg o => o -> SVGPathSeg Source #
newtype SVGPathSegArcAbs Source #
Functions for this inteface are in JSDOM.SVGPathSegArcAbs. Base interface functions are in:
Constructors
SVGPathSegArcAbs | |
Fields |
newtype SVGPathSegArcRel Source #
Functions for this inteface are in JSDOM.SVGPathSegArcRel. Base interface functions are in:
Constructors
SVGPathSegArcRel | |
Fields |
newtype SVGPathSegClosePath Source #
Functions for this inteface are in JSDOM.SVGPathSegClosePath. Base interface functions are in:
Constructors
SVGPathSegClosePath | |
Fields |
newtype SVGPathSegCurvetoCubicAbs Source #
Functions for this inteface are in JSDOM.SVGPathSegCurvetoCubicAbs. Base interface functions are in:
Constructors
SVGPathSegCurvetoCubicAbs | |
Fields |
Instances
newtype SVGPathSegCurvetoCubicRel Source #
Functions for this inteface are in JSDOM.SVGPathSegCurvetoCubicRel. Base interface functions are in:
Constructors
SVGPathSegCurvetoCubicRel | |
Fields |
Instances
newtype SVGPathSegCurvetoCubicSmoothAbs Source #
Functions for this inteface are in JSDOM.SVGPathSegCurvetoCubicSmoothAbs. Base interface functions are in:
Constructors
SVGPathSegCurvetoCubicSmoothAbs | |
Fields |
Instances
newtype SVGPathSegCurvetoCubicSmoothRel Source #
Functions for this inteface are in JSDOM.SVGPathSegCurvetoCubicSmoothRel. Base interface functions are in:
Constructors
SVGPathSegCurvetoCubicSmoothRel | |
Fields |
Instances
newtype SVGPathSegCurvetoQuadraticAbs Source #
Functions for this inteface are in JSDOM.SVGPathSegCurvetoQuadraticAbs. Base interface functions are in:
Constructors
SVGPathSegCurvetoQuadraticAbs | |
Fields |
Instances
newtype SVGPathSegCurvetoQuadraticRel Source #
Functions for this inteface are in JSDOM.SVGPathSegCurvetoQuadraticRel. Base interface functions are in:
Constructors
SVGPathSegCurvetoQuadraticRel | |
Fields |
Instances
newtype SVGPathSegCurvetoQuadraticSmoothAbs Source #
Functions for this inteface are in JSDOM.SVGPathSegCurvetoQuadraticSmoothAbs. Base interface functions are in:
Constructors
SVGPathSegCurvetoQuadraticSmoothAbs | |
Instances
newtype SVGPathSegCurvetoQuadraticSmoothRel Source #
Functions for this inteface are in JSDOM.SVGPathSegCurvetoQuadraticSmoothRel. Base interface functions are in:
Constructors
SVGPathSegCurvetoQuadraticSmoothRel | |
Instances
newtype SVGPathSegLinetoAbs Source #
Functions for this inteface are in JSDOM.SVGPathSegLinetoAbs. Base interface functions are in:
Constructors
SVGPathSegLinetoAbs | |
Fields |
newtype SVGPathSegLinetoHorizontalAbs Source #
Functions for this inteface are in JSDOM.SVGPathSegLinetoHorizontalAbs. Base interface functions are in:
Constructors
SVGPathSegLinetoHorizontalAbs | |
Fields |
Instances
newtype SVGPathSegLinetoHorizontalRel Source #
Functions for this inteface are in JSDOM.SVGPathSegLinetoHorizontalRel. Base interface functions are in:
Constructors
SVGPathSegLinetoHorizontalRel | |
Fields |
Instances
newtype SVGPathSegLinetoRel Source #
Functions for this inteface are in JSDOM.SVGPathSegLinetoRel. Base interface functions are in:
Constructors
SVGPathSegLinetoRel | |
Fields |
newtype SVGPathSegLinetoVerticalAbs Source #
Functions for this inteface are in JSDOM.SVGPathSegLinetoVerticalAbs. Base interface functions are in:
Constructors
SVGPathSegLinetoVerticalAbs | |
Fields |
Instances
newtype SVGPathSegLinetoVerticalRel Source #
Functions for this inteface are in JSDOM.SVGPathSegLinetoVerticalRel. Base interface functions are in:
Constructors
SVGPathSegLinetoVerticalRel | |
Fields |
Instances
newtype SVGPathSegList Source #
Functions for this inteface are in JSDOM.SVGPathSegList.
Constructors
SVGPathSegList | |
Fields |
newtype SVGPathSegMovetoAbs Source #
Functions for this inteface are in JSDOM.SVGPathSegMovetoAbs. Base interface functions are in:
Constructors
SVGPathSegMovetoAbs | |
Fields |
newtype SVGPathSegMovetoRel Source #
Functions for this inteface are in JSDOM.SVGPathSegMovetoRel. Base interface functions are in:
Constructors
SVGPathSegMovetoRel | |
Fields |
newtype SVGPatternElement Source #
Functions for this inteface are in JSDOM.SVGPatternElement. Base interface functions are in:
- JSDOM.SVGElement
- JSDOM.Element
- JSDOM.Node
- JSDOM.EventTarget
- JSDOM.Slotable
- JSDOM.ParentNode
- JSDOM.NonDocumentTypeChildNode
- JSDOM.DocumentAndElementEventHandlers
- JSDOM.ChildNode
- JSDOM.Animatable
- JSDOM.GlobalEventHandlers
- JSDOM.ElementCSSInlineStyle
- JSDOM.SVGURIReference
- JSDOM.SVGTests
- JSDOM.SVGFitToViewBox
- JSDOM.SVGExternalResourcesRequired
Constructors
SVGPatternElement | |
Fields |
Instances
Functions for this inteface are in JSDOM.SVGPoint.
Constructors
SVGPoint | |
Fields
|
gTypeSVGPoint :: JSM GType Source #
newtype SVGPointList Source #
Functions for this inteface are in JSDOM.SVGPointList.
Constructors
SVGPointList | |
Fields |
newtype SVGPolygonElement Source #
Functions for this inteface are in JSDOM.SVGPolygonElement. Base interface functions are in:
- JSDOM.SVGGraphicsElement
- JSDOM.SVGElement
- JSDOM.Element
- JSDOM.Node
- JSDOM.EventTarget
- JSDOM.Slotable
- JSDOM.ParentNode
- JSDOM.NonDocumentTypeChildNode
- JSDOM.DocumentAndElementEventHandlers
- JSDOM.ChildNode
- JSDOM.Animatable
- JSDOM.GlobalEventHandlers
- JSDOM.ElementCSSInlineStyle
- JSDOM.SVGTests
- JSDOM.SVGExternalResourcesRequired
Constructors
SVGPolygonElement | |
Fields |
Instances
newtype SVGPolylineElement Source #
Functions for this inteface are in JSDOM.SVGPolylineElement. Base interface functions are in:
- JSDOM.SVGGraphicsElement
- JSDOM.SVGElement
- JSDOM.Element
- JSDOM.Node
- JSDOM.EventTarget
- JSDOM.Slotable
- JSDOM.ParentNode
- JSDOM.NonDocumentTypeChildNode
- JSDOM.DocumentAndElementEventHandlers
- JSDOM.ChildNode
- JSDOM.Animatable
- JSDOM.GlobalEventHandlers
- JSDOM.ElementCSSInlineStyle
- JSDOM.SVGTests
- JSDOM.SVGExternalResourcesRequired
Constructors
SVGPolylineElement | |
Fields |
Instances
newtype SVGPreserveAspectRatio Source #
Functions for this inteface are in JSDOM.SVGPreserveAspectRatio.
Constructors
SVGPreserveAspectRatio | |
Fields |
newtype SVGRadialGradientElement Source #
Functions for this inteface are in JSDOM.SVGRadialGradientElement. Base interface functions are in:
- JSDOM.SVGGradientElement
- JSDOM.SVGElement
- JSDOM.Element
- JSDOM.Node
- JSDOM.EventTarget
- JSDOM.Slotable
- JSDOM.ParentNode
- JSDOM.NonDocumentTypeChildNode
- JSDOM.DocumentAndElementEventHandlers
- JSDOM.ChildNode
- JSDOM.Animatable
- JSDOM.GlobalEventHandlers
- JSDOM.ElementCSSInlineStyle
- JSDOM.SVGURIReference
- JSDOM.SVGExternalResourcesRequired
Constructors
SVGRadialGradientElement | |
Fields |
Instances
Functions for this inteface are in JSDOM.SVGRect.
gTypeSVGRect :: JSM GType Source #
newtype SVGRectElement Source #
Functions for this inteface are in JSDOM.SVGRectElement. Base interface functions are in:
- JSDOM.SVGGraphicsElement
- JSDOM.SVGElement
- JSDOM.Element
- JSDOM.Node
- JSDOM.EventTarget
- JSDOM.Slotable
- JSDOM.ParentNode
- JSDOM.NonDocumentTypeChildNode
- JSDOM.DocumentAndElementEventHandlers
- JSDOM.ChildNode
- JSDOM.Animatable
- JSDOM.GlobalEventHandlers
- JSDOM.ElementCSSInlineStyle
- JSDOM.SVGTests
- JSDOM.SVGExternalResourcesRequired
Constructors
SVGRectElement | |
Fields |
Instances
newtype SVGRenderingIntent Source #
Functions for this inteface are in JSDOM.SVGRenderingIntent.
Constructors
SVGRenderingIntent | |
Fields |
newtype SVGSVGElement Source #
Functions for this inteface are in JSDOM.SVGSVGElement. Base interface functions are in:
- JSDOM.SVGGraphicsElement
- JSDOM.SVGElement
- JSDOM.Element
- JSDOM.Node
- JSDOM.EventTarget
- JSDOM.Slotable
- JSDOM.ParentNode
- JSDOM.NonDocumentTypeChildNode
- JSDOM.DocumentAndElementEventHandlers
- JSDOM.ChildNode
- JSDOM.Animatable
- JSDOM.GlobalEventHandlers
- JSDOM.ElementCSSInlineStyle
- JSDOM.SVGTests
- JSDOM.SVGZoomAndPan
- JSDOM.SVGFitToViewBox
- JSDOM.SVGExternalResourcesRequired
Constructors
SVGSVGElement | |
Fields |
Instances
newtype SVGScriptElement Source #
Functions for this inteface are in JSDOM.SVGScriptElement. Base interface functions are in:
Constructors
SVGScriptElement | |
Fields |
Instances
newtype SVGSetElement Source #
Functions for this inteface are in JSDOM.SVGSetElement. Base interface functions are in:
- JSDOM.SVGAnimationElement
- JSDOM.SVGElement
- JSDOM.Element
- JSDOM.Node
- JSDOM.EventTarget
- JSDOM.Slotable
- JSDOM.ParentNode
- JSDOM.NonDocumentTypeChildNode
- JSDOM.DocumentAndElementEventHandlers
- JSDOM.ChildNode
- JSDOM.Animatable
- JSDOM.GlobalEventHandlers
- JSDOM.ElementCSSInlineStyle
- JSDOM.SVGTests
- JSDOM.SVGExternalResourcesRequired
Constructors
SVGSetElement | |
Fields |
Instances
newtype SVGStopElement Source #
Functions for this inteface are in JSDOM.SVGStopElement. Base interface functions are in:
Constructors
SVGStopElement | |
Fields |
Instances
newtype SVGStringList Source #
Functions for this inteface are in JSDOM.SVGStringList.
Constructors
SVGStringList | |
Fields |
newtype SVGStyleElement Source #
Functions for this inteface are in JSDOM.SVGStyleElement. Base interface functions are in:
Constructors
SVGStyleElement | |
Fields |
Instances
newtype SVGSwitchElement Source #
Functions for this inteface are in JSDOM.SVGSwitchElement. Base interface functions are in:
- JSDOM.SVGGraphicsElement
- JSDOM.SVGElement
- JSDOM.Element
- JSDOM.Node
- JSDOM.EventTarget
- JSDOM.Slotable
- JSDOM.ParentNode
- JSDOM.NonDocumentTypeChildNode
- JSDOM.DocumentAndElementEventHandlers
- JSDOM.ChildNode
- JSDOM.Animatable
- JSDOM.GlobalEventHandlers
- JSDOM.ElementCSSInlineStyle
- JSDOM.SVGTests
- JSDOM.SVGExternalResourcesRequired
Constructors
SVGSwitchElement | |
Fields |
Instances
newtype SVGSymbolElement Source #
Functions for this inteface are in JSDOM.SVGSymbolElement. Base interface functions are in:
Constructors
SVGSymbolElement | |
Fields |
Instances
newtype SVGTRefElement Source #
Functions for this inteface are in JSDOM.SVGTRefElement. Base interface functions are in:
- JSDOM.SVGTextPositioningElement
- JSDOM.SVGTextContentElement
- JSDOM.SVGGraphicsElement
- JSDOM.SVGElement
- JSDOM.Element
- JSDOM.Node
- JSDOM.EventTarget
- JSDOM.Slotable
- JSDOM.ParentNode
- JSDOM.NonDocumentTypeChildNode
- JSDOM.DocumentAndElementEventHandlers
- JSDOM.ChildNode
- JSDOM.Animatable
- JSDOM.GlobalEventHandlers
- JSDOM.ElementCSSInlineStyle
- JSDOM.SVGTests
- JSDOM.SVGExternalResourcesRequired
- JSDOM.SVGURIReference
Constructors
SVGTRefElement | |
Fields |
Instances
newtype SVGTSpanElement Source #
Functions for this inteface are in JSDOM.SVGTSpanElement. Base interface functions are in:
- JSDOM.SVGTextPositioningElement
- JSDOM.SVGTextContentElement
- JSDOM.SVGGraphicsElement
- JSDOM.SVGElement
- JSDOM.Element
- JSDOM.Node
- JSDOM.EventTarget
- JSDOM.Slotable
- JSDOM.ParentNode
- JSDOM.NonDocumentTypeChildNode
- JSDOM.DocumentAndElementEventHandlers
- JSDOM.ChildNode
- JSDOM.Animatable
- JSDOM.GlobalEventHandlers
- JSDOM.ElementCSSInlineStyle
- JSDOM.SVGTests
- JSDOM.SVGExternalResourcesRequired
Constructors
SVGTSpanElement | |
Fields |
Instances
Functions for this inteface are in JSDOM.SVGTests.
Constructors
SVGTests | |
Fields
|
class IsGObject o => IsSVGTests o Source #
Instances
toSVGTests :: IsSVGTests o => o -> SVGTests Source #
gTypeSVGTests :: JSM GType Source #
newtype SVGTextContentElement Source #
Functions for this inteface are in JSDOM.SVGTextContentElement. Base interface functions are in:
- JSDOM.SVGGraphicsElement
- JSDOM.SVGElement
- JSDOM.Element
- JSDOM.Node
- JSDOM.EventTarget
- JSDOM.Slotable
- JSDOM.ParentNode
- JSDOM.NonDocumentTypeChildNode
- JSDOM.DocumentAndElementEventHandlers
- JSDOM.ChildNode
- JSDOM.Animatable
- JSDOM.GlobalEventHandlers
- JSDOM.ElementCSSInlineStyle
- JSDOM.SVGTests
- JSDOM.SVGExternalResourcesRequired
Constructors
SVGTextContentElement | |
Fields |
Instances
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 Source #
Instances
newtype SVGTextElement Source #
Functions for this inteface are in JSDOM.SVGTextElement. Base interface functions are in:
- JSDOM.SVGTextPositioningElement
- JSDOM.SVGTextContentElement
- JSDOM.SVGGraphicsElement
- JSDOM.SVGElement
- JSDOM.Element
- JSDOM.Node
- JSDOM.EventTarget
- JSDOM.Slotable
- JSDOM.ParentNode
- JSDOM.NonDocumentTypeChildNode
- JSDOM.DocumentAndElementEventHandlers
- JSDOM.ChildNode
- JSDOM.Animatable
- JSDOM.GlobalEventHandlers
- JSDOM.ElementCSSInlineStyle
- JSDOM.SVGTests
- JSDOM.SVGExternalResourcesRequired
Constructors
SVGTextElement | |
Fields |
Instances
newtype SVGTextPathElement Source #
Functions for this inteface are in JSDOM.SVGTextPathElement. Base interface functions are in:
- JSDOM.SVGTextContentElement
- JSDOM.SVGGraphicsElement
- JSDOM.SVGElement
- JSDOM.Element
- JSDOM.Node
- JSDOM.EventTarget
- JSDOM.Slotable
- JSDOM.ParentNode
- JSDOM.NonDocumentTypeChildNode
- JSDOM.DocumentAndElementEventHandlers
- JSDOM.ChildNode
- JSDOM.Animatable
- JSDOM.GlobalEventHandlers
- JSDOM.ElementCSSInlineStyle
- JSDOM.SVGTests
- JSDOM.SVGExternalResourcesRequired
- JSDOM.SVGURIReference
Constructors
SVGTextPathElement | |
Fields |
Instances
newtype SVGTextPositioningElement Source #
Functions for this inteface are in JSDOM.SVGTextPositioningElement. Base interface functions are in:
- JSDOM.SVGTextContentElement
- JSDOM.SVGGraphicsElement
- JSDOM.SVGElement
- JSDOM.Element
- JSDOM.Node
- JSDOM.EventTarget
- JSDOM.Slotable
- JSDOM.ParentNode
- JSDOM.NonDocumentTypeChildNode
- JSDOM.DocumentAndElementEventHandlers
- JSDOM.ChildNode
- JSDOM.Animatable
- JSDOM.GlobalEventHandlers
- JSDOM.ElementCSSInlineStyle
- JSDOM.SVGTests
- JSDOM.SVGExternalResourcesRequired
Constructors
SVGTextPositioningElement | |
Fields |
Instances
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 Source #
toSVGTextPositioningElement :: IsSVGTextPositioningElement o => o -> SVGTextPositioningElement Source #
newtype SVGTitleElement Source #
Functions for this inteface are in JSDOM.SVGTitleElement. Base interface functions are in:
Constructors
SVGTitleElement | |
Fields |
Instances
newtype SVGTransform Source #
Functions for this inteface are in JSDOM.SVGTransform.
Constructors
SVGTransform | |
Fields |
newtype SVGTransformList Source #
Functions for this inteface are in JSDOM.SVGTransformList.
Constructors
SVGTransformList | |
Fields |
newtype SVGURIReference Source #
Functions for this inteface are in JSDOM.SVGURIReference.
Constructors
SVGURIReference | |
Fields |
class IsGObject o => IsSVGURIReference o Source #
Instances
toSVGURIReference :: IsSVGURIReference o => o -> SVGURIReference Source #
newtype SVGUnitTypes Source #
Functions for this inteface are in JSDOM.SVGUnitTypes.
Constructors
SVGUnitTypes | |
Fields |
newtype SVGUseElement Source #
Functions for this inteface are in JSDOM.SVGUseElement. Base interface functions are in:
- JSDOM.SVGGraphicsElement
- JSDOM.SVGElement
- JSDOM.Element
- JSDOM.Node
- JSDOM.EventTarget
- JSDOM.Slotable
- JSDOM.ParentNode
- JSDOM.NonDocumentTypeChildNode
- JSDOM.DocumentAndElementEventHandlers
- JSDOM.ChildNode
- JSDOM.Animatable
- JSDOM.GlobalEventHandlers
- JSDOM.ElementCSSInlineStyle
- JSDOM.SVGTests
- JSDOM.SVGURIReference
- JSDOM.SVGExternalResourcesRequired
Constructors
SVGUseElement | |
Fields |
Instances
newtype SVGVKernElement Source #
Functions for this inteface are in JSDOM.SVGVKernElement. Base interface functions are in:
Constructors
SVGVKernElement | |
Fields |
Instances
newtype SVGViewElement Source #
Functions for this inteface are in JSDOM.SVGViewElement. Base interface functions are in:
- JSDOM.SVGElement
- JSDOM.Element
- JSDOM.Node
- JSDOM.EventTarget
- JSDOM.Slotable
- JSDOM.ParentNode
- JSDOM.NonDocumentTypeChildNode
- JSDOM.DocumentAndElementEventHandlers
- JSDOM.ChildNode
- JSDOM.Animatable
- JSDOM.GlobalEventHandlers
- JSDOM.ElementCSSInlineStyle
- JSDOM.SVGZoomAndPan
- JSDOM.SVGFitToViewBox
- JSDOM.SVGExternalResourcesRequired
Constructors
SVGViewElement | |
Fields |
Instances
newtype SVGViewSpec Source #
Functions for this inteface are in JSDOM.SVGViewSpec. Base interface functions are in:
Constructors
SVGViewSpec | |
Fields |
newtype SVGZoomAndPan Source #
Functions for this inteface are in JSDOM.SVGZoomAndPan.
Constructors
SVGZoomAndPan | |
Fields |
class IsGObject o => IsSVGZoomAndPan o Source #
toSVGZoomAndPan :: IsSVGZoomAndPan o => o -> SVGZoomAndPan Source #
newtype SVGZoomEvent Source #
Functions for this inteface are in JSDOM.SVGZoomEvent. Base interface functions are in:
Constructors
SVGZoomEvent | |
Fields |
Functions for this inteface are in JSDOM.Screen.
gTypeScreen :: JSM GType Source #
newtype ScriptProcessorNode Source #
Functions for this inteface are in JSDOM.ScriptProcessorNode. Base interface functions are in:
Constructors
ScriptProcessorNode | |
Fields |
Instances
newtype ScrollToOptions Source #
Functions for this inteface are in JSDOM.ScrollToOptions.
Constructors
ScrollToOptions | |
Fields |
newtype SecurityPolicyViolationEvent Source #
Functions for this inteface are in JSDOM.SecurityPolicyViolationEvent. Base interface functions are in:
Constructors
SecurityPolicyViolationEvent | |
Fields |
Instances
newtype SecurityPolicyViolationEventInit Source #
Functions for this inteface are in JSDOM.SecurityPolicyViolationEventInit. Base interface functions are in:
Constructors
SecurityPolicyViolationEventInit | |
Fields |
Instances
Functions for this inteface are in JSDOM.Selection.
Constructors
Selection | |
Fields
|
newtype ShadowRoot Source #
Functions for this inteface are in JSDOM.ShadowRoot. Base interface functions are in:
Constructors
ShadowRoot | |
Fields |
Instances
newtype ShadowRootInit Source #
Functions for this inteface are in JSDOM.ShadowRootInit.
Constructors
ShadowRootInit | |
Fields |
newtype SiteBoundCredential Source #
Functions for this inteface are in JSDOM.SiteBoundCredential. Base interface functions are in:
Constructors
SiteBoundCredential | |
Fields |
Instances
class (IsBasicCredential o, IsGObject o) => IsSiteBoundCredential o Source #
toSiteBoundCredential :: IsSiteBoundCredential o => o -> SiteBoundCredential Source #
newtype SiteBoundCredentialData Source #
Functions for this inteface are in JSDOM.SiteBoundCredentialData. Base interface functions are in:
Constructors
SiteBoundCredentialData | |
Fields |
Instances
class (IsCredentialData o, IsGObject o) => IsSiteBoundCredentialData o Source #
Functions for this inteface are in JSDOM.Slotable.
Constructors
Slotable | |
Fields
|
class IsGObject o => IsSlotable o Source #
Instances
toSlotable :: IsSlotable o => o -> Slotable Source #
gTypeSlotable :: JSM GType Source #
newtype SourceBuffer Source #
Functions for this inteface are in JSDOM.SourceBuffer. Base interface functions are in:
Constructors
SourceBuffer | |
Fields |
newtype SourceBufferList Source #
Functions for this inteface are in JSDOM.SourceBufferList. Base interface functions are in:
Constructors
SourceBufferList | |
Fields |
newtype SpeechSynthesis Source #
Functions for this inteface are in JSDOM.SpeechSynthesis.
Constructors
SpeechSynthesis | |
Fields |
newtype SpeechSynthesisEvent Source #
Functions for this inteface are in JSDOM.SpeechSynthesisEvent. Base interface functions are in:
Constructors
SpeechSynthesisEvent | |
Fields |
newtype SpeechSynthesisUtterance Source #
Functions for this inteface are in JSDOM.SpeechSynthesisUtterance. Base interface functions are in:
Constructors
SpeechSynthesisUtterance | |
Fields |
Instances
newtype SpeechSynthesisVoice Source #
Functions for this inteface are in JSDOM.SpeechSynthesisVoice.
Constructors
SpeechSynthesisVoice | |
Fields |
newtype StaticRange Source #
Functions for this inteface are in JSDOM.StaticRange.
Constructors
StaticRange | |
Fields |
Functions for this inteface are in JSDOM.Storage.
gTypeStorage :: JSM GType Source #
newtype StorageEvent Source #
Functions for this inteface are in JSDOM.StorageEvent. Base interface functions are in:
Constructors
StorageEvent | |
Fields |
newtype StorageEventInit Source #
Functions for this inteface are in JSDOM.StorageEventInit. Base interface functions are in:
Constructors
StorageEventInit | |
Fields |
newtype StorageInfo Source #
Functions for this inteface are in JSDOM.StorageInfo.
Constructors
StorageInfo | |
Fields |
newtype StorageQuota Source #
Functions for this inteface are in JSDOM.StorageQuota.
Constructors
StorageQuota | |
Fields |
newtype StyleMedia Source #
Functions for this inteface are in JSDOM.StyleMedia.
Constructors
StyleMedia | |
Fields |
newtype StyleSheet Source #
Functions for this inteface are in JSDOM.StyleSheet.
Constructors
StyleSheet | |
Fields |
class IsGObject o => IsStyleSheet o Source #
Instances
toStyleSheet :: IsStyleSheet o => o -> StyleSheet Source #
newtype StyleSheetList Source #
Functions for this inteface are in JSDOM.StyleSheetList.
Constructors
StyleSheetList | |
Fields |
newtype SubtleCrypto Source #
Functions for this inteface are in JSDOM.SubtleCrypto.
Constructors
SubtleCrypto | |
Fields |
Functions for this inteface are in JSDOM.Text. Base interface functions are in:
Instances
class (IsCharacterData o, IsNode o, IsEventTarget o, IsNonDocumentTypeChildNode o, IsChildNode o, IsSlotable o, IsGObject o) => IsText o Source #
newtype TextDecodeOptions Source #
Functions for this inteface are in JSDOM.TextDecodeOptions.
Constructors
TextDecodeOptions | |
Fields |
newtype TextDecoder Source #
Functions for this inteface are in JSDOM.TextDecoder.
Constructors
TextDecoder | |
Fields |
newtype TextDecoderOptions Source #
Functions for this inteface are in JSDOM.TextDecoderOptions.
Constructors
TextDecoderOptions | |
Fields |
newtype TextEncoder Source #
Functions for this inteface are in JSDOM.TextEncoder.
Constructors
TextEncoder | |
Fields |
Functions for this inteface are in JSDOM.TextEvent. Base interface functions are in:
Constructors
TextEvent | |
Fields
|
newtype TextMetrics Source #
Functions for this inteface are in JSDOM.TextMetrics.
Constructors
TextMetrics | |
Fields |
Functions for this inteface are in JSDOM.TextTrack. Base interface functions are in:
Constructors
TextTrack | |
Fields
|
newtype TextTrackCue Source #
Functions for this inteface are in JSDOM.TextTrackCue. Base interface functions are in:
Constructors
TextTrackCue | |
Fields |
class (IsEventTarget o, IsGObject o) => IsTextTrackCue o Source #
toTextTrackCue :: IsTextTrackCue o => o -> TextTrackCue Source #
newtype TextTrackCueList Source #
Functions for this inteface are in JSDOM.TextTrackCueList.
Constructors
TextTrackCueList | |
Fields |
newtype TextTrackList Source #
Functions for this inteface are in JSDOM.TextTrackList. Base interface functions are in:
Constructors
TextTrackList | |
Fields |
newtype TimeRanges Source #
Functions for this inteface are in JSDOM.TimeRanges.
Constructors
TimeRanges | |
Fields |
Functions for this inteface are in JSDOM.Touch.
gTypeTouch :: JSM GType Source #
newtype TouchEvent Source #
Functions for this inteface are in JSDOM.TouchEvent. Base interface functions are in:
Constructors
TouchEvent | |
Fields |
newtype TouchEventInit Source #
Functions for this inteface are in JSDOM.TouchEventInit. Base interface functions are in:
Constructors
TouchEventInit | |
Fields |
Functions for this inteface are in JSDOM.TouchList.
Constructors
TouchList | |
Fields
|
newtype TrackEvent Source #
Functions for this inteface are in JSDOM.TrackEvent. Base interface functions are in:
Constructors
TrackEvent | |
Fields |
newtype TrackEventInit Source #
Functions for this inteface are in JSDOM.TrackEventInit. Base interface functions are in:
Constructors
TrackEventInit | |
Fields |
newtype TransitionEvent Source #
Functions for this inteface are in JSDOM.TransitionEvent. Base interface functions are in:
Constructors
TransitionEvent | |
Fields |
newtype TransitionEventInit Source #
Functions for this inteface are in JSDOM.TransitionEventInit. Base interface functions are in:
Constructors
TransitionEventInit | |
Fields |
newtype TreeWalker Source #
Functions for this inteface are in JSDOM.TreeWalker.
Constructors
TreeWalker | |
Fields |
Functions for this inteface are in JSDOM.UIEvent. Base interface functions are in:
class (IsEvent o, IsGObject o) => IsUIEvent o Source #
Instances
gTypeUIEvent :: JSM GType Source #
newtype UIEventInit Source #
Functions for this inteface are in JSDOM.UIEventInit. Base interface functions are in:
Constructors
UIEventInit | |
Fields |
class (IsEventInit o, IsGObject o) => IsUIEventInit o Source #
Instances
toUIEventInit :: IsUIEventInit o => o -> UIEventInit Source #
Functions for this inteface are in JSDOM.URL.
newtype URLSearchParams Source #
Functions for this inteface are in JSDOM.URLSearchParams.
Constructors
URLSearchParams | |
Fields |
newtype UserMessageHandler Source #
Functions for this inteface are in JSDOM.UserMessageHandler.
Constructors
UserMessageHandler | |
Fields |
newtype UserMessageHandlersNamespace Source #
Functions for this inteface are in JSDOM.UserMessageHandlersNamespace.
Constructors
UserMessageHandlersNamespace | |
Fields |
Functions for this inteface are in JSDOM.VTTCue. Base interface functions are in:
gTypeVTTCue :: JSM GType Source #
Functions for this inteface are in JSDOM.VTTRegion.
Constructors
VTTRegion | |
Fields
|
newtype VTTRegionList Source #
Functions for this inteface are in JSDOM.VTTRegionList.
Constructors
VTTRegionList | |
Fields |
newtype ValidityState Source #
Functions for this inteface are in JSDOM.ValidityState.
Constructors
ValidityState | |
Fields |
newtype VideoPlaybackQuality Source #
Functions for this inteface are in JSDOM.VideoPlaybackQuality.
Constructors
VideoPlaybackQuality | |
Fields |
newtype VideoTrack Source #
Functions for this inteface are in JSDOM.VideoTrack.
Constructors
VideoTrack | |
Fields |
newtype VideoTrackList Source #
Functions for this inteface are in JSDOM.VideoTrackList. Base interface functions are in:
Constructors
VideoTrackList | |
Fields |
newtype WaveShaperNode Source #
Functions for this inteface are in JSDOM.WaveShaperNode. Base interface functions are in:
Constructors
WaveShaperNode | |
Fields |
newtype WebGL2RenderingContext Source #
Functions for this inteface are in JSDOM.WebGL2RenderingContext. Base interface functions are in:
Constructors
WebGL2RenderingContext | |
Fields |
Instances
newtype WebGLActiveInfo Source #
Functions for this inteface are in JSDOM.WebGLActiveInfo.
Constructors
WebGLActiveInfo | |
Fields |
newtype WebGLBuffer Source #
Functions for this inteface are in JSDOM.WebGLBuffer.
Constructors
WebGLBuffer | |
Fields |
newtype WebGLCompressedTextureATC Source #
Functions for this inteface are in JSDOM.WebGLCompressedTextureATC.
Constructors
WebGLCompressedTextureATC | |
Fields |
newtype WebGLCompressedTexturePVRTC Source #
Functions for this inteface are in JSDOM.WebGLCompressedTexturePVRTC.
Constructors
WebGLCompressedTexturePVRTC | |
Fields |
newtype WebGLCompressedTextureS3TC Source #
Functions for this inteface are in JSDOM.WebGLCompressedTextureS3TC.
Constructors
WebGLCompressedTextureS3TC | |
Fields |
newtype WebGLContextAttributes Source #
Functions for this inteface are in JSDOM.WebGLContextAttributes.
Constructors
WebGLContextAttributes | |
Fields |
newtype WebGLContextEvent Source #
Functions for this inteface are in JSDOM.WebGLContextEvent. Base interface functions are in:
Constructors
WebGLContextEvent | |
Fields |
newtype WebGLContextEventInit Source #
Functions for this inteface are in JSDOM.WebGLContextEventInit. Base interface functions are in:
Constructors
WebGLContextEventInit | |
Fields |
newtype WebGLDebugRendererInfo Source #
Functions for this inteface are in JSDOM.WebGLDebugRendererInfo.
Constructors
WebGLDebugRendererInfo | |
Fields |
newtype WebGLDebugShaders Source #
Functions for this inteface are in JSDOM.WebGLDebugShaders.
Constructors
WebGLDebugShaders | |
Fields |
newtype WebGLDepthTexture Source #
Functions for this inteface are in JSDOM.WebGLDepthTexture.
Constructors
WebGLDepthTexture | |
Fields |
newtype WebGLDrawBuffers Source #
Functions for this inteface are in JSDOM.WebGLDrawBuffers.
Constructors
WebGLDrawBuffers | |
Fields |
newtype WebGLFramebuffer Source #
Functions for this inteface are in JSDOM.WebGLFramebuffer.
Constructors
WebGLFramebuffer | |
Fields |
newtype WebGLLoseContext Source #
Functions for this inteface are in JSDOM.WebGLLoseContext.
Constructors
WebGLLoseContext | |
Fields |
newtype WebGLProgram Source #
Functions for this inteface are in JSDOM.WebGLProgram.
Constructors
WebGLProgram | |
Fields |
newtype WebGLQuery Source #
Functions for this inteface are in JSDOM.WebGLQuery.
Constructors
WebGLQuery | |
Fields |
newtype WebGLRenderbuffer Source #
Functions for this inteface are in JSDOM.WebGLRenderbuffer.
Constructors
WebGLRenderbuffer | |
Fields |
newtype WebGLRenderingContext Source #
Functions for this inteface are in JSDOM.WebGLRenderingContext. Base interface functions are in:
Constructors
WebGLRenderingContext | |
Fields |
Instances
newtype WebGLRenderingContextBase Source #
Functions for this inteface are in JSDOM.WebGLRenderingContextBase.
Constructors
WebGLRenderingContextBase | |
Fields |
Instances
class IsGObject o => IsWebGLRenderingContextBase o Source #
toWebGLRenderingContextBase :: IsWebGLRenderingContextBase o => o -> WebGLRenderingContextBase Source #
newtype WebGLSampler Source #
Functions for this inteface are in JSDOM.WebGLSampler.
Constructors
WebGLSampler | |
Fields |
newtype WebGLShader Source #
Functions for this inteface are in JSDOM.WebGLShader.
Constructors
WebGLShader | |
Fields |
newtype WebGLShaderPrecisionFormat Source #
Functions for this inteface are in JSDOM.WebGLShaderPrecisionFormat.
Constructors
WebGLShaderPrecisionFormat | |
Fields |
Functions for this inteface are in JSDOM.WebGLSync.
Constructors
WebGLSync | |
Fields
|
newtype WebGLTexture Source #
Functions for this inteface are in JSDOM.WebGLTexture.
Constructors
WebGLTexture | |
Fields |
newtype WebGLTransformFeedback Source #
Functions for this inteface are in JSDOM.WebGLTransformFeedback.
Constructors
WebGLTransformFeedback | |
Fields |
newtype WebGLUniformLocation Source #
Functions for this inteface are in JSDOM.WebGLUniformLocation.
Constructors
WebGLUniformLocation | |
Fields |
newtype WebGLVertexArrayObject Source #
Functions for this inteface are in JSDOM.WebGLVertexArrayObject.
Constructors
WebGLVertexArrayObject | |
Fields |
newtype WebGLVertexArrayObjectOES Source #
Functions for this inteface are in JSDOM.WebGLVertexArrayObjectOES.
Constructors
WebGLVertexArrayObjectOES | |
Fields |
newtype WebGPUBuffer Source #
Functions for this inteface are in JSDOM.WebGPUBuffer.
Constructors
WebGPUBuffer | |
Fields |
newtype WebGPUCommandBuffer Source #
Functions for this inteface are in JSDOM.WebGPUCommandBuffer.
Constructors
WebGPUCommandBuffer | |
Fields |
newtype WebGPUCommandQueue Source #
Functions for this inteface are in JSDOM.WebGPUCommandQueue.
Constructors
WebGPUCommandQueue | |
Fields |
newtype WebGPUComputeCommandEncoder Source #
Functions for this inteface are in JSDOM.WebGPUComputeCommandEncoder.
Constructors
WebGPUComputeCommandEncoder | |
Fields |
newtype WebGPUComputePipelineState Source #
Functions for this inteface are in JSDOM.WebGPUComputePipelineState.
Constructors
WebGPUComputePipelineState | |
Fields |
newtype WebGPUDepthStencilDescriptor Source #
Functions for this inteface are in JSDOM.WebGPUDepthStencilDescriptor.
Constructors
WebGPUDepthStencilDescriptor | |
Fields |
newtype WebGPUDepthStencilState Source #
Functions for this inteface are in JSDOM.WebGPUDepthStencilState.
Constructors
WebGPUDepthStencilState | |
Fields |
newtype WebGPUDrawable Source #
Functions for this inteface are in JSDOM.WebGPUDrawable.
Constructors
WebGPUDrawable | |
Fields |
newtype WebGPUFunction Source #
Functions for this inteface are in JSDOM.WebGPUFunction.
Constructors
WebGPUFunction | |
Fields |
newtype WebGPULibrary Source #
Functions for this inteface are in JSDOM.WebGPULibrary.
Constructors
WebGPULibrary | |
Fields |
newtype WebGPURenderCommandEncoder Source #
Functions for this inteface are in JSDOM.WebGPURenderCommandEncoder.
Constructors
WebGPURenderCommandEncoder | |
Fields |
newtype WebGPURenderPassAttachmentDescriptor Source #
Functions for this inteface are in JSDOM.WebGPURenderPassAttachmentDescriptor.
Constructors
WebGPURenderPassAttachmentDescriptor | |
Instances
class IsGObject o => IsWebGPURenderPassAttachmentDescriptor o Source #
toWebGPURenderPassAttachmentDescriptor :: IsWebGPURenderPassAttachmentDescriptor o => o -> WebGPURenderPassAttachmentDescriptor Source #
newtype WebGPURenderPassColorAttachmentDescriptor Source #
Functions for this inteface are in JSDOM.WebGPURenderPassColorAttachmentDescriptor. Base interface functions are in:
Mozilla WebGPURenderPassColorAttachmentDescriptor documentation
Constructors
WebGPURenderPassColorAttachmentDescriptor | |
Instances
noWebGPURenderPassColorAttachmentDescriptor :: Maybe WebGPURenderPassColorAttachmentDescriptor Source #
newtype WebGPURenderPassDepthAttachmentDescriptor Source #
Functions for this inteface are in JSDOM.WebGPURenderPassDepthAttachmentDescriptor. Base interface functions are in:
Mozilla WebGPURenderPassDepthAttachmentDescriptor documentation
Constructors
WebGPURenderPassDepthAttachmentDescriptor | |
Instances
noWebGPURenderPassDepthAttachmentDescriptor :: Maybe WebGPURenderPassDepthAttachmentDescriptor Source #
newtype WebGPURenderPassDescriptor Source #
Functions for this inteface are in JSDOM.WebGPURenderPassDescriptor.
Constructors
WebGPURenderPassDescriptor | |
Fields |
newtype WebGPURenderPipelineColorAttachmentDescriptor Source #
Functions for this inteface are in JSDOM.WebGPURenderPipelineColorAttachmentDescriptor.
Mozilla WebGPURenderPipelineColorAttachmentDescriptor documentation
Constructors
WebGPURenderPipelineColorAttachmentDescriptor | |
Instances
noWebGPURenderPipelineColorAttachmentDescriptor :: Maybe WebGPURenderPipelineColorAttachmentDescriptor Source #
newtype WebGPURenderPipelineDescriptor Source #
Functions for this inteface are in JSDOM.WebGPURenderPipelineDescriptor.
Constructors
WebGPURenderPipelineDescriptor | |
Fields |
Instances
newtype WebGPURenderPipelineState Source #
Functions for this inteface are in JSDOM.WebGPURenderPipelineState.
Constructors
WebGPURenderPipelineState | |
Fields |
newtype WebGPURenderingContext Source #
Functions for this inteface are in JSDOM.WebGPURenderingContext.
Constructors
WebGPURenderingContext | |
Fields |
newtype WebGPUSize Source #
Functions for this inteface are in JSDOM.WebGPUSize.
Constructors
WebGPUSize | |
Fields |
newtype WebGPUTexture Source #
Functions for this inteface are in JSDOM.WebGPUTexture.
Constructors
WebGPUTexture | |
Fields |
newtype WebGPUTextureDescriptor Source #
Functions for this inteface are in JSDOM.WebGPUTextureDescriptor.
Constructors
WebGPUTextureDescriptor | |
Fields |
newtype WebKitAnimationEvent Source #
Functions for this inteface are in JSDOM.WebKitAnimationEvent. Base interface functions are in:
Constructors
WebKitAnimationEvent | |
Fields |
newtype WebKitAnimationEventInit Source #
Functions for this inteface are in JSDOM.WebKitAnimationEventInit. Base interface functions are in:
Constructors
WebKitAnimationEventInit | |
Fields |
Instances
newtype WebKitCSSMatrix Source #
Functions for this inteface are in JSDOM.WebKitCSSMatrix.
Constructors
WebKitCSSMatrix | |
Fields |
newtype WebKitCSSRegionRule Source #
Functions for this inteface are in JSDOM.WebKitCSSRegionRule. Base interface functions are in:
Constructors
WebKitCSSRegionRule | |
Fields |
newtype WebKitCSSViewportRule Source #
Functions for this inteface are in JSDOM.WebKitCSSViewportRule. Base interface functions are in:
Constructors
WebKitCSSViewportRule | |
Fields |
newtype WebKitMediaKeyError Source #
Functions for this inteface are in JSDOM.WebKitMediaKeyError.
Constructors
WebKitMediaKeyError | |
Fields |
newtype WebKitMediaKeyMessageEvent Source #
Functions for this inteface are in JSDOM.WebKitMediaKeyMessageEvent. Base interface functions are in:
Constructors
WebKitMediaKeyMessageEvent | |
Fields |
Instances
newtype WebKitMediaKeyMessageEventInit Source #
Functions for this inteface are in JSDOM.WebKitMediaKeyMessageEventInit. Base interface functions are in:
Constructors
WebKitMediaKeyMessageEventInit | |
Fields |
Instances
newtype WebKitMediaKeyNeededEvent Source #
Functions for this inteface are in JSDOM.WebKitMediaKeyNeededEvent. Base interface functions are in:
Constructors
WebKitMediaKeyNeededEvent | |
Fields |
Instances
newtype WebKitMediaKeyNeededEventInit Source #
Functions for this inteface are in JSDOM.WebKitMediaKeyNeededEventInit. Base interface functions are in:
Constructors
WebKitMediaKeyNeededEventInit | |
Fields |
Instances
newtype WebKitMediaKeySession Source #
Functions for this inteface are in JSDOM.WebKitMediaKeySession. Base interface functions are in:
Constructors
WebKitMediaKeySession | |
Fields |
newtype WebKitMediaKeys Source #
Functions for this inteface are in JSDOM.WebKitMediaKeys.
Constructors
WebKitMediaKeys | |
Fields |
newtype WebKitNamedFlow Source #
Functions for this inteface are in JSDOM.WebKitNamedFlow. Base interface functions are in:
Constructors
WebKitNamedFlow | |
Fields |
newtype WebKitNamespace Source #
Functions for this inteface are in JSDOM.WebKitNamespace.
Constructors
WebKitNamespace | |
Fields |
newtype WebKitPlaybackTargetAvailabilityEvent Source #
Functions for this inteface are in JSDOM.WebKitPlaybackTargetAvailabilityEvent. Base interface functions are in:
Constructors
WebKitPlaybackTargetAvailabilityEvent | |
Instances
newtype WebKitPlaybackTargetAvailabilityEventInit Source #
Functions for this inteface are in JSDOM.WebKitPlaybackTargetAvailabilityEventInit. Base interface functions are in:
Mozilla WebKitPlaybackTargetAvailabilityEventInit documentation
Constructors
WebKitPlaybackTargetAvailabilityEventInit | |
Instances
noWebKitPlaybackTargetAvailabilityEventInit :: Maybe WebKitPlaybackTargetAvailabilityEventInit Source #
newtype WebKitPoint Source #
Functions for this inteface are in JSDOM.WebKitPoint.
Constructors
WebKitPoint | |
Fields |
newtype WebKitSubtleCrypto Source #
Functions for this inteface are in JSDOM.WebKitSubtleCrypto.
Constructors
WebKitSubtleCrypto | |
Fields |
newtype WebKitTransitionEvent Source #
Functions for this inteface are in JSDOM.WebKitTransitionEvent. Base interface functions are in:
Constructors
WebKitTransitionEvent | |
Fields |
newtype WebKitTransitionEventInit Source #
Functions for this inteface are in JSDOM.WebKitTransitionEventInit. Base interface functions are in:
Constructors
WebKitTransitionEventInit | |
Fields |
Instances
Functions for this inteface are in JSDOM.WebSocket. Base interface functions are in:
Constructors
WebSocket | |
Fields
|
newtype WheelEvent Source #
Functions for this inteface are in JSDOM.WheelEvent. Base interface functions are in:
Constructors
WheelEvent | |
Fields |
newtype WheelEventInit Source #
Functions for this inteface are in JSDOM.WheelEventInit. Base interface functions are in:
Constructors
WheelEventInit | |
Fields |
Instances
Functions for this inteface are in JSDOM.Window. Base interface functions are in:
Instances
gTypeWindow :: JSM GType Source #
newtype WindowEventHandlers Source #
Functions for this inteface are in JSDOM.WindowEventHandlers.
Constructors
WindowEventHandlers | |
Fields |
class IsGObject o => IsWindowEventHandlers o Source #
toWindowEventHandlers :: IsWindowEventHandlers o => o -> WindowEventHandlers Source #
newtype WindowOrWorkerGlobalScope Source #
Functions for this inteface are in JSDOM.WindowOrWorkerGlobalScope.
Constructors
WindowOrWorkerGlobalScope | |
Fields |
Instances
class IsGObject o => IsWindowOrWorkerGlobalScope o Source #
toWindowOrWorkerGlobalScope :: IsWindowOrWorkerGlobalScope o => o -> WindowOrWorkerGlobalScope Source #
Functions for this inteface are in JSDOM.Worker. Base interface functions are in:
gTypeWorker :: JSM GType Source #
newtype WorkerGlobalScope Source #
Functions for this inteface are in JSDOM.WorkerGlobalScope. Base interface functions are in:
Constructors
WorkerGlobalScope | |
Fields |
Instances
class (IsEventTarget o, IsWindowOrWorkerGlobalScope o, IsGlobalPerformance o, IsGlobalCrypto o, IsGObject o) => IsWorkerGlobalScope o Source #
toWorkerGlobalScope :: IsWorkerGlobalScope o => o -> WorkerGlobalScope Source #
newtype WorkerLocation Source #
Functions for this inteface are in JSDOM.WorkerLocation.
Constructors
WorkerLocation | |
Fields |
newtype WorkerNavigator Source #
Functions for this inteface are in JSDOM.WorkerNavigator. Base interface functions are in:
Constructors
WorkerNavigator | |
Fields |
newtype WritableStream Source #
Functions for this inteface are in JSDOM.WritableStream.
Constructors
WritableStream | |
Fields |
newtype XMLDocument Source #
Functions for this inteface are in JSDOM.XMLDocument. Base interface functions are in:
Constructors
XMLDocument | |
Fields |
Instances
newtype XMLHttpRequest Source #
Functions for this inteface are in JSDOM.XMLHttpRequest. Base interface functions are in:
Constructors
XMLHttpRequest | |
Fields |
Instances
newtype XMLHttpRequestEventTarget Source #
Functions for this inteface are in JSDOM.XMLHttpRequestEventTarget. Base interface functions are in:
Constructors
XMLHttpRequestEventTarget | |
Fields |
Instances
class (IsEventTarget o, IsGObject o) => IsXMLHttpRequestEventTarget o Source #
toXMLHttpRequestEventTarget :: IsXMLHttpRequestEventTarget o => o -> XMLHttpRequestEventTarget Source #
newtype XMLHttpRequestProgressEvent Source #
Functions for this inteface are in JSDOM.XMLHttpRequestProgressEvent. Base interface functions are in:
Constructors
XMLHttpRequestProgressEvent | |
Fields |
Instances
newtype XMLHttpRequestUpload Source #
Functions for this inteface are in JSDOM.XMLHttpRequestUpload. Base interface functions are in:
Constructors
XMLHttpRequestUpload | |
Fields |
Instances
newtype XMLSerializer Source #
Functions for this inteface are in JSDOM.XMLSerializer.
Constructors
XMLSerializer | |
Fields |
newtype XPathEvaluator Source #
Functions for this inteface are in JSDOM.XPathEvaluator.
Constructors
XPathEvaluator | |
Fields |
newtype XPathException Source #
Functions for this inteface are in JSDOM.XPathException.
Constructors
XPathException | |
Fields |
newtype XPathExpression Source #
Functions for this inteface are in JSDOM.XPathExpression.
Constructors
XPathExpression | |
Fields |
newtype XPathNSResolver Source #
Functions for this inteface are in JSDOM.XPathNSResolver.
Constructors
XPathNSResolver | |
Fields |
newtype XPathResult Source #
Functions for this inteface are in JSDOM.XPathResult.
Constructors
XPathResult | |
Fields |
newtype XSLTProcessor Source #
Functions for this inteface are in JSDOM.XSLTProcessor.
Constructors
XSLTProcessor | |
Fields |