{-# OPTIONS_GHC -fno-warn-orphans -fno-warn-unused-imports #-} -- Generated code. {-# OPTIONS_GHC -fno-warn-unused-imports #-} {-# LANGUAGE ForeignFunctionInterface, ConstraintKinds, TypeFamilies, MultiParamTypeClasses, KindSignatures, FlexibleInstances, UndecidableInstances, DataKinds, OverloadedStrings, NegativeLiterals, FlexibleContexts #-} module GI.WebKitAttributes where import Prelude () import Data.GI.Base.ShortPrelude import Data.Char import Data.Int import Data.Word import qualified Data.ByteString.Char8 as B import Data.ByteString.Char8 (ByteString) import qualified Data.Map as Map import Foreign.C import Foreign.Ptr import Foreign.ForeignPtr import Foreign.ForeignPtr.Unsafe (unsafeForeignPtrToPtr) import Foreign.Storable (peek, poke, sizeOf) import Control.Applicative ((<$>)) import Control.Exception (onException) import Control.Monad.IO.Class import qualified Data.Text as T import Data.GI.Base.Attributes hiding (get, set) import Data.GI.Base.BasicTypes import Data.GI.Base.BasicConversions import Data.GI.Base.Closure import Data.GI.Base.GError import Data.GI.Base.GHashTable import Data.GI.Base.GParamSpec import Data.GI.Base.GVariant import Data.GI.Base.GValue import Data.GI.Base.ManagedPtr import Data.GI.Base.Overloading import Data.GI.Base.Properties hiding (new) import Data.GI.Base.Signals (SignalConnectMode(..), connectSignalFunPtr, SignalHandlerId) import Data.GI.Base.Utils import qualified GI.Gtk as Gtk import qualified GI.GtkAttributes as GtkA import qualified GI.Soup as Soup import qualified GI.SoupAttributes as SoupA import GI.WebKit -- VVV Prop "is-id" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMAttrIsId :: (MonadIO m, DOMAttrK o) => o -> m Bool getDOMAttrIsId obj = liftIO $ getObjectPropertyBool obj "is-id" data DOMAttrIsIdPropertyInfo instance AttrInfo DOMAttrIsIdPropertyInfo where type AttrAllowedOps DOMAttrIsIdPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMAttrIsIdPropertyInfo = (~) () type AttrBaseTypeConstraint DOMAttrIsIdPropertyInfo = DOMAttrK type AttrGetType DOMAttrIsIdPropertyInfo = Bool type AttrLabel DOMAttrIsIdPropertyInfo = "DOMAttr::is-id" attrGet _ = getDOMAttrIsId attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "name" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMAttrName :: (MonadIO m, DOMAttrK o) => o -> m T.Text getDOMAttrName obj = liftIO $ getObjectPropertyString obj "name" data DOMAttrNamePropertyInfo instance AttrInfo DOMAttrNamePropertyInfo where type AttrAllowedOps DOMAttrNamePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMAttrNamePropertyInfo = (~) () type AttrBaseTypeConstraint DOMAttrNamePropertyInfo = DOMAttrK type AttrGetType DOMAttrNamePropertyInfo = T.Text type AttrLabel DOMAttrNamePropertyInfo = "DOMAttr::name" attrGet _ = getDOMAttrName attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "owner-element" -- Type: TInterface "WebKit" "DOMElement" -- Flags: [PropertyReadable] getDOMAttrOwnerElement :: (MonadIO m, DOMAttrK o) => o -> m DOMElement getDOMAttrOwnerElement obj = liftIO $ getObjectPropertyObject obj "owner-element" DOMElement data DOMAttrOwnerElementPropertyInfo instance AttrInfo DOMAttrOwnerElementPropertyInfo where type AttrAllowedOps DOMAttrOwnerElementPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMAttrOwnerElementPropertyInfo = (~) () type AttrBaseTypeConstraint DOMAttrOwnerElementPropertyInfo = DOMAttrK type AttrGetType DOMAttrOwnerElementPropertyInfo = DOMElement type AttrLabel DOMAttrOwnerElementPropertyInfo = "DOMAttr::owner-element" attrGet _ = getDOMAttrOwnerElement attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "specified" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMAttrSpecified :: (MonadIO m, DOMAttrK o) => o -> m Bool getDOMAttrSpecified obj = liftIO $ getObjectPropertyBool obj "specified" data DOMAttrSpecifiedPropertyInfo instance AttrInfo DOMAttrSpecifiedPropertyInfo where type AttrAllowedOps DOMAttrSpecifiedPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMAttrSpecifiedPropertyInfo = (~) () type AttrBaseTypeConstraint DOMAttrSpecifiedPropertyInfo = DOMAttrK type AttrGetType DOMAttrSpecifiedPropertyInfo = Bool type AttrLabel DOMAttrSpecifiedPropertyInfo = "DOMAttr::specified" attrGet _ = getDOMAttrSpecified attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "value" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMAttrValue :: (MonadIO m, DOMAttrK o) => o -> m T.Text getDOMAttrValue obj = liftIO $ getObjectPropertyString obj "value" setDOMAttrValue :: (MonadIO m, DOMAttrK o) => o -> T.Text -> m () setDOMAttrValue obj val = liftIO $ setObjectPropertyString obj "value" val constructDOMAttrValue :: T.Text -> IO ([Char], GValue) constructDOMAttrValue val = constructObjectPropertyString "value" val data DOMAttrValuePropertyInfo instance AttrInfo DOMAttrValuePropertyInfo where type AttrAllowedOps DOMAttrValuePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMAttrValuePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMAttrValuePropertyInfo = DOMAttrK type AttrGetType DOMAttrValuePropertyInfo = T.Text type AttrLabel DOMAttrValuePropertyInfo = "DOMAttr::value" attrGet _ = getDOMAttrValue attrSet _ = setDOMAttrValue attrConstruct _ = constructDOMAttrValue type instance AttributeList DOMAttr = '[ '("base-uri", DOMNodeBaseUriPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("is-id", DOMAttrIsIdPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("name", DOMAttrNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("owner-element", DOMAttrOwnerElementPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("specified", DOMAttrSpecifiedPropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("value", DOMAttrValuePropertyInfo)] -- VVV Prop "enabled" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMAudioTrackEnabled :: (MonadIO m, DOMAudioTrackK o) => o -> m Bool getDOMAudioTrackEnabled obj = liftIO $ getObjectPropertyBool obj "enabled" setDOMAudioTrackEnabled :: (MonadIO m, DOMAudioTrackK o) => o -> Bool -> m () setDOMAudioTrackEnabled obj val = liftIO $ setObjectPropertyBool obj "enabled" val constructDOMAudioTrackEnabled :: Bool -> IO ([Char], GValue) constructDOMAudioTrackEnabled val = constructObjectPropertyBool "enabled" val data DOMAudioTrackEnabledPropertyInfo instance AttrInfo DOMAudioTrackEnabledPropertyInfo where type AttrAllowedOps DOMAudioTrackEnabledPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMAudioTrackEnabledPropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMAudioTrackEnabledPropertyInfo = DOMAudioTrackK type AttrGetType DOMAudioTrackEnabledPropertyInfo = Bool type AttrLabel DOMAudioTrackEnabledPropertyInfo = "DOMAudioTrack::enabled" attrGet _ = getDOMAudioTrackEnabled attrSet _ = setDOMAudioTrackEnabled attrConstruct _ = constructDOMAudioTrackEnabled -- VVV Prop "id" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMAudioTrackId :: (MonadIO m, DOMAudioTrackK o) => o -> m T.Text getDOMAudioTrackId obj = liftIO $ getObjectPropertyString obj "id" data DOMAudioTrackIdPropertyInfo instance AttrInfo DOMAudioTrackIdPropertyInfo where type AttrAllowedOps DOMAudioTrackIdPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMAudioTrackIdPropertyInfo = (~) () type AttrBaseTypeConstraint DOMAudioTrackIdPropertyInfo = DOMAudioTrackK type AttrGetType DOMAudioTrackIdPropertyInfo = T.Text type AttrLabel DOMAudioTrackIdPropertyInfo = "DOMAudioTrack::id" attrGet _ = getDOMAudioTrackId attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "kind" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMAudioTrackKind :: (MonadIO m, DOMAudioTrackK o) => o -> m T.Text getDOMAudioTrackKind obj = liftIO $ getObjectPropertyString obj "kind" data DOMAudioTrackKindPropertyInfo instance AttrInfo DOMAudioTrackKindPropertyInfo where type AttrAllowedOps DOMAudioTrackKindPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMAudioTrackKindPropertyInfo = (~) () type AttrBaseTypeConstraint DOMAudioTrackKindPropertyInfo = DOMAudioTrackK type AttrGetType DOMAudioTrackKindPropertyInfo = T.Text type AttrLabel DOMAudioTrackKindPropertyInfo = "DOMAudioTrack::kind" attrGet _ = getDOMAudioTrackKind attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "label" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMAudioTrackLabel :: (MonadIO m, DOMAudioTrackK o) => o -> m T.Text getDOMAudioTrackLabel obj = liftIO $ getObjectPropertyString obj "label" data DOMAudioTrackLabelPropertyInfo instance AttrInfo DOMAudioTrackLabelPropertyInfo where type AttrAllowedOps DOMAudioTrackLabelPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMAudioTrackLabelPropertyInfo = (~) () type AttrBaseTypeConstraint DOMAudioTrackLabelPropertyInfo = DOMAudioTrackK type AttrGetType DOMAudioTrackLabelPropertyInfo = T.Text type AttrLabel DOMAudioTrackLabelPropertyInfo = "DOMAudioTrack::label" attrGet _ = getDOMAudioTrackLabel attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "language" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMAudioTrackLanguage :: (MonadIO m, DOMAudioTrackK o) => o -> m T.Text getDOMAudioTrackLanguage obj = liftIO $ getObjectPropertyString obj "language" data DOMAudioTrackLanguagePropertyInfo instance AttrInfo DOMAudioTrackLanguagePropertyInfo where type AttrAllowedOps DOMAudioTrackLanguagePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMAudioTrackLanguagePropertyInfo = (~) () type AttrBaseTypeConstraint DOMAudioTrackLanguagePropertyInfo = DOMAudioTrackK type AttrGetType DOMAudioTrackLanguagePropertyInfo = T.Text type AttrLabel DOMAudioTrackLanguagePropertyInfo = "DOMAudioTrack::language" attrGet _ = getDOMAudioTrackLanguage attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMAudioTrack = '[ '("core-object", DOMObjectCoreObjectPropertyInfo), '("enabled", DOMAudioTrackEnabledPropertyInfo), '("id", DOMAudioTrackIdPropertyInfo), '("kind", DOMAudioTrackKindPropertyInfo), '("label", DOMAudioTrackLabelPropertyInfo), '("language", DOMAudioTrackLanguagePropertyInfo)] -- VVV Prop "length" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMAudioTrackListLength :: (MonadIO m, DOMAudioTrackListK o) => o -> m Word64 getDOMAudioTrackListLength obj = liftIO $ getObjectPropertyUInt64 obj "length" data DOMAudioTrackListLengthPropertyInfo instance AttrInfo DOMAudioTrackListLengthPropertyInfo where type AttrAllowedOps DOMAudioTrackListLengthPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMAudioTrackListLengthPropertyInfo = (~) () type AttrBaseTypeConstraint DOMAudioTrackListLengthPropertyInfo = DOMAudioTrackListK type AttrGetType DOMAudioTrackListLengthPropertyInfo = Word64 type AttrLabel DOMAudioTrackListLengthPropertyInfo = "DOMAudioTrackList::length" attrGet _ = getDOMAudioTrackListLength attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMAudioTrackList = '[ '("core-object", DOMObjectCoreObjectPropertyInfo), '("length", DOMAudioTrackListLengthPropertyInfo)] -- VVV Prop "visible" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMBarInfoVisible :: (MonadIO m, DOMBarInfoK o) => o -> m Bool getDOMBarInfoVisible obj = liftIO $ getObjectPropertyBool obj "visible" data DOMBarInfoVisiblePropertyInfo instance AttrInfo DOMBarInfoVisiblePropertyInfo where type AttrAllowedOps DOMBarInfoVisiblePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMBarInfoVisiblePropertyInfo = (~) () type AttrBaseTypeConstraint DOMBarInfoVisiblePropertyInfo = DOMBarInfoK type AttrGetType DOMBarInfoVisiblePropertyInfo = Bool type AttrLabel DOMBarInfoVisiblePropertyInfo = "DOMBarInfo::visible" attrGet _ = getDOMBarInfoVisible attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMBarInfo = '[ '("core-object", DOMObjectCoreObjectPropertyInfo), '("visible", DOMBarInfoVisiblePropertyInfo)] -- VVV Prop "visible" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMBarPropVisible :: (MonadIO m, DOMBarPropK o) => o -> m Bool getDOMBarPropVisible obj = liftIO $ getObjectPropertyBool obj "visible" data DOMBarPropVisiblePropertyInfo instance AttrInfo DOMBarPropVisiblePropertyInfo where type AttrAllowedOps DOMBarPropVisiblePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMBarPropVisiblePropertyInfo = (~) () type AttrBaseTypeConstraint DOMBarPropVisiblePropertyInfo = DOMBarPropK type AttrGetType DOMBarPropVisiblePropertyInfo = Bool type AttrLabel DOMBarPropVisiblePropertyInfo = "DOMBarProp::visible" attrGet _ = getDOMBarPropVisible attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMBarProp = '[ '("core-object", DOMObjectCoreObjectPropertyInfo), '("visible", DOMBarPropVisiblePropertyInfo)] -- VVV Prop "charging" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMBatteryManagerCharging :: (MonadIO m, DOMBatteryManagerK o) => o -> m Bool getDOMBatteryManagerCharging obj = liftIO $ getObjectPropertyBool obj "charging" data DOMBatteryManagerChargingPropertyInfo instance AttrInfo DOMBatteryManagerChargingPropertyInfo where type AttrAllowedOps DOMBatteryManagerChargingPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMBatteryManagerChargingPropertyInfo = (~) () type AttrBaseTypeConstraint DOMBatteryManagerChargingPropertyInfo = DOMBatteryManagerK type AttrGetType DOMBatteryManagerChargingPropertyInfo = Bool type AttrLabel DOMBatteryManagerChargingPropertyInfo = "DOMBatteryManager::charging" attrGet _ = getDOMBatteryManagerCharging attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "charging-time" -- Type: TBasicType TDouble -- Flags: [PropertyReadable] getDOMBatteryManagerChargingTime :: (MonadIO m, DOMBatteryManagerK o) => o -> m Double getDOMBatteryManagerChargingTime obj = liftIO $ getObjectPropertyDouble obj "charging-time" data DOMBatteryManagerChargingTimePropertyInfo instance AttrInfo DOMBatteryManagerChargingTimePropertyInfo where type AttrAllowedOps DOMBatteryManagerChargingTimePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMBatteryManagerChargingTimePropertyInfo = (~) () type AttrBaseTypeConstraint DOMBatteryManagerChargingTimePropertyInfo = DOMBatteryManagerK type AttrGetType DOMBatteryManagerChargingTimePropertyInfo = Double type AttrLabel DOMBatteryManagerChargingTimePropertyInfo = "DOMBatteryManager::charging-time" attrGet _ = getDOMBatteryManagerChargingTime attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "discharging-time" -- Type: TBasicType TDouble -- Flags: [PropertyReadable] getDOMBatteryManagerDischargingTime :: (MonadIO m, DOMBatteryManagerK o) => o -> m Double getDOMBatteryManagerDischargingTime obj = liftIO $ getObjectPropertyDouble obj "discharging-time" data DOMBatteryManagerDischargingTimePropertyInfo instance AttrInfo DOMBatteryManagerDischargingTimePropertyInfo where type AttrAllowedOps DOMBatteryManagerDischargingTimePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMBatteryManagerDischargingTimePropertyInfo = (~) () type AttrBaseTypeConstraint DOMBatteryManagerDischargingTimePropertyInfo = DOMBatteryManagerK type AttrGetType DOMBatteryManagerDischargingTimePropertyInfo = Double type AttrLabel DOMBatteryManagerDischargingTimePropertyInfo = "DOMBatteryManager::discharging-time" attrGet _ = getDOMBatteryManagerDischargingTime attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "level" -- Type: TBasicType TDouble -- Flags: [PropertyReadable] getDOMBatteryManagerLevel :: (MonadIO m, DOMBatteryManagerK o) => o -> m Double getDOMBatteryManagerLevel obj = liftIO $ getObjectPropertyDouble obj "level" data DOMBatteryManagerLevelPropertyInfo instance AttrInfo DOMBatteryManagerLevelPropertyInfo where type AttrAllowedOps DOMBatteryManagerLevelPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMBatteryManagerLevelPropertyInfo = (~) () type AttrBaseTypeConstraint DOMBatteryManagerLevelPropertyInfo = DOMBatteryManagerK type AttrGetType DOMBatteryManagerLevelPropertyInfo = Double type AttrLabel DOMBatteryManagerLevelPropertyInfo = "DOMBatteryManager::level" attrGet _ = getDOMBatteryManagerLevel attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMBatteryManager = '[ '("charging", DOMBatteryManagerChargingPropertyInfo), '("charging-time", DOMBatteryManagerChargingTimePropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("discharging-time", DOMBatteryManagerDischargingTimePropertyInfo), '("level", DOMBatteryManagerLevelPropertyInfo)] -- VVV Prop "size" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMBlobSize :: (MonadIO m, DOMBlobK o) => o -> m Word64 getDOMBlobSize obj = liftIO $ getObjectPropertyUInt64 obj "size" data DOMBlobSizePropertyInfo instance AttrInfo DOMBlobSizePropertyInfo where type AttrAllowedOps DOMBlobSizePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMBlobSizePropertyInfo = (~) () type AttrBaseTypeConstraint DOMBlobSizePropertyInfo = DOMBlobK type AttrGetType DOMBlobSizePropertyInfo = Word64 type AttrLabel DOMBlobSizePropertyInfo = "DOMBlob::size" attrGet _ = getDOMBlobSize attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "type" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMBlobType :: (MonadIO m, DOMBlobK o) => o -> m T.Text getDOMBlobType obj = liftIO $ getObjectPropertyString obj "type" data DOMBlobTypePropertyInfo instance AttrInfo DOMBlobTypePropertyInfo where type AttrAllowedOps DOMBlobTypePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMBlobTypePropertyInfo = (~) () type AttrBaseTypeConstraint DOMBlobTypePropertyInfo = DOMBlobK type AttrGetType DOMBlobTypePropertyInfo = T.Text type AttrLabel DOMBlobTypePropertyInfo = "DOMBlob::type" attrGet _ = getDOMBlobType attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMBlob = '[ '("core-object", DOMObjectCoreObjectPropertyInfo), '("size", DOMBlobSizePropertyInfo), '("type", DOMBlobTypePropertyInfo)] type instance AttributeList DOMCDATASection = '[ '("base-uri", DOMNodeBaseUriPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("data", DOMCharacterDataDataPropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("length", DOMCharacterDataLengthPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("whole-text", DOMTextWholeTextPropertyInfo)] -- VVV Prop "css-text" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMCSSRuleCssText :: (MonadIO m, DOMCSSRuleK o) => o -> m T.Text getDOMCSSRuleCssText obj = liftIO $ getObjectPropertyString obj "css-text" setDOMCSSRuleCssText :: (MonadIO m, DOMCSSRuleK o) => o -> T.Text -> m () setDOMCSSRuleCssText obj val = liftIO $ setObjectPropertyString obj "css-text" val constructDOMCSSRuleCssText :: T.Text -> IO ([Char], GValue) constructDOMCSSRuleCssText val = constructObjectPropertyString "css-text" val data DOMCSSRuleCssTextPropertyInfo instance AttrInfo DOMCSSRuleCssTextPropertyInfo where type AttrAllowedOps DOMCSSRuleCssTextPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMCSSRuleCssTextPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMCSSRuleCssTextPropertyInfo = DOMCSSRuleK type AttrGetType DOMCSSRuleCssTextPropertyInfo = T.Text type AttrLabel DOMCSSRuleCssTextPropertyInfo = "DOMCSSRule::css-text" attrGet _ = getDOMCSSRuleCssText attrSet _ = setDOMCSSRuleCssText attrConstruct _ = constructDOMCSSRuleCssText -- VVV Prop "parent-rule" -- Type: TInterface "WebKit" "DOMCSSRule" -- Flags: [PropertyReadable] getDOMCSSRuleParentRule :: (MonadIO m, DOMCSSRuleK o) => o -> m DOMCSSRule getDOMCSSRuleParentRule obj = liftIO $ getObjectPropertyObject obj "parent-rule" DOMCSSRule data DOMCSSRuleParentRulePropertyInfo instance AttrInfo DOMCSSRuleParentRulePropertyInfo where type AttrAllowedOps DOMCSSRuleParentRulePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMCSSRuleParentRulePropertyInfo = (~) () type AttrBaseTypeConstraint DOMCSSRuleParentRulePropertyInfo = DOMCSSRuleK type AttrGetType DOMCSSRuleParentRulePropertyInfo = DOMCSSRule type AttrLabel DOMCSSRuleParentRulePropertyInfo = "DOMCSSRule::parent-rule" attrGet _ = getDOMCSSRuleParentRule attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "parent-style-sheet" -- Type: TInterface "WebKit" "DOMCSSStyleSheet" -- Flags: [PropertyReadable] getDOMCSSRuleParentStyleSheet :: (MonadIO m, DOMCSSRuleK o) => o -> m DOMCSSStyleSheet getDOMCSSRuleParentStyleSheet obj = liftIO $ getObjectPropertyObject obj "parent-style-sheet" DOMCSSStyleSheet data DOMCSSRuleParentStyleSheetPropertyInfo instance AttrInfo DOMCSSRuleParentStyleSheetPropertyInfo where type AttrAllowedOps DOMCSSRuleParentStyleSheetPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMCSSRuleParentStyleSheetPropertyInfo = (~) () type AttrBaseTypeConstraint DOMCSSRuleParentStyleSheetPropertyInfo = DOMCSSRuleK type AttrGetType DOMCSSRuleParentStyleSheetPropertyInfo = DOMCSSStyleSheet type AttrLabel DOMCSSRuleParentStyleSheetPropertyInfo = "DOMCSSRule::parent-style-sheet" attrGet _ = getDOMCSSRuleParentStyleSheet attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "type" -- Type: TBasicType TUInt32 -- Flags: [PropertyReadable] getDOMCSSRuleType :: (MonadIO m, DOMCSSRuleK o) => o -> m Word32 getDOMCSSRuleType obj = liftIO $ getObjectPropertyCUInt obj "type" data DOMCSSRuleTypePropertyInfo instance AttrInfo DOMCSSRuleTypePropertyInfo where type AttrAllowedOps DOMCSSRuleTypePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMCSSRuleTypePropertyInfo = (~) () type AttrBaseTypeConstraint DOMCSSRuleTypePropertyInfo = DOMCSSRuleK type AttrGetType DOMCSSRuleTypePropertyInfo = Word32 type AttrLabel DOMCSSRuleTypePropertyInfo = "DOMCSSRule::type" attrGet _ = getDOMCSSRuleType attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMCSSRule = '[ '("core-object", DOMObjectCoreObjectPropertyInfo), '("css-text", DOMCSSRuleCssTextPropertyInfo), '("parent-rule", DOMCSSRuleParentRulePropertyInfo), '("parent-style-sheet", DOMCSSRuleParentStyleSheetPropertyInfo), '("type", DOMCSSRuleTypePropertyInfo)] -- VVV Prop "length" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMCSSRuleListLength :: (MonadIO m, DOMCSSRuleListK o) => o -> m Word64 getDOMCSSRuleListLength obj = liftIO $ getObjectPropertyUInt64 obj "length" data DOMCSSRuleListLengthPropertyInfo instance AttrInfo DOMCSSRuleListLengthPropertyInfo where type AttrAllowedOps DOMCSSRuleListLengthPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMCSSRuleListLengthPropertyInfo = (~) () type AttrBaseTypeConstraint DOMCSSRuleListLengthPropertyInfo = DOMCSSRuleListK type AttrGetType DOMCSSRuleListLengthPropertyInfo = Word64 type AttrLabel DOMCSSRuleListLengthPropertyInfo = "DOMCSSRuleList::length" attrGet _ = getDOMCSSRuleListLength attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMCSSRuleList = '[ '("core-object", DOMObjectCoreObjectPropertyInfo), '("length", DOMCSSRuleListLengthPropertyInfo)] -- VVV Prop "css-text" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMCSSStyleDeclarationCssText :: (MonadIO m, DOMCSSStyleDeclarationK o) => o -> m T.Text getDOMCSSStyleDeclarationCssText obj = liftIO $ getObjectPropertyString obj "css-text" setDOMCSSStyleDeclarationCssText :: (MonadIO m, DOMCSSStyleDeclarationK o) => o -> T.Text -> m () setDOMCSSStyleDeclarationCssText obj val = liftIO $ setObjectPropertyString obj "css-text" val constructDOMCSSStyleDeclarationCssText :: T.Text -> IO ([Char], GValue) constructDOMCSSStyleDeclarationCssText val = constructObjectPropertyString "css-text" val data DOMCSSStyleDeclarationCssTextPropertyInfo instance AttrInfo DOMCSSStyleDeclarationCssTextPropertyInfo where type AttrAllowedOps DOMCSSStyleDeclarationCssTextPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMCSSStyleDeclarationCssTextPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMCSSStyleDeclarationCssTextPropertyInfo = DOMCSSStyleDeclarationK type AttrGetType DOMCSSStyleDeclarationCssTextPropertyInfo = T.Text type AttrLabel DOMCSSStyleDeclarationCssTextPropertyInfo = "DOMCSSStyleDeclaration::css-text" attrGet _ = getDOMCSSStyleDeclarationCssText attrSet _ = setDOMCSSStyleDeclarationCssText attrConstruct _ = constructDOMCSSStyleDeclarationCssText -- VVV Prop "length" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMCSSStyleDeclarationLength :: (MonadIO m, DOMCSSStyleDeclarationK o) => o -> m Word64 getDOMCSSStyleDeclarationLength obj = liftIO $ getObjectPropertyUInt64 obj "length" data DOMCSSStyleDeclarationLengthPropertyInfo instance AttrInfo DOMCSSStyleDeclarationLengthPropertyInfo where type AttrAllowedOps DOMCSSStyleDeclarationLengthPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMCSSStyleDeclarationLengthPropertyInfo = (~) () type AttrBaseTypeConstraint DOMCSSStyleDeclarationLengthPropertyInfo = DOMCSSStyleDeclarationK type AttrGetType DOMCSSStyleDeclarationLengthPropertyInfo = Word64 type AttrLabel DOMCSSStyleDeclarationLengthPropertyInfo = "DOMCSSStyleDeclaration::length" attrGet _ = getDOMCSSStyleDeclarationLength attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "parent-rule" -- Type: TInterface "WebKit" "DOMCSSRule" -- Flags: [PropertyReadable] getDOMCSSStyleDeclarationParentRule :: (MonadIO m, DOMCSSStyleDeclarationK o) => o -> m DOMCSSRule getDOMCSSStyleDeclarationParentRule obj = liftIO $ getObjectPropertyObject obj "parent-rule" DOMCSSRule data DOMCSSStyleDeclarationParentRulePropertyInfo instance AttrInfo DOMCSSStyleDeclarationParentRulePropertyInfo where type AttrAllowedOps DOMCSSStyleDeclarationParentRulePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMCSSStyleDeclarationParentRulePropertyInfo = (~) () type AttrBaseTypeConstraint DOMCSSStyleDeclarationParentRulePropertyInfo = DOMCSSStyleDeclarationK type AttrGetType DOMCSSStyleDeclarationParentRulePropertyInfo = DOMCSSRule type AttrLabel DOMCSSStyleDeclarationParentRulePropertyInfo = "DOMCSSStyleDeclaration::parent-rule" attrGet _ = getDOMCSSStyleDeclarationParentRule attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMCSSStyleDeclaration = '[ '("core-object", DOMObjectCoreObjectPropertyInfo), '("css-text", DOMCSSStyleDeclarationCssTextPropertyInfo), '("length", DOMCSSStyleDeclarationLengthPropertyInfo), '("parent-rule", DOMCSSStyleDeclarationParentRulePropertyInfo)] -- VVV Prop "css-rules" -- Type: TInterface "WebKit" "DOMCSSRuleList" -- Flags: [PropertyReadable] getDOMCSSStyleSheetCssRules :: (MonadIO m, DOMCSSStyleSheetK o) => o -> m DOMCSSRuleList getDOMCSSStyleSheetCssRules obj = liftIO $ getObjectPropertyObject obj "css-rules" DOMCSSRuleList data DOMCSSStyleSheetCssRulesPropertyInfo instance AttrInfo DOMCSSStyleSheetCssRulesPropertyInfo where type AttrAllowedOps DOMCSSStyleSheetCssRulesPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMCSSStyleSheetCssRulesPropertyInfo = (~) () type AttrBaseTypeConstraint DOMCSSStyleSheetCssRulesPropertyInfo = DOMCSSStyleSheetK type AttrGetType DOMCSSStyleSheetCssRulesPropertyInfo = DOMCSSRuleList type AttrLabel DOMCSSStyleSheetCssRulesPropertyInfo = "DOMCSSStyleSheet::css-rules" attrGet _ = getDOMCSSStyleSheetCssRules attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "owner-rule" -- Type: TInterface "WebKit" "DOMCSSRule" -- Flags: [PropertyReadable] getDOMCSSStyleSheetOwnerRule :: (MonadIO m, DOMCSSStyleSheetK o) => o -> m DOMCSSRule getDOMCSSStyleSheetOwnerRule obj = liftIO $ getObjectPropertyObject obj "owner-rule" DOMCSSRule data DOMCSSStyleSheetOwnerRulePropertyInfo instance AttrInfo DOMCSSStyleSheetOwnerRulePropertyInfo where type AttrAllowedOps DOMCSSStyleSheetOwnerRulePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMCSSStyleSheetOwnerRulePropertyInfo = (~) () type AttrBaseTypeConstraint DOMCSSStyleSheetOwnerRulePropertyInfo = DOMCSSStyleSheetK type AttrGetType DOMCSSStyleSheetOwnerRulePropertyInfo = DOMCSSRule type AttrLabel DOMCSSStyleSheetOwnerRulePropertyInfo = "DOMCSSStyleSheet::owner-rule" attrGet _ = getDOMCSSStyleSheetOwnerRule attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "rules" -- Type: TInterface "WebKit" "DOMCSSRuleList" -- Flags: [PropertyReadable] getDOMCSSStyleSheetRules :: (MonadIO m, DOMCSSStyleSheetK o) => o -> m DOMCSSRuleList getDOMCSSStyleSheetRules obj = liftIO $ getObjectPropertyObject obj "rules" DOMCSSRuleList data DOMCSSStyleSheetRulesPropertyInfo instance AttrInfo DOMCSSStyleSheetRulesPropertyInfo where type AttrAllowedOps DOMCSSStyleSheetRulesPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMCSSStyleSheetRulesPropertyInfo = (~) () type AttrBaseTypeConstraint DOMCSSStyleSheetRulesPropertyInfo = DOMCSSStyleSheetK type AttrGetType DOMCSSStyleSheetRulesPropertyInfo = DOMCSSRuleList type AttrLabel DOMCSSStyleSheetRulesPropertyInfo = "DOMCSSStyleSheet::rules" attrGet _ = getDOMCSSStyleSheetRules attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMCSSStyleSheet = '[ '("core-object", DOMObjectCoreObjectPropertyInfo), '("css-rules", DOMCSSStyleSheetCssRulesPropertyInfo), '("disabled", DOMStyleSheetDisabledPropertyInfo), '("href", DOMStyleSheetHrefPropertyInfo), '("media", DOMStyleSheetMediaPropertyInfo), '("owner-node", DOMStyleSheetOwnerNodePropertyInfo), '("owner-rule", DOMCSSStyleSheetOwnerRulePropertyInfo), '("parent-style-sheet", DOMStyleSheetParentStyleSheetPropertyInfo), '("rules", DOMCSSStyleSheetRulesPropertyInfo), '("title", DOMStyleSheetTitlePropertyInfo), '("type", DOMStyleSheetTypePropertyInfo)] -- VVV Prop "css-text" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMCSSValueCssText :: (MonadIO m, DOMCSSValueK o) => o -> m T.Text getDOMCSSValueCssText obj = liftIO $ getObjectPropertyString obj "css-text" setDOMCSSValueCssText :: (MonadIO m, DOMCSSValueK o) => o -> T.Text -> m () setDOMCSSValueCssText obj val = liftIO $ setObjectPropertyString obj "css-text" val constructDOMCSSValueCssText :: T.Text -> IO ([Char], GValue) constructDOMCSSValueCssText val = constructObjectPropertyString "css-text" val data DOMCSSValueCssTextPropertyInfo instance AttrInfo DOMCSSValueCssTextPropertyInfo where type AttrAllowedOps DOMCSSValueCssTextPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMCSSValueCssTextPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMCSSValueCssTextPropertyInfo = DOMCSSValueK type AttrGetType DOMCSSValueCssTextPropertyInfo = T.Text type AttrLabel DOMCSSValueCssTextPropertyInfo = "DOMCSSValue::css-text" attrGet _ = getDOMCSSValueCssText attrSet _ = setDOMCSSValueCssText attrConstruct _ = constructDOMCSSValueCssText -- VVV Prop "css-value-type" -- Type: TBasicType TUInt32 -- Flags: [PropertyReadable] getDOMCSSValueCssValueType :: (MonadIO m, DOMCSSValueK o) => o -> m Word32 getDOMCSSValueCssValueType obj = liftIO $ getObjectPropertyCUInt obj "css-value-type" data DOMCSSValueCssValueTypePropertyInfo instance AttrInfo DOMCSSValueCssValueTypePropertyInfo where type AttrAllowedOps DOMCSSValueCssValueTypePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMCSSValueCssValueTypePropertyInfo = (~) () type AttrBaseTypeConstraint DOMCSSValueCssValueTypePropertyInfo = DOMCSSValueK type AttrGetType DOMCSSValueCssValueTypePropertyInfo = Word32 type AttrLabel DOMCSSValueCssValueTypePropertyInfo = "DOMCSSValue::css-value-type" attrGet _ = getDOMCSSValueCssValueType attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMCSSValue = '[ '("core-object", DOMObjectCoreObjectPropertyInfo), '("css-text", DOMCSSValueCssTextPropertyInfo), '("css-value-type", DOMCSSValueCssValueTypePropertyInfo)] -- VVV Prop "data" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMCharacterDataData :: (MonadIO m, DOMCharacterDataK o) => o -> m T.Text getDOMCharacterDataData obj = liftIO $ getObjectPropertyString obj "data" setDOMCharacterDataData :: (MonadIO m, DOMCharacterDataK o) => o -> T.Text -> m () setDOMCharacterDataData obj val = liftIO $ setObjectPropertyString obj "data" val constructDOMCharacterDataData :: T.Text -> IO ([Char], GValue) constructDOMCharacterDataData val = constructObjectPropertyString "data" val data DOMCharacterDataDataPropertyInfo instance AttrInfo DOMCharacterDataDataPropertyInfo where type AttrAllowedOps DOMCharacterDataDataPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMCharacterDataDataPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMCharacterDataDataPropertyInfo = DOMCharacterDataK type AttrGetType DOMCharacterDataDataPropertyInfo = T.Text type AttrLabel DOMCharacterDataDataPropertyInfo = "DOMCharacterData::data" attrGet _ = getDOMCharacterDataData attrSet _ = setDOMCharacterDataData attrConstruct _ = constructDOMCharacterDataData -- VVV Prop "length" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMCharacterDataLength :: (MonadIO m, DOMCharacterDataK o) => o -> m Word64 getDOMCharacterDataLength obj = liftIO $ getObjectPropertyUInt64 obj "length" data DOMCharacterDataLengthPropertyInfo instance AttrInfo DOMCharacterDataLengthPropertyInfo where type AttrAllowedOps DOMCharacterDataLengthPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMCharacterDataLengthPropertyInfo = (~) () type AttrBaseTypeConstraint DOMCharacterDataLengthPropertyInfo = DOMCharacterDataK type AttrGetType DOMCharacterDataLengthPropertyInfo = Word64 type AttrLabel DOMCharacterDataLengthPropertyInfo = "DOMCharacterData::length" attrGet _ = getDOMCharacterDataLength attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMCharacterData = '[ '("base-uri", DOMNodeBaseUriPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("data", DOMCharacterDataDataPropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("length", DOMCharacterDataLengthPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo)] type instance AttributeList DOMComment = '[ '("base-uri", DOMNodeBaseUriPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("data", DOMCharacterDataDataPropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("length", DOMCharacterDataLengthPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo)] type instance AttributeList DOMConsole = '[ '("core-object", DOMObjectCoreObjectPropertyInfo)] -- VVV Prop "status" -- Type: TBasicType TUInt32 -- Flags: [PropertyReadable] getDOMDOMApplicationCacheStatus :: (MonadIO m, DOMDOMApplicationCacheK o) => o -> m Word32 getDOMDOMApplicationCacheStatus obj = liftIO $ getObjectPropertyCUInt obj "status" data DOMDOMApplicationCacheStatusPropertyInfo instance AttrInfo DOMDOMApplicationCacheStatusPropertyInfo where type AttrAllowedOps DOMDOMApplicationCacheStatusPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMApplicationCacheStatusPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMApplicationCacheStatusPropertyInfo = DOMDOMApplicationCacheK type AttrGetType DOMDOMApplicationCacheStatusPropertyInfo = Word32 type AttrLabel DOMDOMApplicationCacheStatusPropertyInfo = "DOMDOMApplicationCache::status" attrGet _ = getDOMDOMApplicationCacheStatus attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMDOMApplicationCache = '[ '("core-object", DOMObjectCoreObjectPropertyInfo), '("status", DOMDOMApplicationCacheStatusPropertyInfo)] type instance AttributeList DOMDOMImplementation = '[ '("core-object", DOMObjectCoreObjectPropertyInfo)] -- VVV Prop "description" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMDOMMimeTypeDescription :: (MonadIO m, DOMDOMMimeTypeK o) => o -> m T.Text getDOMDOMMimeTypeDescription obj = liftIO $ getObjectPropertyString obj "description" data DOMDOMMimeTypeDescriptionPropertyInfo instance AttrInfo DOMDOMMimeTypeDescriptionPropertyInfo where type AttrAllowedOps DOMDOMMimeTypeDescriptionPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMMimeTypeDescriptionPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMMimeTypeDescriptionPropertyInfo = DOMDOMMimeTypeK type AttrGetType DOMDOMMimeTypeDescriptionPropertyInfo = T.Text type AttrLabel DOMDOMMimeTypeDescriptionPropertyInfo = "DOMDOMMimeType::description" attrGet _ = getDOMDOMMimeTypeDescription attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "enabled-plugin" -- Type: TInterface "WebKit" "DOMDOMPlugin" -- Flags: [PropertyReadable] getDOMDOMMimeTypeEnabledPlugin :: (MonadIO m, DOMDOMMimeTypeK o) => o -> m DOMDOMPlugin getDOMDOMMimeTypeEnabledPlugin obj = liftIO $ getObjectPropertyObject obj "enabled-plugin" DOMDOMPlugin data DOMDOMMimeTypeEnabledPluginPropertyInfo instance AttrInfo DOMDOMMimeTypeEnabledPluginPropertyInfo where type AttrAllowedOps DOMDOMMimeTypeEnabledPluginPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMMimeTypeEnabledPluginPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMMimeTypeEnabledPluginPropertyInfo = DOMDOMMimeTypeK type AttrGetType DOMDOMMimeTypeEnabledPluginPropertyInfo = DOMDOMPlugin type AttrLabel DOMDOMMimeTypeEnabledPluginPropertyInfo = "DOMDOMMimeType::enabled-plugin" attrGet _ = getDOMDOMMimeTypeEnabledPlugin attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "suffixes" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMDOMMimeTypeSuffixes :: (MonadIO m, DOMDOMMimeTypeK o) => o -> m T.Text getDOMDOMMimeTypeSuffixes obj = liftIO $ getObjectPropertyString obj "suffixes" data DOMDOMMimeTypeSuffixesPropertyInfo instance AttrInfo DOMDOMMimeTypeSuffixesPropertyInfo where type AttrAllowedOps DOMDOMMimeTypeSuffixesPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMMimeTypeSuffixesPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMMimeTypeSuffixesPropertyInfo = DOMDOMMimeTypeK type AttrGetType DOMDOMMimeTypeSuffixesPropertyInfo = T.Text type AttrLabel DOMDOMMimeTypeSuffixesPropertyInfo = "DOMDOMMimeType::suffixes" attrGet _ = getDOMDOMMimeTypeSuffixes attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "type" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMDOMMimeTypeType :: (MonadIO m, DOMDOMMimeTypeK o) => o -> m T.Text getDOMDOMMimeTypeType obj = liftIO $ getObjectPropertyString obj "type" data DOMDOMMimeTypeTypePropertyInfo instance AttrInfo DOMDOMMimeTypeTypePropertyInfo where type AttrAllowedOps DOMDOMMimeTypeTypePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMMimeTypeTypePropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMMimeTypeTypePropertyInfo = DOMDOMMimeTypeK type AttrGetType DOMDOMMimeTypeTypePropertyInfo = T.Text type AttrLabel DOMDOMMimeTypeTypePropertyInfo = "DOMDOMMimeType::type" attrGet _ = getDOMDOMMimeTypeType attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMDOMMimeType = '[ '("core-object", DOMObjectCoreObjectPropertyInfo), '("description", DOMDOMMimeTypeDescriptionPropertyInfo), '("enabled-plugin", DOMDOMMimeTypeEnabledPluginPropertyInfo), '("suffixes", DOMDOMMimeTypeSuffixesPropertyInfo), '("type", DOMDOMMimeTypeTypePropertyInfo)] -- VVV Prop "length" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMDOMMimeTypeArrayLength :: (MonadIO m, DOMDOMMimeTypeArrayK o) => o -> m Word64 getDOMDOMMimeTypeArrayLength obj = liftIO $ getObjectPropertyUInt64 obj "length" data DOMDOMMimeTypeArrayLengthPropertyInfo instance AttrInfo DOMDOMMimeTypeArrayLengthPropertyInfo where type AttrAllowedOps DOMDOMMimeTypeArrayLengthPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMMimeTypeArrayLengthPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMMimeTypeArrayLengthPropertyInfo = DOMDOMMimeTypeArrayK type AttrGetType DOMDOMMimeTypeArrayLengthPropertyInfo = Word64 type AttrLabel DOMDOMMimeTypeArrayLengthPropertyInfo = "DOMDOMMimeTypeArray::length" attrGet _ = getDOMDOMMimeTypeArrayLength attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMDOMMimeTypeArray = '[ '("core-object", DOMObjectCoreObjectPropertyInfo), '("length", DOMDOMMimeTypeArrayLengthPropertyInfo)] -- VVV Prop "length" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMDOMNamedFlowCollectionLength :: (MonadIO m, DOMDOMNamedFlowCollectionK o) => o -> m Word64 getDOMDOMNamedFlowCollectionLength obj = liftIO $ getObjectPropertyUInt64 obj "length" data DOMDOMNamedFlowCollectionLengthPropertyInfo instance AttrInfo DOMDOMNamedFlowCollectionLengthPropertyInfo where type AttrAllowedOps DOMDOMNamedFlowCollectionLengthPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMNamedFlowCollectionLengthPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMNamedFlowCollectionLengthPropertyInfo = DOMDOMNamedFlowCollectionK type AttrGetType DOMDOMNamedFlowCollectionLengthPropertyInfo = Word64 type AttrLabel DOMDOMNamedFlowCollectionLengthPropertyInfo = "DOMDOMNamedFlowCollection::length" attrGet _ = getDOMDOMNamedFlowCollectionLength attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMDOMNamedFlowCollection = '[ '("core-object", DOMObjectCoreObjectPropertyInfo), '("length", DOMDOMNamedFlowCollectionLengthPropertyInfo)] -- VVV Prop "description" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMDOMPluginDescription :: (MonadIO m, DOMDOMPluginK o) => o -> m T.Text getDOMDOMPluginDescription obj = liftIO $ getObjectPropertyString obj "description" data DOMDOMPluginDescriptionPropertyInfo instance AttrInfo DOMDOMPluginDescriptionPropertyInfo where type AttrAllowedOps DOMDOMPluginDescriptionPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMPluginDescriptionPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMPluginDescriptionPropertyInfo = DOMDOMPluginK type AttrGetType DOMDOMPluginDescriptionPropertyInfo = T.Text type AttrLabel DOMDOMPluginDescriptionPropertyInfo = "DOMDOMPlugin::description" attrGet _ = getDOMDOMPluginDescription attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "filename" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMDOMPluginFilename :: (MonadIO m, DOMDOMPluginK o) => o -> m T.Text getDOMDOMPluginFilename obj = liftIO $ getObjectPropertyString obj "filename" data DOMDOMPluginFilenamePropertyInfo instance AttrInfo DOMDOMPluginFilenamePropertyInfo where type AttrAllowedOps DOMDOMPluginFilenamePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMPluginFilenamePropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMPluginFilenamePropertyInfo = DOMDOMPluginK type AttrGetType DOMDOMPluginFilenamePropertyInfo = T.Text type AttrLabel DOMDOMPluginFilenamePropertyInfo = "DOMDOMPlugin::filename" attrGet _ = getDOMDOMPluginFilename attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "length" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMDOMPluginLength :: (MonadIO m, DOMDOMPluginK o) => o -> m Word64 getDOMDOMPluginLength obj = liftIO $ getObjectPropertyUInt64 obj "length" data DOMDOMPluginLengthPropertyInfo instance AttrInfo DOMDOMPluginLengthPropertyInfo where type AttrAllowedOps DOMDOMPluginLengthPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMPluginLengthPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMPluginLengthPropertyInfo = DOMDOMPluginK type AttrGetType DOMDOMPluginLengthPropertyInfo = Word64 type AttrLabel DOMDOMPluginLengthPropertyInfo = "DOMDOMPlugin::length" attrGet _ = getDOMDOMPluginLength attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "name" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMDOMPluginName :: (MonadIO m, DOMDOMPluginK o) => o -> m T.Text getDOMDOMPluginName obj = liftIO $ getObjectPropertyString obj "name" data DOMDOMPluginNamePropertyInfo instance AttrInfo DOMDOMPluginNamePropertyInfo where type AttrAllowedOps DOMDOMPluginNamePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMPluginNamePropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMPluginNamePropertyInfo = DOMDOMPluginK type AttrGetType DOMDOMPluginNamePropertyInfo = T.Text type AttrLabel DOMDOMPluginNamePropertyInfo = "DOMDOMPlugin::name" attrGet _ = getDOMDOMPluginName attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMDOMPlugin = '[ '("core-object", DOMObjectCoreObjectPropertyInfo), '("description", DOMDOMPluginDescriptionPropertyInfo), '("filename", DOMDOMPluginFilenamePropertyInfo), '("length", DOMDOMPluginLengthPropertyInfo), '("name", DOMDOMPluginNamePropertyInfo)] -- VVV Prop "length" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMDOMPluginArrayLength :: (MonadIO m, DOMDOMPluginArrayK o) => o -> m Word64 getDOMDOMPluginArrayLength obj = liftIO $ getObjectPropertyUInt64 obj "length" data DOMDOMPluginArrayLengthPropertyInfo instance AttrInfo DOMDOMPluginArrayLengthPropertyInfo where type AttrAllowedOps DOMDOMPluginArrayLengthPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMPluginArrayLengthPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMPluginArrayLengthPropertyInfo = DOMDOMPluginArrayK type AttrGetType DOMDOMPluginArrayLengthPropertyInfo = Word64 type AttrLabel DOMDOMPluginArrayLengthPropertyInfo = "DOMDOMPluginArray::length" attrGet _ = getDOMDOMPluginArrayLength attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMDOMPluginArray = '[ '("core-object", DOMObjectCoreObjectPropertyInfo), '("length", DOMDOMPluginArrayLengthPropertyInfo)] -- VVV Prop "allows-eval" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMDOMSecurityPolicyAllowsEval :: (MonadIO m, DOMDOMSecurityPolicyK o) => o -> m Bool getDOMDOMSecurityPolicyAllowsEval obj = liftIO $ getObjectPropertyBool obj "allows-eval" data DOMDOMSecurityPolicyAllowsEvalPropertyInfo instance AttrInfo DOMDOMSecurityPolicyAllowsEvalPropertyInfo where type AttrAllowedOps DOMDOMSecurityPolicyAllowsEvalPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMSecurityPolicyAllowsEvalPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMSecurityPolicyAllowsEvalPropertyInfo = DOMDOMSecurityPolicyK type AttrGetType DOMDOMSecurityPolicyAllowsEvalPropertyInfo = Bool type AttrLabel DOMDOMSecurityPolicyAllowsEvalPropertyInfo = "DOMDOMSecurityPolicy::allows-eval" attrGet _ = getDOMDOMSecurityPolicyAllowsEval attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "allows-inline-script" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMDOMSecurityPolicyAllowsInlineScript :: (MonadIO m, DOMDOMSecurityPolicyK o) => o -> m Bool getDOMDOMSecurityPolicyAllowsInlineScript obj = liftIO $ getObjectPropertyBool obj "allows-inline-script" data DOMDOMSecurityPolicyAllowsInlineScriptPropertyInfo instance AttrInfo DOMDOMSecurityPolicyAllowsInlineScriptPropertyInfo where type AttrAllowedOps DOMDOMSecurityPolicyAllowsInlineScriptPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMSecurityPolicyAllowsInlineScriptPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMSecurityPolicyAllowsInlineScriptPropertyInfo = DOMDOMSecurityPolicyK type AttrGetType DOMDOMSecurityPolicyAllowsInlineScriptPropertyInfo = Bool type AttrLabel DOMDOMSecurityPolicyAllowsInlineScriptPropertyInfo = "DOMDOMSecurityPolicy::allows-inline-script" attrGet _ = getDOMDOMSecurityPolicyAllowsInlineScript attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "allows-inline-style" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMDOMSecurityPolicyAllowsInlineStyle :: (MonadIO m, DOMDOMSecurityPolicyK o) => o -> m Bool getDOMDOMSecurityPolicyAllowsInlineStyle obj = liftIO $ getObjectPropertyBool obj "allows-inline-style" data DOMDOMSecurityPolicyAllowsInlineStylePropertyInfo instance AttrInfo DOMDOMSecurityPolicyAllowsInlineStylePropertyInfo where type AttrAllowedOps DOMDOMSecurityPolicyAllowsInlineStylePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMSecurityPolicyAllowsInlineStylePropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMSecurityPolicyAllowsInlineStylePropertyInfo = DOMDOMSecurityPolicyK type AttrGetType DOMDOMSecurityPolicyAllowsInlineStylePropertyInfo = Bool type AttrLabel DOMDOMSecurityPolicyAllowsInlineStylePropertyInfo = "DOMDOMSecurityPolicy::allows-inline-style" attrGet _ = getDOMDOMSecurityPolicyAllowsInlineStyle attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "is-active" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMDOMSecurityPolicyIsActive :: (MonadIO m, DOMDOMSecurityPolicyK o) => o -> m Bool getDOMDOMSecurityPolicyIsActive obj = liftIO $ getObjectPropertyBool obj "is-active" data DOMDOMSecurityPolicyIsActivePropertyInfo instance AttrInfo DOMDOMSecurityPolicyIsActivePropertyInfo where type AttrAllowedOps DOMDOMSecurityPolicyIsActivePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMSecurityPolicyIsActivePropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMSecurityPolicyIsActivePropertyInfo = DOMDOMSecurityPolicyK type AttrGetType DOMDOMSecurityPolicyIsActivePropertyInfo = Bool type AttrLabel DOMDOMSecurityPolicyIsActivePropertyInfo = "DOMDOMSecurityPolicy::is-active" attrGet _ = getDOMDOMSecurityPolicyIsActive attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "report-ur-is" -- Type: TInterface "WebKit" "DOMDOMStringList" -- Flags: [PropertyReadable] getDOMDOMSecurityPolicyReportUrIs :: (MonadIO m, DOMDOMSecurityPolicyK o) => o -> m DOMDOMStringList getDOMDOMSecurityPolicyReportUrIs obj = liftIO $ getObjectPropertyObject obj "report-ur-is" DOMDOMStringList data DOMDOMSecurityPolicyReportUrIsPropertyInfo instance AttrInfo DOMDOMSecurityPolicyReportUrIsPropertyInfo where type AttrAllowedOps DOMDOMSecurityPolicyReportUrIsPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMSecurityPolicyReportUrIsPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMSecurityPolicyReportUrIsPropertyInfo = DOMDOMSecurityPolicyK type AttrGetType DOMDOMSecurityPolicyReportUrIsPropertyInfo = DOMDOMStringList type AttrLabel DOMDOMSecurityPolicyReportUrIsPropertyInfo = "DOMDOMSecurityPolicy::report-ur-is" attrGet _ = getDOMDOMSecurityPolicyReportUrIs attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMDOMSecurityPolicy = '[ '("allows-eval", DOMDOMSecurityPolicyAllowsEvalPropertyInfo), '("allows-inline-script", DOMDOMSecurityPolicyAllowsInlineScriptPropertyInfo), '("allows-inline-style", DOMDOMSecurityPolicyAllowsInlineStylePropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("is-active", DOMDOMSecurityPolicyIsActivePropertyInfo), '("report-ur-is", DOMDOMSecurityPolicyReportUrIsPropertyInfo)] -- VVV Prop "anchor-node" -- Type: TInterface "WebKit" "DOMNode" -- Flags: [PropertyReadable] getDOMDOMSelectionAnchorNode :: (MonadIO m, DOMDOMSelectionK o) => o -> m DOMNode getDOMDOMSelectionAnchorNode obj = liftIO $ getObjectPropertyObject obj "anchor-node" DOMNode data DOMDOMSelectionAnchorNodePropertyInfo instance AttrInfo DOMDOMSelectionAnchorNodePropertyInfo where type AttrAllowedOps DOMDOMSelectionAnchorNodePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMSelectionAnchorNodePropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMSelectionAnchorNodePropertyInfo = DOMDOMSelectionK type AttrGetType DOMDOMSelectionAnchorNodePropertyInfo = DOMNode type AttrLabel DOMDOMSelectionAnchorNodePropertyInfo = "DOMDOMSelection::anchor-node" attrGet _ = getDOMDOMSelectionAnchorNode attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "anchor-offset" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMDOMSelectionAnchorOffset :: (MonadIO m, DOMDOMSelectionK o) => o -> m Int64 getDOMDOMSelectionAnchorOffset obj = liftIO $ getObjectPropertyInt64 obj "anchor-offset" data DOMDOMSelectionAnchorOffsetPropertyInfo instance AttrInfo DOMDOMSelectionAnchorOffsetPropertyInfo where type AttrAllowedOps DOMDOMSelectionAnchorOffsetPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMSelectionAnchorOffsetPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMSelectionAnchorOffsetPropertyInfo = DOMDOMSelectionK type AttrGetType DOMDOMSelectionAnchorOffsetPropertyInfo = Int64 type AttrLabel DOMDOMSelectionAnchorOffsetPropertyInfo = "DOMDOMSelection::anchor-offset" attrGet _ = getDOMDOMSelectionAnchorOffset attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "base-node" -- Type: TInterface "WebKit" "DOMNode" -- Flags: [PropertyReadable] getDOMDOMSelectionBaseNode :: (MonadIO m, DOMDOMSelectionK o) => o -> m DOMNode getDOMDOMSelectionBaseNode obj = liftIO $ getObjectPropertyObject obj "base-node" DOMNode data DOMDOMSelectionBaseNodePropertyInfo instance AttrInfo DOMDOMSelectionBaseNodePropertyInfo where type AttrAllowedOps DOMDOMSelectionBaseNodePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMSelectionBaseNodePropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMSelectionBaseNodePropertyInfo = DOMDOMSelectionK type AttrGetType DOMDOMSelectionBaseNodePropertyInfo = DOMNode type AttrLabel DOMDOMSelectionBaseNodePropertyInfo = "DOMDOMSelection::base-node" attrGet _ = getDOMDOMSelectionBaseNode attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "base-offset" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMDOMSelectionBaseOffset :: (MonadIO m, DOMDOMSelectionK o) => o -> m Int64 getDOMDOMSelectionBaseOffset obj = liftIO $ getObjectPropertyInt64 obj "base-offset" data DOMDOMSelectionBaseOffsetPropertyInfo instance AttrInfo DOMDOMSelectionBaseOffsetPropertyInfo where type AttrAllowedOps DOMDOMSelectionBaseOffsetPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMSelectionBaseOffsetPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMSelectionBaseOffsetPropertyInfo = DOMDOMSelectionK type AttrGetType DOMDOMSelectionBaseOffsetPropertyInfo = Int64 type AttrLabel DOMDOMSelectionBaseOffsetPropertyInfo = "DOMDOMSelection::base-offset" attrGet _ = getDOMDOMSelectionBaseOffset attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "extent-node" -- Type: TInterface "WebKit" "DOMNode" -- Flags: [PropertyReadable] getDOMDOMSelectionExtentNode :: (MonadIO m, DOMDOMSelectionK o) => o -> m DOMNode getDOMDOMSelectionExtentNode obj = liftIO $ getObjectPropertyObject obj "extent-node" DOMNode data DOMDOMSelectionExtentNodePropertyInfo instance AttrInfo DOMDOMSelectionExtentNodePropertyInfo where type AttrAllowedOps DOMDOMSelectionExtentNodePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMSelectionExtentNodePropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMSelectionExtentNodePropertyInfo = DOMDOMSelectionK type AttrGetType DOMDOMSelectionExtentNodePropertyInfo = DOMNode type AttrLabel DOMDOMSelectionExtentNodePropertyInfo = "DOMDOMSelection::extent-node" attrGet _ = getDOMDOMSelectionExtentNode attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "extent-offset" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMDOMSelectionExtentOffset :: (MonadIO m, DOMDOMSelectionK o) => o -> m Int64 getDOMDOMSelectionExtentOffset obj = liftIO $ getObjectPropertyInt64 obj "extent-offset" data DOMDOMSelectionExtentOffsetPropertyInfo instance AttrInfo DOMDOMSelectionExtentOffsetPropertyInfo where type AttrAllowedOps DOMDOMSelectionExtentOffsetPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMSelectionExtentOffsetPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMSelectionExtentOffsetPropertyInfo = DOMDOMSelectionK type AttrGetType DOMDOMSelectionExtentOffsetPropertyInfo = Int64 type AttrLabel DOMDOMSelectionExtentOffsetPropertyInfo = "DOMDOMSelection::extent-offset" attrGet _ = getDOMDOMSelectionExtentOffset attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "focus-node" -- Type: TInterface "WebKit" "DOMNode" -- Flags: [PropertyReadable] getDOMDOMSelectionFocusNode :: (MonadIO m, DOMDOMSelectionK o) => o -> m DOMNode getDOMDOMSelectionFocusNode obj = liftIO $ getObjectPropertyObject obj "focus-node" DOMNode data DOMDOMSelectionFocusNodePropertyInfo instance AttrInfo DOMDOMSelectionFocusNodePropertyInfo where type AttrAllowedOps DOMDOMSelectionFocusNodePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMSelectionFocusNodePropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMSelectionFocusNodePropertyInfo = DOMDOMSelectionK type AttrGetType DOMDOMSelectionFocusNodePropertyInfo = DOMNode type AttrLabel DOMDOMSelectionFocusNodePropertyInfo = "DOMDOMSelection::focus-node" attrGet _ = getDOMDOMSelectionFocusNode attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "focus-offset" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMDOMSelectionFocusOffset :: (MonadIO m, DOMDOMSelectionK o) => o -> m Int64 getDOMDOMSelectionFocusOffset obj = liftIO $ getObjectPropertyInt64 obj "focus-offset" data DOMDOMSelectionFocusOffsetPropertyInfo instance AttrInfo DOMDOMSelectionFocusOffsetPropertyInfo where type AttrAllowedOps DOMDOMSelectionFocusOffsetPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMSelectionFocusOffsetPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMSelectionFocusOffsetPropertyInfo = DOMDOMSelectionK type AttrGetType DOMDOMSelectionFocusOffsetPropertyInfo = Int64 type AttrLabel DOMDOMSelectionFocusOffsetPropertyInfo = "DOMDOMSelection::focus-offset" attrGet _ = getDOMDOMSelectionFocusOffset attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "is-collapsed" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMDOMSelectionIsCollapsed :: (MonadIO m, DOMDOMSelectionK o) => o -> m Bool getDOMDOMSelectionIsCollapsed obj = liftIO $ getObjectPropertyBool obj "is-collapsed" data DOMDOMSelectionIsCollapsedPropertyInfo instance AttrInfo DOMDOMSelectionIsCollapsedPropertyInfo where type AttrAllowedOps DOMDOMSelectionIsCollapsedPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMSelectionIsCollapsedPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMSelectionIsCollapsedPropertyInfo = DOMDOMSelectionK type AttrGetType DOMDOMSelectionIsCollapsedPropertyInfo = Bool type AttrLabel DOMDOMSelectionIsCollapsedPropertyInfo = "DOMDOMSelection::is-collapsed" attrGet _ = getDOMDOMSelectionIsCollapsed attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "range-count" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMDOMSelectionRangeCount :: (MonadIO m, DOMDOMSelectionK o) => o -> m Int64 getDOMDOMSelectionRangeCount obj = liftIO $ getObjectPropertyInt64 obj "range-count" data DOMDOMSelectionRangeCountPropertyInfo instance AttrInfo DOMDOMSelectionRangeCountPropertyInfo where type AttrAllowedOps DOMDOMSelectionRangeCountPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMSelectionRangeCountPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMSelectionRangeCountPropertyInfo = DOMDOMSelectionK type AttrGetType DOMDOMSelectionRangeCountPropertyInfo = Int64 type AttrLabel DOMDOMSelectionRangeCountPropertyInfo = "DOMDOMSelection::range-count" attrGet _ = getDOMDOMSelectionRangeCount attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "type" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMDOMSelectionType :: (MonadIO m, DOMDOMSelectionK o) => o -> m T.Text getDOMDOMSelectionType obj = liftIO $ getObjectPropertyString obj "type" data DOMDOMSelectionTypePropertyInfo instance AttrInfo DOMDOMSelectionTypePropertyInfo where type AttrAllowedOps DOMDOMSelectionTypePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMSelectionTypePropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMSelectionTypePropertyInfo = DOMDOMSelectionK type AttrGetType DOMDOMSelectionTypePropertyInfo = T.Text type AttrLabel DOMDOMSelectionTypePropertyInfo = "DOMDOMSelection::type" attrGet _ = getDOMDOMSelectionType attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMDOMSelection = '[ '("anchor-node", DOMDOMSelectionAnchorNodePropertyInfo), '("anchor-offset", DOMDOMSelectionAnchorOffsetPropertyInfo), '("base-node", DOMDOMSelectionBaseNodePropertyInfo), '("base-offset", DOMDOMSelectionBaseOffsetPropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("extent-node", DOMDOMSelectionExtentNodePropertyInfo), '("extent-offset", DOMDOMSelectionExtentOffsetPropertyInfo), '("focus-node", DOMDOMSelectionFocusNodePropertyInfo), '("focus-offset", DOMDOMSelectionFocusOffsetPropertyInfo), '("is-collapsed", DOMDOMSelectionIsCollapsedPropertyInfo), '("range-count", DOMDOMSelectionRangeCountPropertyInfo), '("type", DOMDOMSelectionTypePropertyInfo)] -- VVV Prop "value" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMDOMSettableTokenListValue :: (MonadIO m, DOMDOMSettableTokenListK o) => o -> m T.Text getDOMDOMSettableTokenListValue obj = liftIO $ getObjectPropertyString obj "value" setDOMDOMSettableTokenListValue :: (MonadIO m, DOMDOMSettableTokenListK o) => o -> T.Text -> m () setDOMDOMSettableTokenListValue obj val = liftIO $ setObjectPropertyString obj "value" val constructDOMDOMSettableTokenListValue :: T.Text -> IO ([Char], GValue) constructDOMDOMSettableTokenListValue val = constructObjectPropertyString "value" val data DOMDOMSettableTokenListValuePropertyInfo instance AttrInfo DOMDOMSettableTokenListValuePropertyInfo where type AttrAllowedOps DOMDOMSettableTokenListValuePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMDOMSettableTokenListValuePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMDOMSettableTokenListValuePropertyInfo = DOMDOMSettableTokenListK type AttrGetType DOMDOMSettableTokenListValuePropertyInfo = T.Text type AttrLabel DOMDOMSettableTokenListValuePropertyInfo = "DOMDOMSettableTokenList::value" attrGet _ = getDOMDOMSettableTokenListValue attrSet _ = setDOMDOMSettableTokenListValue attrConstruct _ = constructDOMDOMSettableTokenListValue type instance AttributeList DOMDOMSettableTokenList = '[ '("core-object", DOMObjectCoreObjectPropertyInfo), '("length", DOMDOMTokenListLengthPropertyInfo), '("value", DOMDOMSettableTokenListValuePropertyInfo)] -- VVV Prop "length" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMDOMStringListLength :: (MonadIO m, DOMDOMStringListK o) => o -> m Word64 getDOMDOMStringListLength obj = liftIO $ getObjectPropertyUInt64 obj "length" data DOMDOMStringListLengthPropertyInfo instance AttrInfo DOMDOMStringListLengthPropertyInfo where type AttrAllowedOps DOMDOMStringListLengthPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMStringListLengthPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMStringListLengthPropertyInfo = DOMDOMStringListK type AttrGetType DOMDOMStringListLengthPropertyInfo = Word64 type AttrLabel DOMDOMStringListLengthPropertyInfo = "DOMDOMStringList::length" attrGet _ = getDOMDOMStringListLength attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMDOMStringList = '[ '("core-object", DOMObjectCoreObjectPropertyInfo), '("length", DOMDOMStringListLengthPropertyInfo)] type instance AttributeList DOMDOMStringMap = '[ '("core-object", DOMObjectCoreObjectPropertyInfo)] -- VVV Prop "length" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMDOMTokenListLength :: (MonadIO m, DOMDOMTokenListK o) => o -> m Word64 getDOMDOMTokenListLength obj = liftIO $ getObjectPropertyUInt64 obj "length" data DOMDOMTokenListLengthPropertyInfo instance AttrInfo DOMDOMTokenListLengthPropertyInfo where type AttrAllowedOps DOMDOMTokenListLengthPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMTokenListLengthPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMTokenListLengthPropertyInfo = DOMDOMTokenListK type AttrGetType DOMDOMTokenListLengthPropertyInfo = Word64 type AttrLabel DOMDOMTokenListLengthPropertyInfo = "DOMDOMTokenList::length" attrGet _ = getDOMDOMTokenListLength attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMDOMTokenList = '[ '("core-object", DOMObjectCoreObjectPropertyInfo), '("length", DOMDOMTokenListLengthPropertyInfo)] -- VVV Prop "application-cache" -- Type: TInterface "WebKit" "DOMDOMApplicationCache" -- Flags: [PropertyReadable] getDOMDOMWindowApplicationCache :: (MonadIO m, DOMDOMWindowK o) => o -> m DOMDOMApplicationCache getDOMDOMWindowApplicationCache obj = liftIO $ getObjectPropertyObject obj "application-cache" DOMDOMApplicationCache data DOMDOMWindowApplicationCachePropertyInfo instance AttrInfo DOMDOMWindowApplicationCachePropertyInfo where type AttrAllowedOps DOMDOMWindowApplicationCachePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMWindowApplicationCachePropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMWindowApplicationCachePropertyInfo = DOMDOMWindowK type AttrGetType DOMDOMWindowApplicationCachePropertyInfo = DOMDOMApplicationCache type AttrLabel DOMDOMWindowApplicationCachePropertyInfo = "DOMDOMWindow::application-cache" attrGet _ = getDOMDOMWindowApplicationCache attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "client-information" -- Type: TInterface "WebKit" "DOMNavigator" -- Flags: [PropertyReadable] getDOMDOMWindowClientInformation :: (MonadIO m, DOMDOMWindowK o) => o -> m DOMNavigator getDOMDOMWindowClientInformation obj = liftIO $ getObjectPropertyObject obj "client-information" DOMNavigator data DOMDOMWindowClientInformationPropertyInfo instance AttrInfo DOMDOMWindowClientInformationPropertyInfo where type AttrAllowedOps DOMDOMWindowClientInformationPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMWindowClientInformationPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMWindowClientInformationPropertyInfo = DOMDOMWindowK type AttrGetType DOMDOMWindowClientInformationPropertyInfo = DOMNavigator type AttrLabel DOMDOMWindowClientInformationPropertyInfo = "DOMDOMWindow::client-information" attrGet _ = getDOMDOMWindowClientInformation attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "closed" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMDOMWindowClosed :: (MonadIO m, DOMDOMWindowK o) => o -> m Bool getDOMDOMWindowClosed obj = liftIO $ getObjectPropertyBool obj "closed" data DOMDOMWindowClosedPropertyInfo instance AttrInfo DOMDOMWindowClosedPropertyInfo where type AttrAllowedOps DOMDOMWindowClosedPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMWindowClosedPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMWindowClosedPropertyInfo = DOMDOMWindowK type AttrGetType DOMDOMWindowClosedPropertyInfo = Bool type AttrLabel DOMDOMWindowClosedPropertyInfo = "DOMDOMWindow::closed" attrGet _ = getDOMDOMWindowClosed attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "console" -- Type: TInterface "WebKit" "DOMConsole" -- Flags: [PropertyReadable] getDOMDOMWindowConsole :: (MonadIO m, DOMDOMWindowK o) => o -> m DOMConsole getDOMDOMWindowConsole obj = liftIO $ getObjectPropertyObject obj "console" DOMConsole data DOMDOMWindowConsolePropertyInfo instance AttrInfo DOMDOMWindowConsolePropertyInfo where type AttrAllowedOps DOMDOMWindowConsolePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMWindowConsolePropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMWindowConsolePropertyInfo = DOMDOMWindowK type AttrGetType DOMDOMWindowConsolePropertyInfo = DOMConsole type AttrLabel DOMDOMWindowConsolePropertyInfo = "DOMDOMWindow::console" attrGet _ = getDOMDOMWindowConsole attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "css" -- Type: TInterface "WebKit" "DOMDOMWindowCSS" -- Flags: [PropertyReadable] getDOMDOMWindowCss :: (MonadIO m, DOMDOMWindowK o) => o -> m DOMDOMWindowCSS getDOMDOMWindowCss obj = liftIO $ getObjectPropertyObject obj "css" DOMDOMWindowCSS data DOMDOMWindowCssPropertyInfo instance AttrInfo DOMDOMWindowCssPropertyInfo where type AttrAllowedOps DOMDOMWindowCssPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMWindowCssPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMWindowCssPropertyInfo = DOMDOMWindowK type AttrGetType DOMDOMWindowCssPropertyInfo = DOMDOMWindowCSS type AttrLabel DOMDOMWindowCssPropertyInfo = "DOMDOMWindow::css" attrGet _ = getDOMDOMWindowCss attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "default-status" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMDOMWindowDefaultStatus :: (MonadIO m, DOMDOMWindowK o) => o -> m T.Text getDOMDOMWindowDefaultStatus obj = liftIO $ getObjectPropertyString obj "default-status" setDOMDOMWindowDefaultStatus :: (MonadIO m, DOMDOMWindowK o) => o -> T.Text -> m () setDOMDOMWindowDefaultStatus obj val = liftIO $ setObjectPropertyString obj "default-status" val constructDOMDOMWindowDefaultStatus :: T.Text -> IO ([Char], GValue) constructDOMDOMWindowDefaultStatus val = constructObjectPropertyString "default-status" val data DOMDOMWindowDefaultStatusPropertyInfo instance AttrInfo DOMDOMWindowDefaultStatusPropertyInfo where type AttrAllowedOps DOMDOMWindowDefaultStatusPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMDOMWindowDefaultStatusPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMDOMWindowDefaultStatusPropertyInfo = DOMDOMWindowK type AttrGetType DOMDOMWindowDefaultStatusPropertyInfo = T.Text type AttrLabel DOMDOMWindowDefaultStatusPropertyInfo = "DOMDOMWindow::default-status" attrGet _ = getDOMDOMWindowDefaultStatus attrSet _ = setDOMDOMWindowDefaultStatus attrConstruct _ = constructDOMDOMWindowDefaultStatus -- VVV Prop "device-pixel-ratio" -- Type: TBasicType TDouble -- Flags: [PropertyReadable] getDOMDOMWindowDevicePixelRatio :: (MonadIO m, DOMDOMWindowK o) => o -> m Double getDOMDOMWindowDevicePixelRatio obj = liftIO $ getObjectPropertyDouble obj "device-pixel-ratio" data DOMDOMWindowDevicePixelRatioPropertyInfo instance AttrInfo DOMDOMWindowDevicePixelRatioPropertyInfo where type AttrAllowedOps DOMDOMWindowDevicePixelRatioPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMWindowDevicePixelRatioPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMWindowDevicePixelRatioPropertyInfo = DOMDOMWindowK type AttrGetType DOMDOMWindowDevicePixelRatioPropertyInfo = Double type AttrLabel DOMDOMWindowDevicePixelRatioPropertyInfo = "DOMDOMWindow::device-pixel-ratio" attrGet _ = getDOMDOMWindowDevicePixelRatio attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "document" -- Type: TInterface "WebKit" "DOMDocument" -- Flags: [PropertyReadable] getDOMDOMWindowDocument :: (MonadIO m, DOMDOMWindowK o) => o -> m DOMDocument getDOMDOMWindowDocument obj = liftIO $ getObjectPropertyObject obj "document" DOMDocument data DOMDOMWindowDocumentPropertyInfo instance AttrInfo DOMDOMWindowDocumentPropertyInfo where type AttrAllowedOps DOMDOMWindowDocumentPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMWindowDocumentPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMWindowDocumentPropertyInfo = DOMDOMWindowK type AttrGetType DOMDOMWindowDocumentPropertyInfo = DOMDocument type AttrLabel DOMDOMWindowDocumentPropertyInfo = "DOMDOMWindow::document" attrGet _ = getDOMDOMWindowDocument attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "frame-element" -- Type: TInterface "WebKit" "DOMElement" -- Flags: [PropertyReadable] getDOMDOMWindowFrameElement :: (MonadIO m, DOMDOMWindowK o) => o -> m DOMElement getDOMDOMWindowFrameElement obj = liftIO $ getObjectPropertyObject obj "frame-element" DOMElement data DOMDOMWindowFrameElementPropertyInfo instance AttrInfo DOMDOMWindowFrameElementPropertyInfo where type AttrAllowedOps DOMDOMWindowFrameElementPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMWindowFrameElementPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMWindowFrameElementPropertyInfo = DOMDOMWindowK type AttrGetType DOMDOMWindowFrameElementPropertyInfo = DOMElement type AttrLabel DOMDOMWindowFrameElementPropertyInfo = "DOMDOMWindow::frame-element" attrGet _ = getDOMDOMWindowFrameElement attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "frames" -- Type: TInterface "WebKit" "DOMDOMWindow" -- Flags: [PropertyReadable] getDOMDOMWindowFrames :: (MonadIO m, DOMDOMWindowK o) => o -> m DOMDOMWindow getDOMDOMWindowFrames obj = liftIO $ getObjectPropertyObject obj "frames" DOMDOMWindow data DOMDOMWindowFramesPropertyInfo instance AttrInfo DOMDOMWindowFramesPropertyInfo where type AttrAllowedOps DOMDOMWindowFramesPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMWindowFramesPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMWindowFramesPropertyInfo = DOMDOMWindowK type AttrGetType DOMDOMWindowFramesPropertyInfo = DOMDOMWindow type AttrLabel DOMDOMWindowFramesPropertyInfo = "DOMDOMWindow::frames" attrGet _ = getDOMDOMWindowFrames attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "history" -- Type: TInterface "WebKit" "DOMHistory" -- Flags: [PropertyReadable] getDOMDOMWindowHistory :: (MonadIO m, DOMDOMWindowK o) => o -> m DOMHistory getDOMDOMWindowHistory obj = liftIO $ getObjectPropertyObject obj "history" DOMHistory data DOMDOMWindowHistoryPropertyInfo instance AttrInfo DOMDOMWindowHistoryPropertyInfo where type AttrAllowedOps DOMDOMWindowHistoryPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMWindowHistoryPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMWindowHistoryPropertyInfo = DOMDOMWindowK type AttrGetType DOMDOMWindowHistoryPropertyInfo = DOMHistory type AttrLabel DOMDOMWindowHistoryPropertyInfo = "DOMDOMWindow::history" attrGet _ = getDOMDOMWindowHistory attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "inner-height" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMDOMWindowInnerHeight :: (MonadIO m, DOMDOMWindowK o) => o -> m Int64 getDOMDOMWindowInnerHeight obj = liftIO $ getObjectPropertyInt64 obj "inner-height" data DOMDOMWindowInnerHeightPropertyInfo instance AttrInfo DOMDOMWindowInnerHeightPropertyInfo where type AttrAllowedOps DOMDOMWindowInnerHeightPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMWindowInnerHeightPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMWindowInnerHeightPropertyInfo = DOMDOMWindowK type AttrGetType DOMDOMWindowInnerHeightPropertyInfo = Int64 type AttrLabel DOMDOMWindowInnerHeightPropertyInfo = "DOMDOMWindow::inner-height" attrGet _ = getDOMDOMWindowInnerHeight attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "inner-width" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMDOMWindowInnerWidth :: (MonadIO m, DOMDOMWindowK o) => o -> m Int64 getDOMDOMWindowInnerWidth obj = liftIO $ getObjectPropertyInt64 obj "inner-width" data DOMDOMWindowInnerWidthPropertyInfo instance AttrInfo DOMDOMWindowInnerWidthPropertyInfo where type AttrAllowedOps DOMDOMWindowInnerWidthPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMWindowInnerWidthPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMWindowInnerWidthPropertyInfo = DOMDOMWindowK type AttrGetType DOMDOMWindowInnerWidthPropertyInfo = Int64 type AttrLabel DOMDOMWindowInnerWidthPropertyInfo = "DOMDOMWindow::inner-width" attrGet _ = getDOMDOMWindowInnerWidth attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "length" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMDOMWindowLength :: (MonadIO m, DOMDOMWindowK o) => o -> m Word64 getDOMDOMWindowLength obj = liftIO $ getObjectPropertyUInt64 obj "length" data DOMDOMWindowLengthPropertyInfo instance AttrInfo DOMDOMWindowLengthPropertyInfo where type AttrAllowedOps DOMDOMWindowLengthPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMWindowLengthPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMWindowLengthPropertyInfo = DOMDOMWindowK type AttrGetType DOMDOMWindowLengthPropertyInfo = Word64 type AttrLabel DOMDOMWindowLengthPropertyInfo = "DOMDOMWindow::length" attrGet _ = getDOMDOMWindowLength attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "local-storage" -- Type: TInterface "WebKit" "DOMStorage" -- Flags: [PropertyReadable] getDOMDOMWindowLocalStorage :: (MonadIO m, DOMDOMWindowK o) => o -> m DOMStorage getDOMDOMWindowLocalStorage obj = liftIO $ getObjectPropertyObject obj "local-storage" DOMStorage data DOMDOMWindowLocalStoragePropertyInfo instance AttrInfo DOMDOMWindowLocalStoragePropertyInfo where type AttrAllowedOps DOMDOMWindowLocalStoragePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMWindowLocalStoragePropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMWindowLocalStoragePropertyInfo = DOMDOMWindowK type AttrGetType DOMDOMWindowLocalStoragePropertyInfo = DOMStorage type AttrLabel DOMDOMWindowLocalStoragePropertyInfo = "DOMDOMWindow::local-storage" attrGet _ = getDOMDOMWindowLocalStorage attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "locationbar" -- Type: TInterface "WebKit" "DOMBarProp" -- Flags: [PropertyReadable] getDOMDOMWindowLocationbar :: (MonadIO m, DOMDOMWindowK o) => o -> m DOMBarProp getDOMDOMWindowLocationbar obj = liftIO $ getObjectPropertyObject obj "locationbar" DOMBarProp data DOMDOMWindowLocationbarPropertyInfo instance AttrInfo DOMDOMWindowLocationbarPropertyInfo where type AttrAllowedOps DOMDOMWindowLocationbarPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMWindowLocationbarPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMWindowLocationbarPropertyInfo = DOMDOMWindowK type AttrGetType DOMDOMWindowLocationbarPropertyInfo = DOMBarProp type AttrLabel DOMDOMWindowLocationbarPropertyInfo = "DOMDOMWindow::locationbar" attrGet _ = getDOMDOMWindowLocationbar attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "menubar" -- Type: TInterface "WebKit" "DOMBarProp" -- Flags: [PropertyReadable] getDOMDOMWindowMenubar :: (MonadIO m, DOMDOMWindowK o) => o -> m DOMBarProp getDOMDOMWindowMenubar obj = liftIO $ getObjectPropertyObject obj "menubar" DOMBarProp data DOMDOMWindowMenubarPropertyInfo instance AttrInfo DOMDOMWindowMenubarPropertyInfo where type AttrAllowedOps DOMDOMWindowMenubarPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMWindowMenubarPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMWindowMenubarPropertyInfo = DOMDOMWindowK type AttrGetType DOMDOMWindowMenubarPropertyInfo = DOMBarProp type AttrLabel DOMDOMWindowMenubarPropertyInfo = "DOMDOMWindow::menubar" attrGet _ = getDOMDOMWindowMenubar attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "name" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMDOMWindowName :: (MonadIO m, DOMDOMWindowK o) => o -> m T.Text getDOMDOMWindowName obj = liftIO $ getObjectPropertyString obj "name" setDOMDOMWindowName :: (MonadIO m, DOMDOMWindowK o) => o -> T.Text -> m () setDOMDOMWindowName obj val = liftIO $ setObjectPropertyString obj "name" val constructDOMDOMWindowName :: T.Text -> IO ([Char], GValue) constructDOMDOMWindowName val = constructObjectPropertyString "name" val data DOMDOMWindowNamePropertyInfo instance AttrInfo DOMDOMWindowNamePropertyInfo where type AttrAllowedOps DOMDOMWindowNamePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMDOMWindowNamePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMDOMWindowNamePropertyInfo = DOMDOMWindowK type AttrGetType DOMDOMWindowNamePropertyInfo = T.Text type AttrLabel DOMDOMWindowNamePropertyInfo = "DOMDOMWindow::name" attrGet _ = getDOMDOMWindowName attrSet _ = setDOMDOMWindowName attrConstruct _ = constructDOMDOMWindowName -- VVV Prop "navigator" -- Type: TInterface "WebKit" "DOMNavigator" -- Flags: [PropertyReadable] getDOMDOMWindowNavigator :: (MonadIO m, DOMDOMWindowK o) => o -> m DOMNavigator getDOMDOMWindowNavigator obj = liftIO $ getObjectPropertyObject obj "navigator" DOMNavigator data DOMDOMWindowNavigatorPropertyInfo instance AttrInfo DOMDOMWindowNavigatorPropertyInfo where type AttrAllowedOps DOMDOMWindowNavigatorPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMWindowNavigatorPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMWindowNavigatorPropertyInfo = DOMDOMWindowK type AttrGetType DOMDOMWindowNavigatorPropertyInfo = DOMNavigator type AttrLabel DOMDOMWindowNavigatorPropertyInfo = "DOMDOMWindow::navigator" attrGet _ = getDOMDOMWindowNavigator attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "offscreen-buffering" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMDOMWindowOffscreenBuffering :: (MonadIO m, DOMDOMWindowK o) => o -> m Bool getDOMDOMWindowOffscreenBuffering obj = liftIO $ getObjectPropertyBool obj "offscreen-buffering" data DOMDOMWindowOffscreenBufferingPropertyInfo instance AttrInfo DOMDOMWindowOffscreenBufferingPropertyInfo where type AttrAllowedOps DOMDOMWindowOffscreenBufferingPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMWindowOffscreenBufferingPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMWindowOffscreenBufferingPropertyInfo = DOMDOMWindowK type AttrGetType DOMDOMWindowOffscreenBufferingPropertyInfo = Bool type AttrLabel DOMDOMWindowOffscreenBufferingPropertyInfo = "DOMDOMWindow::offscreen-buffering" attrGet _ = getDOMDOMWindowOffscreenBuffering attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "opener" -- Type: TInterface "WebKit" "DOMDOMWindow" -- Flags: [PropertyReadable] getDOMDOMWindowOpener :: (MonadIO m, DOMDOMWindowK o) => o -> m DOMDOMWindow getDOMDOMWindowOpener obj = liftIO $ getObjectPropertyObject obj "opener" DOMDOMWindow data DOMDOMWindowOpenerPropertyInfo instance AttrInfo DOMDOMWindowOpenerPropertyInfo where type AttrAllowedOps DOMDOMWindowOpenerPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMWindowOpenerPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMWindowOpenerPropertyInfo = DOMDOMWindowK type AttrGetType DOMDOMWindowOpenerPropertyInfo = DOMDOMWindow type AttrLabel DOMDOMWindowOpenerPropertyInfo = "DOMDOMWindow::opener" attrGet _ = getDOMDOMWindowOpener attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "outer-height" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMDOMWindowOuterHeight :: (MonadIO m, DOMDOMWindowK o) => o -> m Int64 getDOMDOMWindowOuterHeight obj = liftIO $ getObjectPropertyInt64 obj "outer-height" data DOMDOMWindowOuterHeightPropertyInfo instance AttrInfo DOMDOMWindowOuterHeightPropertyInfo where type AttrAllowedOps DOMDOMWindowOuterHeightPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMWindowOuterHeightPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMWindowOuterHeightPropertyInfo = DOMDOMWindowK type AttrGetType DOMDOMWindowOuterHeightPropertyInfo = Int64 type AttrLabel DOMDOMWindowOuterHeightPropertyInfo = "DOMDOMWindow::outer-height" attrGet _ = getDOMDOMWindowOuterHeight attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "outer-width" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMDOMWindowOuterWidth :: (MonadIO m, DOMDOMWindowK o) => o -> m Int64 getDOMDOMWindowOuterWidth obj = liftIO $ getObjectPropertyInt64 obj "outer-width" data DOMDOMWindowOuterWidthPropertyInfo instance AttrInfo DOMDOMWindowOuterWidthPropertyInfo where type AttrAllowedOps DOMDOMWindowOuterWidthPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMWindowOuterWidthPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMWindowOuterWidthPropertyInfo = DOMDOMWindowK type AttrGetType DOMDOMWindowOuterWidthPropertyInfo = Int64 type AttrLabel DOMDOMWindowOuterWidthPropertyInfo = "DOMDOMWindow::outer-width" attrGet _ = getDOMDOMWindowOuterWidth attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "page-x-offset" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMDOMWindowPageXOffset :: (MonadIO m, DOMDOMWindowK o) => o -> m Int64 getDOMDOMWindowPageXOffset obj = liftIO $ getObjectPropertyInt64 obj "page-x-offset" data DOMDOMWindowPageXOffsetPropertyInfo instance AttrInfo DOMDOMWindowPageXOffsetPropertyInfo where type AttrAllowedOps DOMDOMWindowPageXOffsetPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMWindowPageXOffsetPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMWindowPageXOffsetPropertyInfo = DOMDOMWindowK type AttrGetType DOMDOMWindowPageXOffsetPropertyInfo = Int64 type AttrLabel DOMDOMWindowPageXOffsetPropertyInfo = "DOMDOMWindow::page-x-offset" attrGet _ = getDOMDOMWindowPageXOffset attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "page-y-offset" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMDOMWindowPageYOffset :: (MonadIO m, DOMDOMWindowK o) => o -> m Int64 getDOMDOMWindowPageYOffset obj = liftIO $ getObjectPropertyInt64 obj "page-y-offset" data DOMDOMWindowPageYOffsetPropertyInfo instance AttrInfo DOMDOMWindowPageYOffsetPropertyInfo where type AttrAllowedOps DOMDOMWindowPageYOffsetPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMWindowPageYOffsetPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMWindowPageYOffsetPropertyInfo = DOMDOMWindowK type AttrGetType DOMDOMWindowPageYOffsetPropertyInfo = Int64 type AttrLabel DOMDOMWindowPageYOffsetPropertyInfo = "DOMDOMWindow::page-y-offset" attrGet _ = getDOMDOMWindowPageYOffset attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "parent" -- Type: TInterface "WebKit" "DOMDOMWindow" -- Flags: [PropertyReadable] getDOMDOMWindowParent :: (MonadIO m, DOMDOMWindowK o) => o -> m DOMDOMWindow getDOMDOMWindowParent obj = liftIO $ getObjectPropertyObject obj "parent" DOMDOMWindow data DOMDOMWindowParentPropertyInfo instance AttrInfo DOMDOMWindowParentPropertyInfo where type AttrAllowedOps DOMDOMWindowParentPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMWindowParentPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMWindowParentPropertyInfo = DOMDOMWindowK type AttrGetType DOMDOMWindowParentPropertyInfo = DOMDOMWindow type AttrLabel DOMDOMWindowParentPropertyInfo = "DOMDOMWindow::parent" attrGet _ = getDOMDOMWindowParent attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "performance" -- Type: TInterface "WebKit" "DOMPerformance" -- Flags: [PropertyReadable] getDOMDOMWindowPerformance :: (MonadIO m, DOMDOMWindowK o) => o -> m DOMPerformance getDOMDOMWindowPerformance obj = liftIO $ getObjectPropertyObject obj "performance" DOMPerformance data DOMDOMWindowPerformancePropertyInfo instance AttrInfo DOMDOMWindowPerformancePropertyInfo where type AttrAllowedOps DOMDOMWindowPerformancePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMWindowPerformancePropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMWindowPerformancePropertyInfo = DOMDOMWindowK type AttrGetType DOMDOMWindowPerformancePropertyInfo = DOMPerformance type AttrLabel DOMDOMWindowPerformancePropertyInfo = "DOMDOMWindow::performance" attrGet _ = getDOMDOMWindowPerformance attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "personalbar" -- Type: TInterface "WebKit" "DOMBarProp" -- Flags: [PropertyReadable] getDOMDOMWindowPersonalbar :: (MonadIO m, DOMDOMWindowK o) => o -> m DOMBarProp getDOMDOMWindowPersonalbar obj = liftIO $ getObjectPropertyObject obj "personalbar" DOMBarProp data DOMDOMWindowPersonalbarPropertyInfo instance AttrInfo DOMDOMWindowPersonalbarPropertyInfo where type AttrAllowedOps DOMDOMWindowPersonalbarPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMWindowPersonalbarPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMWindowPersonalbarPropertyInfo = DOMDOMWindowK type AttrGetType DOMDOMWindowPersonalbarPropertyInfo = DOMBarProp type AttrLabel DOMDOMWindowPersonalbarPropertyInfo = "DOMDOMWindow::personalbar" attrGet _ = getDOMDOMWindowPersonalbar attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "screen" -- Type: TInterface "WebKit" "DOMScreen" -- Flags: [PropertyReadable] getDOMDOMWindowScreen :: (MonadIO m, DOMDOMWindowK o) => o -> m DOMScreen getDOMDOMWindowScreen obj = liftIO $ getObjectPropertyObject obj "screen" DOMScreen data DOMDOMWindowScreenPropertyInfo instance AttrInfo DOMDOMWindowScreenPropertyInfo where type AttrAllowedOps DOMDOMWindowScreenPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMWindowScreenPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMWindowScreenPropertyInfo = DOMDOMWindowK type AttrGetType DOMDOMWindowScreenPropertyInfo = DOMScreen type AttrLabel DOMDOMWindowScreenPropertyInfo = "DOMDOMWindow::screen" attrGet _ = getDOMDOMWindowScreen attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "screen-left" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMDOMWindowScreenLeft :: (MonadIO m, DOMDOMWindowK o) => o -> m Int64 getDOMDOMWindowScreenLeft obj = liftIO $ getObjectPropertyInt64 obj "screen-left" data DOMDOMWindowScreenLeftPropertyInfo instance AttrInfo DOMDOMWindowScreenLeftPropertyInfo where type AttrAllowedOps DOMDOMWindowScreenLeftPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMWindowScreenLeftPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMWindowScreenLeftPropertyInfo = DOMDOMWindowK type AttrGetType DOMDOMWindowScreenLeftPropertyInfo = Int64 type AttrLabel DOMDOMWindowScreenLeftPropertyInfo = "DOMDOMWindow::screen-left" attrGet _ = getDOMDOMWindowScreenLeft attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "screen-top" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMDOMWindowScreenTop :: (MonadIO m, DOMDOMWindowK o) => o -> m Int64 getDOMDOMWindowScreenTop obj = liftIO $ getObjectPropertyInt64 obj "screen-top" data DOMDOMWindowScreenTopPropertyInfo instance AttrInfo DOMDOMWindowScreenTopPropertyInfo where type AttrAllowedOps DOMDOMWindowScreenTopPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMWindowScreenTopPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMWindowScreenTopPropertyInfo = DOMDOMWindowK type AttrGetType DOMDOMWindowScreenTopPropertyInfo = Int64 type AttrLabel DOMDOMWindowScreenTopPropertyInfo = "DOMDOMWindow::screen-top" attrGet _ = getDOMDOMWindowScreenTop attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "screen-x" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMDOMWindowScreenX :: (MonadIO m, DOMDOMWindowK o) => o -> m Int64 getDOMDOMWindowScreenX obj = liftIO $ getObjectPropertyInt64 obj "screen-x" data DOMDOMWindowScreenXPropertyInfo instance AttrInfo DOMDOMWindowScreenXPropertyInfo where type AttrAllowedOps DOMDOMWindowScreenXPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMWindowScreenXPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMWindowScreenXPropertyInfo = DOMDOMWindowK type AttrGetType DOMDOMWindowScreenXPropertyInfo = Int64 type AttrLabel DOMDOMWindowScreenXPropertyInfo = "DOMDOMWindow::screen-x" attrGet _ = getDOMDOMWindowScreenX attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "screen-y" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMDOMWindowScreenY :: (MonadIO m, DOMDOMWindowK o) => o -> m Int64 getDOMDOMWindowScreenY obj = liftIO $ getObjectPropertyInt64 obj "screen-y" data DOMDOMWindowScreenYPropertyInfo instance AttrInfo DOMDOMWindowScreenYPropertyInfo where type AttrAllowedOps DOMDOMWindowScreenYPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMWindowScreenYPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMWindowScreenYPropertyInfo = DOMDOMWindowK type AttrGetType DOMDOMWindowScreenYPropertyInfo = Int64 type AttrLabel DOMDOMWindowScreenYPropertyInfo = "DOMDOMWindow::screen-y" attrGet _ = getDOMDOMWindowScreenY attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "scroll-x" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMDOMWindowScrollX :: (MonadIO m, DOMDOMWindowK o) => o -> m Int64 getDOMDOMWindowScrollX obj = liftIO $ getObjectPropertyInt64 obj "scroll-x" data DOMDOMWindowScrollXPropertyInfo instance AttrInfo DOMDOMWindowScrollXPropertyInfo where type AttrAllowedOps DOMDOMWindowScrollXPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMWindowScrollXPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMWindowScrollXPropertyInfo = DOMDOMWindowK type AttrGetType DOMDOMWindowScrollXPropertyInfo = Int64 type AttrLabel DOMDOMWindowScrollXPropertyInfo = "DOMDOMWindow::scroll-x" attrGet _ = getDOMDOMWindowScrollX attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "scroll-y" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMDOMWindowScrollY :: (MonadIO m, DOMDOMWindowK o) => o -> m Int64 getDOMDOMWindowScrollY obj = liftIO $ getObjectPropertyInt64 obj "scroll-y" data DOMDOMWindowScrollYPropertyInfo instance AttrInfo DOMDOMWindowScrollYPropertyInfo where type AttrAllowedOps DOMDOMWindowScrollYPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMWindowScrollYPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMWindowScrollYPropertyInfo = DOMDOMWindowK type AttrGetType DOMDOMWindowScrollYPropertyInfo = Int64 type AttrLabel DOMDOMWindowScrollYPropertyInfo = "DOMDOMWindow::scroll-y" attrGet _ = getDOMDOMWindowScrollY attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "scrollbars" -- Type: TInterface "WebKit" "DOMBarProp" -- Flags: [PropertyReadable] getDOMDOMWindowScrollbars :: (MonadIO m, DOMDOMWindowK o) => o -> m DOMBarProp getDOMDOMWindowScrollbars obj = liftIO $ getObjectPropertyObject obj "scrollbars" DOMBarProp data DOMDOMWindowScrollbarsPropertyInfo instance AttrInfo DOMDOMWindowScrollbarsPropertyInfo where type AttrAllowedOps DOMDOMWindowScrollbarsPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMWindowScrollbarsPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMWindowScrollbarsPropertyInfo = DOMDOMWindowK type AttrGetType DOMDOMWindowScrollbarsPropertyInfo = DOMBarProp type AttrLabel DOMDOMWindowScrollbarsPropertyInfo = "DOMDOMWindow::scrollbars" attrGet _ = getDOMDOMWindowScrollbars attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "self" -- Type: TInterface "WebKit" "DOMDOMWindow" -- Flags: [PropertyReadable] getDOMDOMWindowSelf :: (MonadIO m, DOMDOMWindowK o) => o -> m DOMDOMWindow getDOMDOMWindowSelf obj = liftIO $ getObjectPropertyObject obj "self" DOMDOMWindow data DOMDOMWindowSelfPropertyInfo instance AttrInfo DOMDOMWindowSelfPropertyInfo where type AttrAllowedOps DOMDOMWindowSelfPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMWindowSelfPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMWindowSelfPropertyInfo = DOMDOMWindowK type AttrGetType DOMDOMWindowSelfPropertyInfo = DOMDOMWindow type AttrLabel DOMDOMWindowSelfPropertyInfo = "DOMDOMWindow::self" attrGet _ = getDOMDOMWindowSelf attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "session-storage" -- Type: TInterface "WebKit" "DOMStorage" -- Flags: [PropertyReadable] getDOMDOMWindowSessionStorage :: (MonadIO m, DOMDOMWindowK o) => o -> m DOMStorage getDOMDOMWindowSessionStorage obj = liftIO $ getObjectPropertyObject obj "session-storage" DOMStorage data DOMDOMWindowSessionStoragePropertyInfo instance AttrInfo DOMDOMWindowSessionStoragePropertyInfo where type AttrAllowedOps DOMDOMWindowSessionStoragePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMWindowSessionStoragePropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMWindowSessionStoragePropertyInfo = DOMDOMWindowK type AttrGetType DOMDOMWindowSessionStoragePropertyInfo = DOMStorage type AttrLabel DOMDOMWindowSessionStoragePropertyInfo = "DOMDOMWindow::session-storage" attrGet _ = getDOMDOMWindowSessionStorage attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "status" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMDOMWindowStatus :: (MonadIO m, DOMDOMWindowK o) => o -> m T.Text getDOMDOMWindowStatus obj = liftIO $ getObjectPropertyString obj "status" setDOMDOMWindowStatus :: (MonadIO m, DOMDOMWindowK o) => o -> T.Text -> m () setDOMDOMWindowStatus obj val = liftIO $ setObjectPropertyString obj "status" val constructDOMDOMWindowStatus :: T.Text -> IO ([Char], GValue) constructDOMDOMWindowStatus val = constructObjectPropertyString "status" val data DOMDOMWindowStatusPropertyInfo instance AttrInfo DOMDOMWindowStatusPropertyInfo where type AttrAllowedOps DOMDOMWindowStatusPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMDOMWindowStatusPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMDOMWindowStatusPropertyInfo = DOMDOMWindowK type AttrGetType DOMDOMWindowStatusPropertyInfo = T.Text type AttrLabel DOMDOMWindowStatusPropertyInfo = "DOMDOMWindow::status" attrGet _ = getDOMDOMWindowStatus attrSet _ = setDOMDOMWindowStatus attrConstruct _ = constructDOMDOMWindowStatus -- VVV Prop "statusbar" -- Type: TInterface "WebKit" "DOMBarProp" -- Flags: [PropertyReadable] getDOMDOMWindowStatusbar :: (MonadIO m, DOMDOMWindowK o) => o -> m DOMBarProp getDOMDOMWindowStatusbar obj = liftIO $ getObjectPropertyObject obj "statusbar" DOMBarProp data DOMDOMWindowStatusbarPropertyInfo instance AttrInfo DOMDOMWindowStatusbarPropertyInfo where type AttrAllowedOps DOMDOMWindowStatusbarPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMWindowStatusbarPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMWindowStatusbarPropertyInfo = DOMDOMWindowK type AttrGetType DOMDOMWindowStatusbarPropertyInfo = DOMBarProp type AttrLabel DOMDOMWindowStatusbarPropertyInfo = "DOMDOMWindow::statusbar" attrGet _ = getDOMDOMWindowStatusbar attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "style-media" -- Type: TInterface "WebKit" "DOMStyleMedia" -- Flags: [PropertyReadable] getDOMDOMWindowStyleMedia :: (MonadIO m, DOMDOMWindowK o) => o -> m DOMStyleMedia getDOMDOMWindowStyleMedia obj = liftIO $ getObjectPropertyObject obj "style-media" DOMStyleMedia data DOMDOMWindowStyleMediaPropertyInfo instance AttrInfo DOMDOMWindowStyleMediaPropertyInfo where type AttrAllowedOps DOMDOMWindowStyleMediaPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMWindowStyleMediaPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMWindowStyleMediaPropertyInfo = DOMDOMWindowK type AttrGetType DOMDOMWindowStyleMediaPropertyInfo = DOMStyleMedia type AttrLabel DOMDOMWindowStyleMediaPropertyInfo = "DOMDOMWindow::style-media" attrGet _ = getDOMDOMWindowStyleMedia attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "toolbar" -- Type: TInterface "WebKit" "DOMBarProp" -- Flags: [PropertyReadable] getDOMDOMWindowToolbar :: (MonadIO m, DOMDOMWindowK o) => o -> m DOMBarProp getDOMDOMWindowToolbar obj = liftIO $ getObjectPropertyObject obj "toolbar" DOMBarProp data DOMDOMWindowToolbarPropertyInfo instance AttrInfo DOMDOMWindowToolbarPropertyInfo where type AttrAllowedOps DOMDOMWindowToolbarPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMWindowToolbarPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMWindowToolbarPropertyInfo = DOMDOMWindowK type AttrGetType DOMDOMWindowToolbarPropertyInfo = DOMBarProp type AttrLabel DOMDOMWindowToolbarPropertyInfo = "DOMDOMWindow::toolbar" attrGet _ = getDOMDOMWindowToolbar attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "top" -- Type: TInterface "WebKit" "DOMDOMWindow" -- Flags: [PropertyReadable] getDOMDOMWindowTop :: (MonadIO m, DOMDOMWindowK o) => o -> m DOMDOMWindow getDOMDOMWindowTop obj = liftIO $ getObjectPropertyObject obj "top" DOMDOMWindow data DOMDOMWindowTopPropertyInfo instance AttrInfo DOMDOMWindowTopPropertyInfo where type AttrAllowedOps DOMDOMWindowTopPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMWindowTopPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMWindowTopPropertyInfo = DOMDOMWindowK type AttrGetType DOMDOMWindowTopPropertyInfo = DOMDOMWindow type AttrLabel DOMDOMWindowTopPropertyInfo = "DOMDOMWindow::top" attrGet _ = getDOMDOMWindowTop attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "webkit-storage-info" -- Type: TInterface "WebKit" "DOMStorageInfo" -- Flags: [PropertyReadable] getDOMDOMWindowWebkitStorageInfo :: (MonadIO m, DOMDOMWindowK o) => o -> m DOMStorageInfo getDOMDOMWindowWebkitStorageInfo obj = liftIO $ getObjectPropertyObject obj "webkit-storage-info" DOMStorageInfo data DOMDOMWindowWebkitStorageInfoPropertyInfo instance AttrInfo DOMDOMWindowWebkitStorageInfoPropertyInfo where type AttrAllowedOps DOMDOMWindowWebkitStorageInfoPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMWindowWebkitStorageInfoPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMWindowWebkitStorageInfoPropertyInfo = DOMDOMWindowK type AttrGetType DOMDOMWindowWebkitStorageInfoPropertyInfo = DOMStorageInfo type AttrLabel DOMDOMWindowWebkitStorageInfoPropertyInfo = "DOMDOMWindow::webkit-storage-info" attrGet _ = getDOMDOMWindowWebkitStorageInfo attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "window" -- Type: TInterface "WebKit" "DOMDOMWindow" -- Flags: [PropertyReadable] getDOMDOMWindowWindow :: (MonadIO m, DOMDOMWindowK o) => o -> m DOMDOMWindow getDOMDOMWindowWindow obj = liftIO $ getObjectPropertyObject obj "window" DOMDOMWindow data DOMDOMWindowWindowPropertyInfo instance AttrInfo DOMDOMWindowWindowPropertyInfo where type AttrAllowedOps DOMDOMWindowWindowPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDOMWindowWindowPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDOMWindowWindowPropertyInfo = DOMDOMWindowK type AttrGetType DOMDOMWindowWindowPropertyInfo = DOMDOMWindow type AttrLabel DOMDOMWindowWindowPropertyInfo = "DOMDOMWindow::window" attrGet _ = getDOMDOMWindowWindow attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMDOMWindow = '[ '("application-cache", DOMDOMWindowApplicationCachePropertyInfo), '("client-information", DOMDOMWindowClientInformationPropertyInfo), '("closed", DOMDOMWindowClosedPropertyInfo), '("console", DOMDOMWindowConsolePropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("css", DOMDOMWindowCssPropertyInfo), '("default-status", DOMDOMWindowDefaultStatusPropertyInfo), '("device-pixel-ratio", DOMDOMWindowDevicePixelRatioPropertyInfo), '("document", DOMDOMWindowDocumentPropertyInfo), '("frame-element", DOMDOMWindowFrameElementPropertyInfo), '("frames", DOMDOMWindowFramesPropertyInfo), '("history", DOMDOMWindowHistoryPropertyInfo), '("inner-height", DOMDOMWindowInnerHeightPropertyInfo), '("inner-width", DOMDOMWindowInnerWidthPropertyInfo), '("length", DOMDOMWindowLengthPropertyInfo), '("local-storage", DOMDOMWindowLocalStoragePropertyInfo), '("locationbar", DOMDOMWindowLocationbarPropertyInfo), '("menubar", DOMDOMWindowMenubarPropertyInfo), '("name", DOMDOMWindowNamePropertyInfo), '("navigator", DOMDOMWindowNavigatorPropertyInfo), '("offscreen-buffering", DOMDOMWindowOffscreenBufferingPropertyInfo), '("opener", DOMDOMWindowOpenerPropertyInfo), '("outer-height", DOMDOMWindowOuterHeightPropertyInfo), '("outer-width", DOMDOMWindowOuterWidthPropertyInfo), '("page-x-offset", DOMDOMWindowPageXOffsetPropertyInfo), '("page-y-offset", DOMDOMWindowPageYOffsetPropertyInfo), '("parent", DOMDOMWindowParentPropertyInfo), '("performance", DOMDOMWindowPerformancePropertyInfo), '("personalbar", DOMDOMWindowPersonalbarPropertyInfo), '("screen", DOMDOMWindowScreenPropertyInfo), '("screen-left", DOMDOMWindowScreenLeftPropertyInfo), '("screen-top", DOMDOMWindowScreenTopPropertyInfo), '("screen-x", DOMDOMWindowScreenXPropertyInfo), '("screen-y", DOMDOMWindowScreenYPropertyInfo), '("scroll-x", DOMDOMWindowScrollXPropertyInfo), '("scroll-y", DOMDOMWindowScrollYPropertyInfo), '("scrollbars", DOMDOMWindowScrollbarsPropertyInfo), '("self", DOMDOMWindowSelfPropertyInfo), '("session-storage", DOMDOMWindowSessionStoragePropertyInfo), '("status", DOMDOMWindowStatusPropertyInfo), '("statusbar", DOMDOMWindowStatusbarPropertyInfo), '("style-media", DOMDOMWindowStyleMediaPropertyInfo), '("toolbar", DOMDOMWindowToolbarPropertyInfo), '("top", DOMDOMWindowTopPropertyInfo), '("webkit-storage-info", DOMDOMWindowWebkitStorageInfoPropertyInfo), '("window", DOMDOMWindowWindowPropertyInfo)] type instance AttributeList DOMDOMWindowCSS = '[ '("core-object", DOMObjectCoreObjectPropertyInfo)] -- VVV Prop "version" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMDatabaseVersion :: (MonadIO m, DOMDatabaseK o) => o -> m T.Text getDOMDatabaseVersion obj = liftIO $ getObjectPropertyString obj "version" data DOMDatabaseVersionPropertyInfo instance AttrInfo DOMDatabaseVersionPropertyInfo where type AttrAllowedOps DOMDatabaseVersionPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDatabaseVersionPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDatabaseVersionPropertyInfo = DOMDatabaseK type AttrGetType DOMDatabaseVersionPropertyInfo = T.Text type AttrLabel DOMDatabaseVersionPropertyInfo = "DOMDatabase::version" attrGet _ = getDOMDatabaseVersion attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMDatabase = '[ '("core-object", DOMObjectCoreObjectPropertyInfo), '("version", DOMDatabaseVersionPropertyInfo)] -- VVV Prop "anchors" -- Type: TInterface "WebKit" "DOMHTMLCollection" -- Flags: [PropertyReadable] getDOMDocumentAnchors :: (MonadIO m, DOMDocumentK o) => o -> m DOMHTMLCollection getDOMDocumentAnchors obj = liftIO $ getObjectPropertyObject obj "anchors" DOMHTMLCollection data DOMDocumentAnchorsPropertyInfo instance AttrInfo DOMDocumentAnchorsPropertyInfo where type AttrAllowedOps DOMDocumentAnchorsPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDocumentAnchorsPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDocumentAnchorsPropertyInfo = DOMDocumentK type AttrGetType DOMDocumentAnchorsPropertyInfo = DOMHTMLCollection type AttrLabel DOMDocumentAnchorsPropertyInfo = "DOMDocument::anchors" attrGet _ = getDOMDocumentAnchors attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "applets" -- Type: TInterface "WebKit" "DOMHTMLCollection" -- Flags: [PropertyReadable] getDOMDocumentApplets :: (MonadIO m, DOMDocumentK o) => o -> m DOMHTMLCollection getDOMDocumentApplets obj = liftIO $ getObjectPropertyObject obj "applets" DOMHTMLCollection data DOMDocumentAppletsPropertyInfo instance AttrInfo DOMDocumentAppletsPropertyInfo where type AttrAllowedOps DOMDocumentAppletsPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDocumentAppletsPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDocumentAppletsPropertyInfo = DOMDocumentK type AttrGetType DOMDocumentAppletsPropertyInfo = DOMHTMLCollection type AttrLabel DOMDocumentAppletsPropertyInfo = "DOMDocument::applets" attrGet _ = getDOMDocumentApplets attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "body" -- Type: TInterface "WebKit" "DOMHTMLElement" -- Flags: [PropertyReadable] getDOMDocumentBody :: (MonadIO m, DOMDocumentK o) => o -> m DOMHTMLElement getDOMDocumentBody obj = liftIO $ getObjectPropertyObject obj "body" DOMHTMLElement data DOMDocumentBodyPropertyInfo instance AttrInfo DOMDocumentBodyPropertyInfo where type AttrAllowedOps DOMDocumentBodyPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDocumentBodyPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDocumentBodyPropertyInfo = DOMDocumentK type AttrGetType DOMDocumentBodyPropertyInfo = DOMHTMLElement type AttrLabel DOMDocumentBodyPropertyInfo = "DOMDocument::body" attrGet _ = getDOMDocumentBody attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "character-set" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMDocumentCharacterSet :: (MonadIO m, DOMDocumentK o) => o -> m T.Text getDOMDocumentCharacterSet obj = liftIO $ getObjectPropertyString obj "character-set" data DOMDocumentCharacterSetPropertyInfo instance AttrInfo DOMDocumentCharacterSetPropertyInfo where type AttrAllowedOps DOMDocumentCharacterSetPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDocumentCharacterSetPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDocumentCharacterSetPropertyInfo = DOMDocumentK type AttrGetType DOMDocumentCharacterSetPropertyInfo = T.Text type AttrLabel DOMDocumentCharacterSetPropertyInfo = "DOMDocument::character-set" attrGet _ = getDOMDocumentCharacterSet attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "charset" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMDocumentCharset :: (MonadIO m, DOMDocumentK o) => o -> m T.Text getDOMDocumentCharset obj = liftIO $ getObjectPropertyString obj "charset" setDOMDocumentCharset :: (MonadIO m, DOMDocumentK o) => o -> T.Text -> m () setDOMDocumentCharset obj val = liftIO $ setObjectPropertyString obj "charset" val constructDOMDocumentCharset :: T.Text -> IO ([Char], GValue) constructDOMDocumentCharset val = constructObjectPropertyString "charset" val data DOMDocumentCharsetPropertyInfo instance AttrInfo DOMDocumentCharsetPropertyInfo where type AttrAllowedOps DOMDocumentCharsetPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMDocumentCharsetPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMDocumentCharsetPropertyInfo = DOMDocumentK type AttrGetType DOMDocumentCharsetPropertyInfo = T.Text type AttrLabel DOMDocumentCharsetPropertyInfo = "DOMDocument::charset" attrGet _ = getDOMDocumentCharset attrSet _ = setDOMDocumentCharset attrConstruct _ = constructDOMDocumentCharset -- VVV Prop "compat-mode" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMDocumentCompatMode :: (MonadIO m, DOMDocumentK o) => o -> m T.Text getDOMDocumentCompatMode obj = liftIO $ getObjectPropertyString obj "compat-mode" data DOMDocumentCompatModePropertyInfo instance AttrInfo DOMDocumentCompatModePropertyInfo where type AttrAllowedOps DOMDocumentCompatModePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDocumentCompatModePropertyInfo = (~) () type AttrBaseTypeConstraint DOMDocumentCompatModePropertyInfo = DOMDocumentK type AttrGetType DOMDocumentCompatModePropertyInfo = T.Text type AttrLabel DOMDocumentCompatModePropertyInfo = "DOMDocument::compat-mode" attrGet _ = getDOMDocumentCompatMode attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "cookie" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMDocumentCookie :: (MonadIO m, DOMDocumentK o) => o -> m T.Text getDOMDocumentCookie obj = liftIO $ getObjectPropertyString obj "cookie" setDOMDocumentCookie :: (MonadIO m, DOMDocumentK o) => o -> T.Text -> m () setDOMDocumentCookie obj val = liftIO $ setObjectPropertyString obj "cookie" val constructDOMDocumentCookie :: T.Text -> IO ([Char], GValue) constructDOMDocumentCookie val = constructObjectPropertyString "cookie" val data DOMDocumentCookiePropertyInfo instance AttrInfo DOMDocumentCookiePropertyInfo where type AttrAllowedOps DOMDocumentCookiePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMDocumentCookiePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMDocumentCookiePropertyInfo = DOMDocumentK type AttrGetType DOMDocumentCookiePropertyInfo = T.Text type AttrLabel DOMDocumentCookiePropertyInfo = "DOMDocument::cookie" attrGet _ = getDOMDocumentCookie attrSet _ = setDOMDocumentCookie attrConstruct _ = constructDOMDocumentCookie -- VVV Prop "current-script" -- Type: TInterface "WebKit" "DOMHTMLScriptElement" -- Flags: [PropertyReadable] getDOMDocumentCurrentScript :: (MonadIO m, DOMDocumentK o) => o -> m DOMHTMLScriptElement getDOMDocumentCurrentScript obj = liftIO $ getObjectPropertyObject obj "current-script" DOMHTMLScriptElement data DOMDocumentCurrentScriptPropertyInfo instance AttrInfo DOMDocumentCurrentScriptPropertyInfo where type AttrAllowedOps DOMDocumentCurrentScriptPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDocumentCurrentScriptPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDocumentCurrentScriptPropertyInfo = DOMDocumentK type AttrGetType DOMDocumentCurrentScriptPropertyInfo = DOMHTMLScriptElement type AttrLabel DOMDocumentCurrentScriptPropertyInfo = "DOMDocument::current-script" attrGet _ = getDOMDocumentCurrentScript attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "default-charset" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMDocumentDefaultCharset :: (MonadIO m, DOMDocumentK o) => o -> m T.Text getDOMDocumentDefaultCharset obj = liftIO $ getObjectPropertyString obj "default-charset" data DOMDocumentDefaultCharsetPropertyInfo instance AttrInfo DOMDocumentDefaultCharsetPropertyInfo where type AttrAllowedOps DOMDocumentDefaultCharsetPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDocumentDefaultCharsetPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDocumentDefaultCharsetPropertyInfo = DOMDocumentK type AttrGetType DOMDocumentDefaultCharsetPropertyInfo = T.Text type AttrLabel DOMDocumentDefaultCharsetPropertyInfo = "DOMDocument::default-charset" attrGet _ = getDOMDocumentDefaultCharset attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "default-view" -- Type: TInterface "WebKit" "DOMDOMWindow" -- Flags: [PropertyReadable] getDOMDocumentDefaultView :: (MonadIO m, DOMDocumentK o) => o -> m DOMDOMWindow getDOMDocumentDefaultView obj = liftIO $ getObjectPropertyObject obj "default-view" DOMDOMWindow data DOMDocumentDefaultViewPropertyInfo instance AttrInfo DOMDocumentDefaultViewPropertyInfo where type AttrAllowedOps DOMDocumentDefaultViewPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDocumentDefaultViewPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDocumentDefaultViewPropertyInfo = DOMDocumentK type AttrGetType DOMDocumentDefaultViewPropertyInfo = DOMDOMWindow type AttrLabel DOMDocumentDefaultViewPropertyInfo = "DOMDocument::default-view" attrGet _ = getDOMDocumentDefaultView attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "doctype" -- Type: TInterface "WebKit" "DOMDocumentType" -- Flags: [PropertyReadable] getDOMDocumentDoctype :: (MonadIO m, DOMDocumentK o) => o -> m DOMDocumentType getDOMDocumentDoctype obj = liftIO $ getObjectPropertyObject obj "doctype" DOMDocumentType data DOMDocumentDoctypePropertyInfo instance AttrInfo DOMDocumentDoctypePropertyInfo where type AttrAllowedOps DOMDocumentDoctypePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDocumentDoctypePropertyInfo = (~) () type AttrBaseTypeConstraint DOMDocumentDoctypePropertyInfo = DOMDocumentK type AttrGetType DOMDocumentDoctypePropertyInfo = DOMDocumentType type AttrLabel DOMDocumentDoctypePropertyInfo = "DOMDocument::doctype" attrGet _ = getDOMDocumentDoctype attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "document-element" -- Type: TInterface "WebKit" "DOMElement" -- Flags: [PropertyReadable] getDOMDocumentDocumentElement :: (MonadIO m, DOMDocumentK o) => o -> m DOMElement getDOMDocumentDocumentElement obj = liftIO $ getObjectPropertyObject obj "document-element" DOMElement data DOMDocumentDocumentElementPropertyInfo instance AttrInfo DOMDocumentDocumentElementPropertyInfo where type AttrAllowedOps DOMDocumentDocumentElementPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDocumentDocumentElementPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDocumentDocumentElementPropertyInfo = DOMDocumentK type AttrGetType DOMDocumentDocumentElementPropertyInfo = DOMElement type AttrLabel DOMDocumentDocumentElementPropertyInfo = "DOMDocument::document-element" attrGet _ = getDOMDocumentDocumentElement attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "document-uri" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMDocumentDocumentUri :: (MonadIO m, DOMDocumentK o) => o -> m T.Text getDOMDocumentDocumentUri obj = liftIO $ getObjectPropertyString obj "document-uri" setDOMDocumentDocumentUri :: (MonadIO m, DOMDocumentK o) => o -> T.Text -> m () setDOMDocumentDocumentUri obj val = liftIO $ setObjectPropertyString obj "document-uri" val constructDOMDocumentDocumentUri :: T.Text -> IO ([Char], GValue) constructDOMDocumentDocumentUri val = constructObjectPropertyString "document-uri" val data DOMDocumentDocumentUriPropertyInfo instance AttrInfo DOMDocumentDocumentUriPropertyInfo where type AttrAllowedOps DOMDocumentDocumentUriPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMDocumentDocumentUriPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMDocumentDocumentUriPropertyInfo = DOMDocumentK type AttrGetType DOMDocumentDocumentUriPropertyInfo = T.Text type AttrLabel DOMDocumentDocumentUriPropertyInfo = "DOMDocument::document-uri" attrGet _ = getDOMDocumentDocumentUri attrSet _ = setDOMDocumentDocumentUri attrConstruct _ = constructDOMDocumentDocumentUri -- VVV Prop "domain" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMDocumentDomain :: (MonadIO m, DOMDocumentK o) => o -> m T.Text getDOMDocumentDomain obj = liftIO $ getObjectPropertyString obj "domain" data DOMDocumentDomainPropertyInfo instance AttrInfo DOMDocumentDomainPropertyInfo where type AttrAllowedOps DOMDocumentDomainPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDocumentDomainPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDocumentDomainPropertyInfo = DOMDocumentK type AttrGetType DOMDocumentDomainPropertyInfo = T.Text type AttrLabel DOMDocumentDomainPropertyInfo = "DOMDocument::domain" attrGet _ = getDOMDocumentDomain attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "forms" -- Type: TInterface "WebKit" "DOMHTMLCollection" -- Flags: [PropertyReadable] getDOMDocumentForms :: (MonadIO m, DOMDocumentK o) => o -> m DOMHTMLCollection getDOMDocumentForms obj = liftIO $ getObjectPropertyObject obj "forms" DOMHTMLCollection data DOMDocumentFormsPropertyInfo instance AttrInfo DOMDocumentFormsPropertyInfo where type AttrAllowedOps DOMDocumentFormsPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDocumentFormsPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDocumentFormsPropertyInfo = DOMDocumentK type AttrGetType DOMDocumentFormsPropertyInfo = DOMHTMLCollection type AttrLabel DOMDocumentFormsPropertyInfo = "DOMDocument::forms" attrGet _ = getDOMDocumentForms attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "head" -- Type: TInterface "WebKit" "DOMHTMLHeadElement" -- Flags: [PropertyReadable] getDOMDocumentHead :: (MonadIO m, DOMDocumentK o) => o -> m DOMHTMLHeadElement getDOMDocumentHead obj = liftIO $ getObjectPropertyObject obj "head" DOMHTMLHeadElement data DOMDocumentHeadPropertyInfo instance AttrInfo DOMDocumentHeadPropertyInfo where type AttrAllowedOps DOMDocumentHeadPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDocumentHeadPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDocumentHeadPropertyInfo = DOMDocumentK type AttrGetType DOMDocumentHeadPropertyInfo = DOMHTMLHeadElement type AttrLabel DOMDocumentHeadPropertyInfo = "DOMDocument::head" attrGet _ = getDOMDocumentHead attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "hidden" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMDocumentHidden :: (MonadIO m, DOMDocumentK o) => o -> m Bool getDOMDocumentHidden obj = liftIO $ getObjectPropertyBool obj "hidden" data DOMDocumentHiddenPropertyInfo instance AttrInfo DOMDocumentHiddenPropertyInfo where type AttrAllowedOps DOMDocumentHiddenPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDocumentHiddenPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDocumentHiddenPropertyInfo = DOMDocumentK type AttrGetType DOMDocumentHiddenPropertyInfo = Bool type AttrLabel DOMDocumentHiddenPropertyInfo = "DOMDocument::hidden" attrGet _ = getDOMDocumentHidden attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "images" -- Type: TInterface "WebKit" "DOMHTMLCollection" -- Flags: [PropertyReadable] getDOMDocumentImages :: (MonadIO m, DOMDocumentK o) => o -> m DOMHTMLCollection getDOMDocumentImages obj = liftIO $ getObjectPropertyObject obj "images" DOMHTMLCollection data DOMDocumentImagesPropertyInfo instance AttrInfo DOMDocumentImagesPropertyInfo where type AttrAllowedOps DOMDocumentImagesPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDocumentImagesPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDocumentImagesPropertyInfo = DOMDocumentK type AttrGetType DOMDocumentImagesPropertyInfo = DOMHTMLCollection type AttrLabel DOMDocumentImagesPropertyInfo = "DOMDocument::images" attrGet _ = getDOMDocumentImages attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "implementation" -- Type: TInterface "WebKit" "DOMDOMImplementation" -- Flags: [PropertyReadable] getDOMDocumentImplementation :: (MonadIO m, DOMDocumentK o) => o -> m DOMDOMImplementation getDOMDocumentImplementation obj = liftIO $ getObjectPropertyObject obj "implementation" DOMDOMImplementation data DOMDocumentImplementationPropertyInfo instance AttrInfo DOMDocumentImplementationPropertyInfo where type AttrAllowedOps DOMDocumentImplementationPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDocumentImplementationPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDocumentImplementationPropertyInfo = DOMDocumentK type AttrGetType DOMDocumentImplementationPropertyInfo = DOMDOMImplementation type AttrLabel DOMDocumentImplementationPropertyInfo = "DOMDocument::implementation" attrGet _ = getDOMDocumentImplementation attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "input-encoding" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMDocumentInputEncoding :: (MonadIO m, DOMDocumentK o) => o -> m T.Text getDOMDocumentInputEncoding obj = liftIO $ getObjectPropertyString obj "input-encoding" data DOMDocumentInputEncodingPropertyInfo instance AttrInfo DOMDocumentInputEncodingPropertyInfo where type AttrAllowedOps DOMDocumentInputEncodingPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDocumentInputEncodingPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDocumentInputEncodingPropertyInfo = DOMDocumentK type AttrGetType DOMDocumentInputEncodingPropertyInfo = T.Text type AttrLabel DOMDocumentInputEncodingPropertyInfo = "DOMDocument::input-encoding" attrGet _ = getDOMDocumentInputEncoding attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "last-modified" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMDocumentLastModified :: (MonadIO m, DOMDocumentK o) => o -> m T.Text getDOMDocumentLastModified obj = liftIO $ getObjectPropertyString obj "last-modified" data DOMDocumentLastModifiedPropertyInfo instance AttrInfo DOMDocumentLastModifiedPropertyInfo where type AttrAllowedOps DOMDocumentLastModifiedPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDocumentLastModifiedPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDocumentLastModifiedPropertyInfo = DOMDocumentK type AttrGetType DOMDocumentLastModifiedPropertyInfo = T.Text type AttrLabel DOMDocumentLastModifiedPropertyInfo = "DOMDocument::last-modified" attrGet _ = getDOMDocumentLastModified attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "links" -- Type: TInterface "WebKit" "DOMHTMLCollection" -- Flags: [PropertyReadable] getDOMDocumentLinks :: (MonadIO m, DOMDocumentK o) => o -> m DOMHTMLCollection getDOMDocumentLinks obj = liftIO $ getObjectPropertyObject obj "links" DOMHTMLCollection data DOMDocumentLinksPropertyInfo instance AttrInfo DOMDocumentLinksPropertyInfo where type AttrAllowedOps DOMDocumentLinksPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDocumentLinksPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDocumentLinksPropertyInfo = DOMDocumentK type AttrGetType DOMDocumentLinksPropertyInfo = DOMHTMLCollection type AttrLabel DOMDocumentLinksPropertyInfo = "DOMDocument::links" attrGet _ = getDOMDocumentLinks attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "preferred-stylesheet-set" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMDocumentPreferredStylesheetSet :: (MonadIO m, DOMDocumentK o) => o -> m T.Text getDOMDocumentPreferredStylesheetSet obj = liftIO $ getObjectPropertyString obj "preferred-stylesheet-set" data DOMDocumentPreferredStylesheetSetPropertyInfo instance AttrInfo DOMDocumentPreferredStylesheetSetPropertyInfo where type AttrAllowedOps DOMDocumentPreferredStylesheetSetPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDocumentPreferredStylesheetSetPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDocumentPreferredStylesheetSetPropertyInfo = DOMDocumentK type AttrGetType DOMDocumentPreferredStylesheetSetPropertyInfo = T.Text type AttrLabel DOMDocumentPreferredStylesheetSetPropertyInfo = "DOMDocument::preferred-stylesheet-set" attrGet _ = getDOMDocumentPreferredStylesheetSet attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "ready-state" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMDocumentReadyState :: (MonadIO m, DOMDocumentK o) => o -> m T.Text getDOMDocumentReadyState obj = liftIO $ getObjectPropertyString obj "ready-state" data DOMDocumentReadyStatePropertyInfo instance AttrInfo DOMDocumentReadyStatePropertyInfo where type AttrAllowedOps DOMDocumentReadyStatePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDocumentReadyStatePropertyInfo = (~) () type AttrBaseTypeConstraint DOMDocumentReadyStatePropertyInfo = DOMDocumentK type AttrGetType DOMDocumentReadyStatePropertyInfo = T.Text type AttrLabel DOMDocumentReadyStatePropertyInfo = "DOMDocument::ready-state" attrGet _ = getDOMDocumentReadyState attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "referrer" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMDocumentReferrer :: (MonadIO m, DOMDocumentK o) => o -> m T.Text getDOMDocumentReferrer obj = liftIO $ getObjectPropertyString obj "referrer" data DOMDocumentReferrerPropertyInfo instance AttrInfo DOMDocumentReferrerPropertyInfo where type AttrAllowedOps DOMDocumentReferrerPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDocumentReferrerPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDocumentReferrerPropertyInfo = DOMDocumentK type AttrGetType DOMDocumentReferrerPropertyInfo = T.Text type AttrLabel DOMDocumentReferrerPropertyInfo = "DOMDocument::referrer" attrGet _ = getDOMDocumentReferrer attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "security-policy" -- Type: TInterface "WebKit" "DOMDOMSecurityPolicy" -- Flags: [PropertyReadable] getDOMDocumentSecurityPolicy :: (MonadIO m, DOMDocumentK o) => o -> m DOMDOMSecurityPolicy getDOMDocumentSecurityPolicy obj = liftIO $ getObjectPropertyObject obj "security-policy" DOMDOMSecurityPolicy data DOMDocumentSecurityPolicyPropertyInfo instance AttrInfo DOMDocumentSecurityPolicyPropertyInfo where type AttrAllowedOps DOMDocumentSecurityPolicyPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDocumentSecurityPolicyPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDocumentSecurityPolicyPropertyInfo = DOMDocumentK type AttrGetType DOMDocumentSecurityPolicyPropertyInfo = DOMDOMSecurityPolicy type AttrLabel DOMDocumentSecurityPolicyPropertyInfo = "DOMDocument::security-policy" attrGet _ = getDOMDocumentSecurityPolicy attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "selected-stylesheet-set" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMDocumentSelectedStylesheetSet :: (MonadIO m, DOMDocumentK o) => o -> m T.Text getDOMDocumentSelectedStylesheetSet obj = liftIO $ getObjectPropertyString obj "selected-stylesheet-set" setDOMDocumentSelectedStylesheetSet :: (MonadIO m, DOMDocumentK o) => o -> T.Text -> m () setDOMDocumentSelectedStylesheetSet obj val = liftIO $ setObjectPropertyString obj "selected-stylesheet-set" val constructDOMDocumentSelectedStylesheetSet :: T.Text -> IO ([Char], GValue) constructDOMDocumentSelectedStylesheetSet val = constructObjectPropertyString "selected-stylesheet-set" val data DOMDocumentSelectedStylesheetSetPropertyInfo instance AttrInfo DOMDocumentSelectedStylesheetSetPropertyInfo where type AttrAllowedOps DOMDocumentSelectedStylesheetSetPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMDocumentSelectedStylesheetSetPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMDocumentSelectedStylesheetSetPropertyInfo = DOMDocumentK type AttrGetType DOMDocumentSelectedStylesheetSetPropertyInfo = T.Text type AttrLabel DOMDocumentSelectedStylesheetSetPropertyInfo = "DOMDocument::selected-stylesheet-set" attrGet _ = getDOMDocumentSelectedStylesheetSet attrSet _ = setDOMDocumentSelectedStylesheetSet attrConstruct _ = constructDOMDocumentSelectedStylesheetSet -- VVV Prop "style-sheets" -- Type: TInterface "WebKit" "DOMStyleSheetList" -- Flags: [PropertyReadable] getDOMDocumentStyleSheets :: (MonadIO m, DOMDocumentK o) => o -> m DOMStyleSheetList getDOMDocumentStyleSheets obj = liftIO $ getObjectPropertyObject obj "style-sheets" DOMStyleSheetList data DOMDocumentStyleSheetsPropertyInfo instance AttrInfo DOMDocumentStyleSheetsPropertyInfo where type AttrAllowedOps DOMDocumentStyleSheetsPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDocumentStyleSheetsPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDocumentStyleSheetsPropertyInfo = DOMDocumentK type AttrGetType DOMDocumentStyleSheetsPropertyInfo = DOMStyleSheetList type AttrLabel DOMDocumentStyleSheetsPropertyInfo = "DOMDocument::style-sheets" attrGet _ = getDOMDocumentStyleSheets attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "title" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMDocumentTitle :: (MonadIO m, DOMDocumentK o) => o -> m T.Text getDOMDocumentTitle obj = liftIO $ getObjectPropertyString obj "title" setDOMDocumentTitle :: (MonadIO m, DOMDocumentK o) => o -> T.Text -> m () setDOMDocumentTitle obj val = liftIO $ setObjectPropertyString obj "title" val constructDOMDocumentTitle :: T.Text -> IO ([Char], GValue) constructDOMDocumentTitle val = constructObjectPropertyString "title" val data DOMDocumentTitlePropertyInfo instance AttrInfo DOMDocumentTitlePropertyInfo where type AttrAllowedOps DOMDocumentTitlePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMDocumentTitlePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMDocumentTitlePropertyInfo = DOMDocumentK type AttrGetType DOMDocumentTitlePropertyInfo = T.Text type AttrLabel DOMDocumentTitlePropertyInfo = "DOMDocument::title" attrGet _ = getDOMDocumentTitle attrSet _ = setDOMDocumentTitle attrConstruct _ = constructDOMDocumentTitle -- VVV Prop "url" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMDocumentUrl :: (MonadIO m, DOMDocumentK o) => o -> m T.Text getDOMDocumentUrl obj = liftIO $ getObjectPropertyString obj "url" data DOMDocumentUrlPropertyInfo instance AttrInfo DOMDocumentUrlPropertyInfo where type AttrAllowedOps DOMDocumentUrlPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDocumentUrlPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDocumentUrlPropertyInfo = DOMDocumentK type AttrGetType DOMDocumentUrlPropertyInfo = T.Text type AttrLabel DOMDocumentUrlPropertyInfo = "DOMDocument::url" attrGet _ = getDOMDocumentUrl attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "visibility-state" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMDocumentVisibilityState :: (MonadIO m, DOMDocumentK o) => o -> m T.Text getDOMDocumentVisibilityState obj = liftIO $ getObjectPropertyString obj "visibility-state" data DOMDocumentVisibilityStatePropertyInfo instance AttrInfo DOMDocumentVisibilityStatePropertyInfo where type AttrAllowedOps DOMDocumentVisibilityStatePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDocumentVisibilityStatePropertyInfo = (~) () type AttrBaseTypeConstraint DOMDocumentVisibilityStatePropertyInfo = DOMDocumentK type AttrGetType DOMDocumentVisibilityStatePropertyInfo = T.Text type AttrLabel DOMDocumentVisibilityStatePropertyInfo = "DOMDocument::visibility-state" attrGet _ = getDOMDocumentVisibilityState attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "webkit-current-full-screen-element" -- Type: TInterface "WebKit" "DOMElement" -- Flags: [PropertyReadable] getDOMDocumentWebkitCurrentFullScreenElement :: (MonadIO m, DOMDocumentK o) => o -> m DOMElement getDOMDocumentWebkitCurrentFullScreenElement obj = liftIO $ getObjectPropertyObject obj "webkit-current-full-screen-element" DOMElement data DOMDocumentWebkitCurrentFullScreenElementPropertyInfo instance AttrInfo DOMDocumentWebkitCurrentFullScreenElementPropertyInfo where type AttrAllowedOps DOMDocumentWebkitCurrentFullScreenElementPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDocumentWebkitCurrentFullScreenElementPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDocumentWebkitCurrentFullScreenElementPropertyInfo = DOMDocumentK type AttrGetType DOMDocumentWebkitCurrentFullScreenElementPropertyInfo = DOMElement type AttrLabel DOMDocumentWebkitCurrentFullScreenElementPropertyInfo = "DOMDocument::webkit-current-full-screen-element" attrGet _ = getDOMDocumentWebkitCurrentFullScreenElement attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "webkit-full-screen-keyboard-input-allowed" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMDocumentWebkitFullScreenKeyboardInputAllowed :: (MonadIO m, DOMDocumentK o) => o -> m Bool getDOMDocumentWebkitFullScreenKeyboardInputAllowed obj = liftIO $ getObjectPropertyBool obj "webkit-full-screen-keyboard-input-allowed" data DOMDocumentWebkitFullScreenKeyboardInputAllowedPropertyInfo instance AttrInfo DOMDocumentWebkitFullScreenKeyboardInputAllowedPropertyInfo where type AttrAllowedOps DOMDocumentWebkitFullScreenKeyboardInputAllowedPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDocumentWebkitFullScreenKeyboardInputAllowedPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDocumentWebkitFullScreenKeyboardInputAllowedPropertyInfo = DOMDocumentK type AttrGetType DOMDocumentWebkitFullScreenKeyboardInputAllowedPropertyInfo = Bool type AttrLabel DOMDocumentWebkitFullScreenKeyboardInputAllowedPropertyInfo = "DOMDocument::webkit-full-screen-keyboard-input-allowed" attrGet _ = getDOMDocumentWebkitFullScreenKeyboardInputAllowed attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "webkit-fullscreen-element" -- Type: TInterface "WebKit" "DOMElement" -- Flags: [PropertyReadable] getDOMDocumentWebkitFullscreenElement :: (MonadIO m, DOMDocumentK o) => o -> m DOMElement getDOMDocumentWebkitFullscreenElement obj = liftIO $ getObjectPropertyObject obj "webkit-fullscreen-element" DOMElement data DOMDocumentWebkitFullscreenElementPropertyInfo instance AttrInfo DOMDocumentWebkitFullscreenElementPropertyInfo where type AttrAllowedOps DOMDocumentWebkitFullscreenElementPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDocumentWebkitFullscreenElementPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDocumentWebkitFullscreenElementPropertyInfo = DOMDocumentK type AttrGetType DOMDocumentWebkitFullscreenElementPropertyInfo = DOMElement type AttrLabel DOMDocumentWebkitFullscreenElementPropertyInfo = "DOMDocument::webkit-fullscreen-element" attrGet _ = getDOMDocumentWebkitFullscreenElement attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "webkit-fullscreen-enabled" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMDocumentWebkitFullscreenEnabled :: (MonadIO m, DOMDocumentK o) => o -> m Bool getDOMDocumentWebkitFullscreenEnabled obj = liftIO $ getObjectPropertyBool obj "webkit-fullscreen-enabled" data DOMDocumentWebkitFullscreenEnabledPropertyInfo instance AttrInfo DOMDocumentWebkitFullscreenEnabledPropertyInfo where type AttrAllowedOps DOMDocumentWebkitFullscreenEnabledPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDocumentWebkitFullscreenEnabledPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDocumentWebkitFullscreenEnabledPropertyInfo = DOMDocumentK type AttrGetType DOMDocumentWebkitFullscreenEnabledPropertyInfo = Bool type AttrLabel DOMDocumentWebkitFullscreenEnabledPropertyInfo = "DOMDocument::webkit-fullscreen-enabled" attrGet _ = getDOMDocumentWebkitFullscreenEnabled attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "webkit-is-full-screen" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMDocumentWebkitIsFullScreen :: (MonadIO m, DOMDocumentK o) => o -> m Bool getDOMDocumentWebkitIsFullScreen obj = liftIO $ getObjectPropertyBool obj "webkit-is-full-screen" data DOMDocumentWebkitIsFullScreenPropertyInfo instance AttrInfo DOMDocumentWebkitIsFullScreenPropertyInfo where type AttrAllowedOps DOMDocumentWebkitIsFullScreenPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDocumentWebkitIsFullScreenPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDocumentWebkitIsFullScreenPropertyInfo = DOMDocumentK type AttrGetType DOMDocumentWebkitIsFullScreenPropertyInfo = Bool type AttrLabel DOMDocumentWebkitIsFullScreenPropertyInfo = "DOMDocument::webkit-is-full-screen" attrGet _ = getDOMDocumentWebkitIsFullScreen attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "webkit-pointer-lock-element" -- Type: TInterface "WebKit" "DOMElement" -- Flags: [PropertyReadable] getDOMDocumentWebkitPointerLockElement :: (MonadIO m, DOMDocumentK o) => o -> m DOMElement getDOMDocumentWebkitPointerLockElement obj = liftIO $ getObjectPropertyObject obj "webkit-pointer-lock-element" DOMElement data DOMDocumentWebkitPointerLockElementPropertyInfo instance AttrInfo DOMDocumentWebkitPointerLockElementPropertyInfo where type AttrAllowedOps DOMDocumentWebkitPointerLockElementPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDocumentWebkitPointerLockElementPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDocumentWebkitPointerLockElementPropertyInfo = DOMDocumentK type AttrGetType DOMDocumentWebkitPointerLockElementPropertyInfo = DOMElement type AttrLabel DOMDocumentWebkitPointerLockElementPropertyInfo = "DOMDocument::webkit-pointer-lock-element" attrGet _ = getDOMDocumentWebkitPointerLockElement attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "xml-encoding" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMDocumentXmlEncoding :: (MonadIO m, DOMDocumentK o) => o -> m T.Text getDOMDocumentXmlEncoding obj = liftIO $ getObjectPropertyString obj "xml-encoding" data DOMDocumentXmlEncodingPropertyInfo instance AttrInfo DOMDocumentXmlEncodingPropertyInfo where type AttrAllowedOps DOMDocumentXmlEncodingPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDocumentXmlEncodingPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDocumentXmlEncodingPropertyInfo = DOMDocumentK type AttrGetType DOMDocumentXmlEncodingPropertyInfo = T.Text type AttrLabel DOMDocumentXmlEncodingPropertyInfo = "DOMDocument::xml-encoding" attrGet _ = getDOMDocumentXmlEncoding attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "xml-standalone" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMDocumentXmlStandalone :: (MonadIO m, DOMDocumentK o) => o -> m Bool getDOMDocumentXmlStandalone obj = liftIO $ getObjectPropertyBool obj "xml-standalone" setDOMDocumentXmlStandalone :: (MonadIO m, DOMDocumentK o) => o -> Bool -> m () setDOMDocumentXmlStandalone obj val = liftIO $ setObjectPropertyBool obj "xml-standalone" val constructDOMDocumentXmlStandalone :: Bool -> IO ([Char], GValue) constructDOMDocumentXmlStandalone val = constructObjectPropertyBool "xml-standalone" val data DOMDocumentXmlStandalonePropertyInfo instance AttrInfo DOMDocumentXmlStandalonePropertyInfo where type AttrAllowedOps DOMDocumentXmlStandalonePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMDocumentXmlStandalonePropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMDocumentXmlStandalonePropertyInfo = DOMDocumentK type AttrGetType DOMDocumentXmlStandalonePropertyInfo = Bool type AttrLabel DOMDocumentXmlStandalonePropertyInfo = "DOMDocument::xml-standalone" attrGet _ = getDOMDocumentXmlStandalone attrSet _ = setDOMDocumentXmlStandalone attrConstruct _ = constructDOMDocumentXmlStandalone -- VVV Prop "xml-version" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMDocumentXmlVersion :: (MonadIO m, DOMDocumentK o) => o -> m T.Text getDOMDocumentXmlVersion obj = liftIO $ getObjectPropertyString obj "xml-version" setDOMDocumentXmlVersion :: (MonadIO m, DOMDocumentK o) => o -> T.Text -> m () setDOMDocumentXmlVersion obj val = liftIO $ setObjectPropertyString obj "xml-version" val constructDOMDocumentXmlVersion :: T.Text -> IO ([Char], GValue) constructDOMDocumentXmlVersion val = constructObjectPropertyString "xml-version" val data DOMDocumentXmlVersionPropertyInfo instance AttrInfo DOMDocumentXmlVersionPropertyInfo where type AttrAllowedOps DOMDocumentXmlVersionPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMDocumentXmlVersionPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMDocumentXmlVersionPropertyInfo = DOMDocumentK type AttrGetType DOMDocumentXmlVersionPropertyInfo = T.Text type AttrLabel DOMDocumentXmlVersionPropertyInfo = "DOMDocument::xml-version" attrGet _ = getDOMDocumentXmlVersion attrSet _ = setDOMDocumentXmlVersion attrConstruct _ = constructDOMDocumentXmlVersion type instance AttributeList DOMDocument = '[ '("anchors", DOMDocumentAnchorsPropertyInfo), '("applets", DOMDocumentAppletsPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("body", DOMDocumentBodyPropertyInfo), '("character-set", DOMDocumentCharacterSetPropertyInfo), '("charset", DOMDocumentCharsetPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("compat-mode", DOMDocumentCompatModePropertyInfo), '("cookie", DOMDocumentCookiePropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("current-script", DOMDocumentCurrentScriptPropertyInfo), '("default-charset", DOMDocumentDefaultCharsetPropertyInfo), '("default-view", DOMDocumentDefaultViewPropertyInfo), '("doctype", DOMDocumentDoctypePropertyInfo), '("document-element", DOMDocumentDocumentElementPropertyInfo), '("document-uri", DOMDocumentDocumentUriPropertyInfo), '("domain", DOMDocumentDomainPropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("forms", DOMDocumentFormsPropertyInfo), '("head", DOMDocumentHeadPropertyInfo), '("hidden", DOMDocumentHiddenPropertyInfo), '("images", DOMDocumentImagesPropertyInfo), '("implementation", DOMDocumentImplementationPropertyInfo), '("input-encoding", DOMDocumentInputEncodingPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-modified", DOMDocumentLastModifiedPropertyInfo), '("links", DOMDocumentLinksPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("preferred-stylesheet-set", DOMDocumentPreferredStylesheetSetPropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("ready-state", DOMDocumentReadyStatePropertyInfo), '("referrer", DOMDocumentReferrerPropertyInfo), '("security-policy", DOMDocumentSecurityPolicyPropertyInfo), '("selected-stylesheet-set", DOMDocumentSelectedStylesheetSetPropertyInfo), '("style-sheets", DOMDocumentStyleSheetsPropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("title", DOMDocumentTitlePropertyInfo), '("url", DOMDocumentUrlPropertyInfo), '("visibility-state", DOMDocumentVisibilityStatePropertyInfo), '("webkit-current-full-screen-element", DOMDocumentWebkitCurrentFullScreenElementPropertyInfo), '("webkit-full-screen-keyboard-input-allowed", DOMDocumentWebkitFullScreenKeyboardInputAllowedPropertyInfo), '("webkit-fullscreen-element", DOMDocumentWebkitFullscreenElementPropertyInfo), '("webkit-fullscreen-enabled", DOMDocumentWebkitFullscreenEnabledPropertyInfo), '("webkit-is-full-screen", DOMDocumentWebkitIsFullScreenPropertyInfo), '("webkit-pointer-lock-element", DOMDocumentWebkitPointerLockElementPropertyInfo), '("xml-encoding", DOMDocumentXmlEncodingPropertyInfo), '("xml-standalone", DOMDocumentXmlStandalonePropertyInfo), '("xml-version", DOMDocumentXmlVersionPropertyInfo)] type instance AttributeList DOMDocumentFragment = '[ '("base-uri", DOMNodeBaseUriPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo)] -- VVV Prop "entities" -- Type: TInterface "WebKit" "DOMNamedNodeMap" -- Flags: [PropertyReadable] getDOMDocumentTypeEntities :: (MonadIO m, DOMDocumentTypeK o) => o -> m DOMNamedNodeMap getDOMDocumentTypeEntities obj = liftIO $ getObjectPropertyObject obj "entities" DOMNamedNodeMap data DOMDocumentTypeEntitiesPropertyInfo instance AttrInfo DOMDocumentTypeEntitiesPropertyInfo where type AttrAllowedOps DOMDocumentTypeEntitiesPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDocumentTypeEntitiesPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDocumentTypeEntitiesPropertyInfo = DOMDocumentTypeK type AttrGetType DOMDocumentTypeEntitiesPropertyInfo = DOMNamedNodeMap type AttrLabel DOMDocumentTypeEntitiesPropertyInfo = "DOMDocumentType::entities" attrGet _ = getDOMDocumentTypeEntities attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "internal-subset" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMDocumentTypeInternalSubset :: (MonadIO m, DOMDocumentTypeK o) => o -> m T.Text getDOMDocumentTypeInternalSubset obj = liftIO $ getObjectPropertyString obj "internal-subset" data DOMDocumentTypeInternalSubsetPropertyInfo instance AttrInfo DOMDocumentTypeInternalSubsetPropertyInfo where type AttrAllowedOps DOMDocumentTypeInternalSubsetPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDocumentTypeInternalSubsetPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDocumentTypeInternalSubsetPropertyInfo = DOMDocumentTypeK type AttrGetType DOMDocumentTypeInternalSubsetPropertyInfo = T.Text type AttrLabel DOMDocumentTypeInternalSubsetPropertyInfo = "DOMDocumentType::internal-subset" attrGet _ = getDOMDocumentTypeInternalSubset attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "name" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMDocumentTypeName :: (MonadIO m, DOMDocumentTypeK o) => o -> m T.Text getDOMDocumentTypeName obj = liftIO $ getObjectPropertyString obj "name" data DOMDocumentTypeNamePropertyInfo instance AttrInfo DOMDocumentTypeNamePropertyInfo where type AttrAllowedOps DOMDocumentTypeNamePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDocumentTypeNamePropertyInfo = (~) () type AttrBaseTypeConstraint DOMDocumentTypeNamePropertyInfo = DOMDocumentTypeK type AttrGetType DOMDocumentTypeNamePropertyInfo = T.Text type AttrLabel DOMDocumentTypeNamePropertyInfo = "DOMDocumentType::name" attrGet _ = getDOMDocumentTypeName attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "notations" -- Type: TInterface "WebKit" "DOMNamedNodeMap" -- Flags: [PropertyReadable] getDOMDocumentTypeNotations :: (MonadIO m, DOMDocumentTypeK o) => o -> m DOMNamedNodeMap getDOMDocumentTypeNotations obj = liftIO $ getObjectPropertyObject obj "notations" DOMNamedNodeMap data DOMDocumentTypeNotationsPropertyInfo instance AttrInfo DOMDocumentTypeNotationsPropertyInfo where type AttrAllowedOps DOMDocumentTypeNotationsPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDocumentTypeNotationsPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDocumentTypeNotationsPropertyInfo = DOMDocumentTypeK type AttrGetType DOMDocumentTypeNotationsPropertyInfo = DOMNamedNodeMap type AttrLabel DOMDocumentTypeNotationsPropertyInfo = "DOMDocumentType::notations" attrGet _ = getDOMDocumentTypeNotations attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "public-id" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMDocumentTypePublicId :: (MonadIO m, DOMDocumentTypeK o) => o -> m T.Text getDOMDocumentTypePublicId obj = liftIO $ getObjectPropertyString obj "public-id" data DOMDocumentTypePublicIdPropertyInfo instance AttrInfo DOMDocumentTypePublicIdPropertyInfo where type AttrAllowedOps DOMDocumentTypePublicIdPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDocumentTypePublicIdPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDocumentTypePublicIdPropertyInfo = DOMDocumentTypeK type AttrGetType DOMDocumentTypePublicIdPropertyInfo = T.Text type AttrLabel DOMDocumentTypePublicIdPropertyInfo = "DOMDocumentType::public-id" attrGet _ = getDOMDocumentTypePublicId attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "system-id" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMDocumentTypeSystemId :: (MonadIO m, DOMDocumentTypeK o) => o -> m T.Text getDOMDocumentTypeSystemId obj = liftIO $ getObjectPropertyString obj "system-id" data DOMDocumentTypeSystemIdPropertyInfo instance AttrInfo DOMDocumentTypeSystemIdPropertyInfo where type AttrAllowedOps DOMDocumentTypeSystemIdPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMDocumentTypeSystemIdPropertyInfo = (~) () type AttrBaseTypeConstraint DOMDocumentTypeSystemIdPropertyInfo = DOMDocumentTypeK type AttrGetType DOMDocumentTypeSystemIdPropertyInfo = T.Text type AttrLabel DOMDocumentTypeSystemIdPropertyInfo = "DOMDocumentType::system-id" attrGet _ = getDOMDocumentTypeSystemId attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMDocumentType = '[ '("base-uri", DOMNodeBaseUriPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("entities", DOMDocumentTypeEntitiesPropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("internal-subset", DOMDocumentTypeInternalSubsetPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("name", DOMDocumentTypeNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("notations", DOMDocumentTypeNotationsPropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("public-id", DOMDocumentTypePublicIdPropertyInfo), '("system-id", DOMDocumentTypeSystemIdPropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo)] -- VVV Prop "attributes" -- Type: TInterface "WebKit" "DOMNamedNodeMap" -- Flags: [PropertyReadable] getDOMElementAttributes :: (MonadIO m, DOMElementK o) => o -> m DOMNamedNodeMap getDOMElementAttributes obj = liftIO $ getObjectPropertyObject obj "attributes" DOMNamedNodeMap data DOMElementAttributesPropertyInfo instance AttrInfo DOMElementAttributesPropertyInfo where type AttrAllowedOps DOMElementAttributesPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMElementAttributesPropertyInfo = (~) () type AttrBaseTypeConstraint DOMElementAttributesPropertyInfo = DOMElementK type AttrGetType DOMElementAttributesPropertyInfo = DOMNamedNodeMap type AttrLabel DOMElementAttributesPropertyInfo = "DOMElement::attributes" attrGet _ = getDOMElementAttributes attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "child-element-count" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMElementChildElementCount :: (MonadIO m, DOMElementK o) => o -> m Word64 getDOMElementChildElementCount obj = liftIO $ getObjectPropertyUInt64 obj "child-element-count" data DOMElementChildElementCountPropertyInfo instance AttrInfo DOMElementChildElementCountPropertyInfo where type AttrAllowedOps DOMElementChildElementCountPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMElementChildElementCountPropertyInfo = (~) () type AttrBaseTypeConstraint DOMElementChildElementCountPropertyInfo = DOMElementK type AttrGetType DOMElementChildElementCountPropertyInfo = Word64 type AttrLabel DOMElementChildElementCountPropertyInfo = "DOMElement::child-element-count" attrGet _ = getDOMElementChildElementCount attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "class-list" -- Type: TInterface "WebKit" "DOMDOMTokenList" -- Flags: [PropertyReadable] getDOMElementClassList :: (MonadIO m, DOMElementK o) => o -> m DOMDOMTokenList getDOMElementClassList obj = liftIO $ getObjectPropertyObject obj "class-list" DOMDOMTokenList data DOMElementClassListPropertyInfo instance AttrInfo DOMElementClassListPropertyInfo where type AttrAllowedOps DOMElementClassListPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMElementClassListPropertyInfo = (~) () type AttrBaseTypeConstraint DOMElementClassListPropertyInfo = DOMElementK type AttrGetType DOMElementClassListPropertyInfo = DOMDOMTokenList type AttrLabel DOMElementClassListPropertyInfo = "DOMElement::class-list" attrGet _ = getDOMElementClassList attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "class-name" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMElementClassName :: (MonadIO m, DOMElementK o) => o -> m T.Text getDOMElementClassName obj = liftIO $ getObjectPropertyString obj "class-name" setDOMElementClassName :: (MonadIO m, DOMElementK o) => o -> T.Text -> m () setDOMElementClassName obj val = liftIO $ setObjectPropertyString obj "class-name" val constructDOMElementClassName :: T.Text -> IO ([Char], GValue) constructDOMElementClassName val = constructObjectPropertyString "class-name" val data DOMElementClassNamePropertyInfo instance AttrInfo DOMElementClassNamePropertyInfo where type AttrAllowedOps DOMElementClassNamePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMElementClassNamePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMElementClassNamePropertyInfo = DOMElementK type AttrGetType DOMElementClassNamePropertyInfo = T.Text type AttrLabel DOMElementClassNamePropertyInfo = "DOMElement::class-name" attrGet _ = getDOMElementClassName attrSet _ = setDOMElementClassName attrConstruct _ = constructDOMElementClassName -- VVV Prop "client-height" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMElementClientHeight :: (MonadIO m, DOMElementK o) => o -> m Int64 getDOMElementClientHeight obj = liftIO $ getObjectPropertyInt64 obj "client-height" data DOMElementClientHeightPropertyInfo instance AttrInfo DOMElementClientHeightPropertyInfo where type AttrAllowedOps DOMElementClientHeightPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMElementClientHeightPropertyInfo = (~) () type AttrBaseTypeConstraint DOMElementClientHeightPropertyInfo = DOMElementK type AttrGetType DOMElementClientHeightPropertyInfo = Int64 type AttrLabel DOMElementClientHeightPropertyInfo = "DOMElement::client-height" attrGet _ = getDOMElementClientHeight attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "client-left" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMElementClientLeft :: (MonadIO m, DOMElementK o) => o -> m Int64 getDOMElementClientLeft obj = liftIO $ getObjectPropertyInt64 obj "client-left" data DOMElementClientLeftPropertyInfo instance AttrInfo DOMElementClientLeftPropertyInfo where type AttrAllowedOps DOMElementClientLeftPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMElementClientLeftPropertyInfo = (~) () type AttrBaseTypeConstraint DOMElementClientLeftPropertyInfo = DOMElementK type AttrGetType DOMElementClientLeftPropertyInfo = Int64 type AttrLabel DOMElementClientLeftPropertyInfo = "DOMElement::client-left" attrGet _ = getDOMElementClientLeft attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "client-top" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMElementClientTop :: (MonadIO m, DOMElementK o) => o -> m Int64 getDOMElementClientTop obj = liftIO $ getObjectPropertyInt64 obj "client-top" data DOMElementClientTopPropertyInfo instance AttrInfo DOMElementClientTopPropertyInfo where type AttrAllowedOps DOMElementClientTopPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMElementClientTopPropertyInfo = (~) () type AttrBaseTypeConstraint DOMElementClientTopPropertyInfo = DOMElementK type AttrGetType DOMElementClientTopPropertyInfo = Int64 type AttrLabel DOMElementClientTopPropertyInfo = "DOMElement::client-top" attrGet _ = getDOMElementClientTop attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "client-width" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMElementClientWidth :: (MonadIO m, DOMElementK o) => o -> m Int64 getDOMElementClientWidth obj = liftIO $ getObjectPropertyInt64 obj "client-width" data DOMElementClientWidthPropertyInfo instance AttrInfo DOMElementClientWidthPropertyInfo where type AttrAllowedOps DOMElementClientWidthPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMElementClientWidthPropertyInfo = (~) () type AttrBaseTypeConstraint DOMElementClientWidthPropertyInfo = DOMElementK type AttrGetType DOMElementClientWidthPropertyInfo = Int64 type AttrLabel DOMElementClientWidthPropertyInfo = "DOMElement::client-width" attrGet _ = getDOMElementClientWidth attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "first-element-child" -- Type: TInterface "WebKit" "DOMElement" -- Flags: [PropertyReadable] getDOMElementFirstElementChild :: (MonadIO m, DOMElementK o) => o -> m DOMElement getDOMElementFirstElementChild obj = liftIO $ getObjectPropertyObject obj "first-element-child" DOMElement data DOMElementFirstElementChildPropertyInfo instance AttrInfo DOMElementFirstElementChildPropertyInfo where type AttrAllowedOps DOMElementFirstElementChildPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMElementFirstElementChildPropertyInfo = (~) () type AttrBaseTypeConstraint DOMElementFirstElementChildPropertyInfo = DOMElementK type AttrGetType DOMElementFirstElementChildPropertyInfo = DOMElement type AttrLabel DOMElementFirstElementChildPropertyInfo = "DOMElement::first-element-child" attrGet _ = getDOMElementFirstElementChild attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "id" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMElementId :: (MonadIO m, DOMElementK o) => o -> m T.Text getDOMElementId obj = liftIO $ getObjectPropertyString obj "id" setDOMElementId :: (MonadIO m, DOMElementK o) => o -> T.Text -> m () setDOMElementId obj val = liftIO $ setObjectPropertyString obj "id" val constructDOMElementId :: T.Text -> IO ([Char], GValue) constructDOMElementId val = constructObjectPropertyString "id" val data DOMElementIdPropertyInfo instance AttrInfo DOMElementIdPropertyInfo where type AttrAllowedOps DOMElementIdPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMElementIdPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMElementIdPropertyInfo = DOMElementK type AttrGetType DOMElementIdPropertyInfo = T.Text type AttrLabel DOMElementIdPropertyInfo = "DOMElement::id" attrGet _ = getDOMElementId attrSet _ = setDOMElementId attrConstruct _ = constructDOMElementId -- VVV Prop "last-element-child" -- Type: TInterface "WebKit" "DOMElement" -- Flags: [PropertyReadable] getDOMElementLastElementChild :: (MonadIO m, DOMElementK o) => o -> m DOMElement getDOMElementLastElementChild obj = liftIO $ getObjectPropertyObject obj "last-element-child" DOMElement data DOMElementLastElementChildPropertyInfo instance AttrInfo DOMElementLastElementChildPropertyInfo where type AttrAllowedOps DOMElementLastElementChildPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMElementLastElementChildPropertyInfo = (~) () type AttrBaseTypeConstraint DOMElementLastElementChildPropertyInfo = DOMElementK type AttrGetType DOMElementLastElementChildPropertyInfo = DOMElement type AttrLabel DOMElementLastElementChildPropertyInfo = "DOMElement::last-element-child" attrGet _ = getDOMElementLastElementChild attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "next-element-sibling" -- Type: TInterface "WebKit" "DOMElement" -- Flags: [PropertyReadable] getDOMElementNextElementSibling :: (MonadIO m, DOMElementK o) => o -> m DOMElement getDOMElementNextElementSibling obj = liftIO $ getObjectPropertyObject obj "next-element-sibling" DOMElement data DOMElementNextElementSiblingPropertyInfo instance AttrInfo DOMElementNextElementSiblingPropertyInfo where type AttrAllowedOps DOMElementNextElementSiblingPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMElementNextElementSiblingPropertyInfo = (~) () type AttrBaseTypeConstraint DOMElementNextElementSiblingPropertyInfo = DOMElementK type AttrGetType DOMElementNextElementSiblingPropertyInfo = DOMElement type AttrLabel DOMElementNextElementSiblingPropertyInfo = "DOMElement::next-element-sibling" attrGet _ = getDOMElementNextElementSibling attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "offset-height" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMElementOffsetHeight :: (MonadIO m, DOMElementK o) => o -> m Int64 getDOMElementOffsetHeight obj = liftIO $ getObjectPropertyInt64 obj "offset-height" data DOMElementOffsetHeightPropertyInfo instance AttrInfo DOMElementOffsetHeightPropertyInfo where type AttrAllowedOps DOMElementOffsetHeightPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMElementOffsetHeightPropertyInfo = (~) () type AttrBaseTypeConstraint DOMElementOffsetHeightPropertyInfo = DOMElementK type AttrGetType DOMElementOffsetHeightPropertyInfo = Int64 type AttrLabel DOMElementOffsetHeightPropertyInfo = "DOMElement::offset-height" attrGet _ = getDOMElementOffsetHeight attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "offset-left" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMElementOffsetLeft :: (MonadIO m, DOMElementK o) => o -> m Int64 getDOMElementOffsetLeft obj = liftIO $ getObjectPropertyInt64 obj "offset-left" data DOMElementOffsetLeftPropertyInfo instance AttrInfo DOMElementOffsetLeftPropertyInfo where type AttrAllowedOps DOMElementOffsetLeftPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMElementOffsetLeftPropertyInfo = (~) () type AttrBaseTypeConstraint DOMElementOffsetLeftPropertyInfo = DOMElementK type AttrGetType DOMElementOffsetLeftPropertyInfo = Int64 type AttrLabel DOMElementOffsetLeftPropertyInfo = "DOMElement::offset-left" attrGet _ = getDOMElementOffsetLeft attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "offset-parent" -- Type: TInterface "WebKit" "DOMElement" -- Flags: [PropertyReadable] getDOMElementOffsetParent :: (MonadIO m, DOMElementK o) => o -> m DOMElement getDOMElementOffsetParent obj = liftIO $ getObjectPropertyObject obj "offset-parent" DOMElement data DOMElementOffsetParentPropertyInfo instance AttrInfo DOMElementOffsetParentPropertyInfo where type AttrAllowedOps DOMElementOffsetParentPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMElementOffsetParentPropertyInfo = (~) () type AttrBaseTypeConstraint DOMElementOffsetParentPropertyInfo = DOMElementK type AttrGetType DOMElementOffsetParentPropertyInfo = DOMElement type AttrLabel DOMElementOffsetParentPropertyInfo = "DOMElement::offset-parent" attrGet _ = getDOMElementOffsetParent attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "offset-top" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMElementOffsetTop :: (MonadIO m, DOMElementK o) => o -> m Int64 getDOMElementOffsetTop obj = liftIO $ getObjectPropertyInt64 obj "offset-top" data DOMElementOffsetTopPropertyInfo instance AttrInfo DOMElementOffsetTopPropertyInfo where type AttrAllowedOps DOMElementOffsetTopPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMElementOffsetTopPropertyInfo = (~) () type AttrBaseTypeConstraint DOMElementOffsetTopPropertyInfo = DOMElementK type AttrGetType DOMElementOffsetTopPropertyInfo = Int64 type AttrLabel DOMElementOffsetTopPropertyInfo = "DOMElement::offset-top" attrGet _ = getDOMElementOffsetTop attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "offset-width" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMElementOffsetWidth :: (MonadIO m, DOMElementK o) => o -> m Int64 getDOMElementOffsetWidth obj = liftIO $ getObjectPropertyInt64 obj "offset-width" data DOMElementOffsetWidthPropertyInfo instance AttrInfo DOMElementOffsetWidthPropertyInfo where type AttrAllowedOps DOMElementOffsetWidthPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMElementOffsetWidthPropertyInfo = (~) () type AttrBaseTypeConstraint DOMElementOffsetWidthPropertyInfo = DOMElementK type AttrGetType DOMElementOffsetWidthPropertyInfo = Int64 type AttrLabel DOMElementOffsetWidthPropertyInfo = "DOMElement::offset-width" attrGet _ = getDOMElementOffsetWidth attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "previous-element-sibling" -- Type: TInterface "WebKit" "DOMElement" -- Flags: [PropertyReadable] getDOMElementPreviousElementSibling :: (MonadIO m, DOMElementK o) => o -> m DOMElement getDOMElementPreviousElementSibling obj = liftIO $ getObjectPropertyObject obj "previous-element-sibling" DOMElement data DOMElementPreviousElementSiblingPropertyInfo instance AttrInfo DOMElementPreviousElementSiblingPropertyInfo where type AttrAllowedOps DOMElementPreviousElementSiblingPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMElementPreviousElementSiblingPropertyInfo = (~) () type AttrBaseTypeConstraint DOMElementPreviousElementSiblingPropertyInfo = DOMElementK type AttrGetType DOMElementPreviousElementSiblingPropertyInfo = DOMElement type AttrLabel DOMElementPreviousElementSiblingPropertyInfo = "DOMElement::previous-element-sibling" attrGet _ = getDOMElementPreviousElementSibling attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "scroll-height" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMElementScrollHeight :: (MonadIO m, DOMElementK o) => o -> m Int64 getDOMElementScrollHeight obj = liftIO $ getObjectPropertyInt64 obj "scroll-height" data DOMElementScrollHeightPropertyInfo instance AttrInfo DOMElementScrollHeightPropertyInfo where type AttrAllowedOps DOMElementScrollHeightPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMElementScrollHeightPropertyInfo = (~) () type AttrBaseTypeConstraint DOMElementScrollHeightPropertyInfo = DOMElementK type AttrGetType DOMElementScrollHeightPropertyInfo = Int64 type AttrLabel DOMElementScrollHeightPropertyInfo = "DOMElement::scroll-height" attrGet _ = getDOMElementScrollHeight attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "scroll-left" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable,PropertyWritable] getDOMElementScrollLeft :: (MonadIO m, DOMElementK o) => o -> m Int64 getDOMElementScrollLeft obj = liftIO $ getObjectPropertyInt64 obj "scroll-left" setDOMElementScrollLeft :: (MonadIO m, DOMElementK o) => o -> Int64 -> m () setDOMElementScrollLeft obj val = liftIO $ setObjectPropertyInt64 obj "scroll-left" val constructDOMElementScrollLeft :: Int64 -> IO ([Char], GValue) constructDOMElementScrollLeft val = constructObjectPropertyInt64 "scroll-left" val data DOMElementScrollLeftPropertyInfo instance AttrInfo DOMElementScrollLeftPropertyInfo where type AttrAllowedOps DOMElementScrollLeftPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMElementScrollLeftPropertyInfo = (~) Int64 type AttrBaseTypeConstraint DOMElementScrollLeftPropertyInfo = DOMElementK type AttrGetType DOMElementScrollLeftPropertyInfo = Int64 type AttrLabel DOMElementScrollLeftPropertyInfo = "DOMElement::scroll-left" attrGet _ = getDOMElementScrollLeft attrSet _ = setDOMElementScrollLeft attrConstruct _ = constructDOMElementScrollLeft -- VVV Prop "scroll-top" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable,PropertyWritable] getDOMElementScrollTop :: (MonadIO m, DOMElementK o) => o -> m Int64 getDOMElementScrollTop obj = liftIO $ getObjectPropertyInt64 obj "scroll-top" setDOMElementScrollTop :: (MonadIO m, DOMElementK o) => o -> Int64 -> m () setDOMElementScrollTop obj val = liftIO $ setObjectPropertyInt64 obj "scroll-top" val constructDOMElementScrollTop :: Int64 -> IO ([Char], GValue) constructDOMElementScrollTop val = constructObjectPropertyInt64 "scroll-top" val data DOMElementScrollTopPropertyInfo instance AttrInfo DOMElementScrollTopPropertyInfo where type AttrAllowedOps DOMElementScrollTopPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMElementScrollTopPropertyInfo = (~) Int64 type AttrBaseTypeConstraint DOMElementScrollTopPropertyInfo = DOMElementK type AttrGetType DOMElementScrollTopPropertyInfo = Int64 type AttrLabel DOMElementScrollTopPropertyInfo = "DOMElement::scroll-top" attrGet _ = getDOMElementScrollTop attrSet _ = setDOMElementScrollTop attrConstruct _ = constructDOMElementScrollTop -- VVV Prop "scroll-width" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMElementScrollWidth :: (MonadIO m, DOMElementK o) => o -> m Int64 getDOMElementScrollWidth obj = liftIO $ getObjectPropertyInt64 obj "scroll-width" data DOMElementScrollWidthPropertyInfo instance AttrInfo DOMElementScrollWidthPropertyInfo where type AttrAllowedOps DOMElementScrollWidthPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMElementScrollWidthPropertyInfo = (~) () type AttrBaseTypeConstraint DOMElementScrollWidthPropertyInfo = DOMElementK type AttrGetType DOMElementScrollWidthPropertyInfo = Int64 type AttrLabel DOMElementScrollWidthPropertyInfo = "DOMElement::scroll-width" attrGet _ = getDOMElementScrollWidth attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "style" -- Type: TInterface "WebKit" "DOMCSSStyleDeclaration" -- Flags: [PropertyReadable] getDOMElementStyle :: (MonadIO m, DOMElementK o) => o -> m DOMCSSStyleDeclaration getDOMElementStyle obj = liftIO $ getObjectPropertyObject obj "style" DOMCSSStyleDeclaration data DOMElementStylePropertyInfo instance AttrInfo DOMElementStylePropertyInfo where type AttrAllowedOps DOMElementStylePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMElementStylePropertyInfo = (~) () type AttrBaseTypeConstraint DOMElementStylePropertyInfo = DOMElementK type AttrGetType DOMElementStylePropertyInfo = DOMCSSStyleDeclaration type AttrLabel DOMElementStylePropertyInfo = "DOMElement::style" attrGet _ = getDOMElementStyle attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "tag-name" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMElementTagName :: (MonadIO m, DOMElementK o) => o -> m T.Text getDOMElementTagName obj = liftIO $ getObjectPropertyString obj "tag-name" data DOMElementTagNamePropertyInfo instance AttrInfo DOMElementTagNamePropertyInfo where type AttrAllowedOps DOMElementTagNamePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMElementTagNamePropertyInfo = (~) () type AttrBaseTypeConstraint DOMElementTagNamePropertyInfo = DOMElementK type AttrGetType DOMElementTagNamePropertyInfo = T.Text type AttrLabel DOMElementTagNamePropertyInfo = "DOMElement::tag-name" attrGet _ = getDOMElementTagName attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "webkit-region-overset" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMElementWebkitRegionOverset :: (MonadIO m, DOMElementK o) => o -> m T.Text getDOMElementWebkitRegionOverset obj = liftIO $ getObjectPropertyString obj "webkit-region-overset" data DOMElementWebkitRegionOversetPropertyInfo instance AttrInfo DOMElementWebkitRegionOversetPropertyInfo where type AttrAllowedOps DOMElementWebkitRegionOversetPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMElementWebkitRegionOversetPropertyInfo = (~) () type AttrBaseTypeConstraint DOMElementWebkitRegionOversetPropertyInfo = DOMElementK type AttrGetType DOMElementWebkitRegionOversetPropertyInfo = T.Text type AttrLabel DOMElementWebkitRegionOversetPropertyInfo = "DOMElement::webkit-region-overset" attrGet _ = getDOMElementWebkitRegionOverset attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMElement = '[ '("attributes", DOMElementAttributesPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("child-element-count", DOMElementChildElementCountPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("class-list", DOMElementClassListPropertyInfo), '("class-name", DOMElementClassNamePropertyInfo), '("client-height", DOMElementClientHeightPropertyInfo), '("client-left", DOMElementClientLeftPropertyInfo), '("client-top", DOMElementClientTopPropertyInfo), '("client-width", DOMElementClientWidthPropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("first-element-child", DOMElementFirstElementChildPropertyInfo), '("id", DOMElementIdPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-element-child", DOMElementLastElementChildPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-element-sibling", DOMElementNextElementSiblingPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("offset-height", DOMElementOffsetHeightPropertyInfo), '("offset-left", DOMElementOffsetLeftPropertyInfo), '("offset-parent", DOMElementOffsetParentPropertyInfo), '("offset-top", DOMElementOffsetTopPropertyInfo), '("offset-width", DOMElementOffsetWidthPropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-element-sibling", DOMElementPreviousElementSiblingPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("scroll-height", DOMElementScrollHeightPropertyInfo), '("scroll-left", DOMElementScrollLeftPropertyInfo), '("scroll-top", DOMElementScrollTopPropertyInfo), '("scroll-width", DOMElementScrollWidthPropertyInfo), '("style", DOMElementStylePropertyInfo), '("tag-name", DOMElementTagNamePropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("webkit-region-overset", DOMElementWebkitRegionOversetPropertyInfo)] type instance AttributeList DOMEntityReference = '[ '("base-uri", DOMNodeBaseUriPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo)] -- VVV Prop "bubbles" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMEventBubbles :: (MonadIO m, DOMEventK o) => o -> m Bool getDOMEventBubbles obj = liftIO $ getObjectPropertyBool obj "bubbles" data DOMEventBubblesPropertyInfo instance AttrInfo DOMEventBubblesPropertyInfo where type AttrAllowedOps DOMEventBubblesPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMEventBubblesPropertyInfo = (~) () type AttrBaseTypeConstraint DOMEventBubblesPropertyInfo = DOMEventK type AttrGetType DOMEventBubblesPropertyInfo = Bool type AttrLabel DOMEventBubblesPropertyInfo = "DOMEvent::bubbles" attrGet _ = getDOMEventBubbles attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "cancel-bubble" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMEventCancelBubble :: (MonadIO m, DOMEventK o) => o -> m Bool getDOMEventCancelBubble obj = liftIO $ getObjectPropertyBool obj "cancel-bubble" setDOMEventCancelBubble :: (MonadIO m, DOMEventK o) => o -> Bool -> m () setDOMEventCancelBubble obj val = liftIO $ setObjectPropertyBool obj "cancel-bubble" val constructDOMEventCancelBubble :: Bool -> IO ([Char], GValue) constructDOMEventCancelBubble val = constructObjectPropertyBool "cancel-bubble" val data DOMEventCancelBubblePropertyInfo instance AttrInfo DOMEventCancelBubblePropertyInfo where type AttrAllowedOps DOMEventCancelBubblePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMEventCancelBubblePropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMEventCancelBubblePropertyInfo = DOMEventK type AttrGetType DOMEventCancelBubblePropertyInfo = Bool type AttrLabel DOMEventCancelBubblePropertyInfo = "DOMEvent::cancel-bubble" attrGet _ = getDOMEventCancelBubble attrSet _ = setDOMEventCancelBubble attrConstruct _ = constructDOMEventCancelBubble -- VVV Prop "cancelable" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMEventCancelable :: (MonadIO m, DOMEventK o) => o -> m Bool getDOMEventCancelable obj = liftIO $ getObjectPropertyBool obj "cancelable" data DOMEventCancelablePropertyInfo instance AttrInfo DOMEventCancelablePropertyInfo where type AttrAllowedOps DOMEventCancelablePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMEventCancelablePropertyInfo = (~) () type AttrBaseTypeConstraint DOMEventCancelablePropertyInfo = DOMEventK type AttrGetType DOMEventCancelablePropertyInfo = Bool type AttrLabel DOMEventCancelablePropertyInfo = "DOMEvent::cancelable" attrGet _ = getDOMEventCancelable attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "current-target" -- Type: TInterface "WebKit" "DOMEventTarget" -- Flags: [PropertyReadable] getDOMEventCurrentTarget :: (MonadIO m, DOMEventK o) => o -> m DOMEventTarget getDOMEventCurrentTarget obj = liftIO $ getObjectPropertyObject obj "current-target" DOMEventTarget data DOMEventCurrentTargetPropertyInfo instance AttrInfo DOMEventCurrentTargetPropertyInfo where type AttrAllowedOps DOMEventCurrentTargetPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMEventCurrentTargetPropertyInfo = (~) () type AttrBaseTypeConstraint DOMEventCurrentTargetPropertyInfo = DOMEventK type AttrGetType DOMEventCurrentTargetPropertyInfo = DOMEventTarget type AttrLabel DOMEventCurrentTargetPropertyInfo = "DOMEvent::current-target" attrGet _ = getDOMEventCurrentTarget attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "default-prevented" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMEventDefaultPrevented :: (MonadIO m, DOMEventK o) => o -> m Bool getDOMEventDefaultPrevented obj = liftIO $ getObjectPropertyBool obj "default-prevented" data DOMEventDefaultPreventedPropertyInfo instance AttrInfo DOMEventDefaultPreventedPropertyInfo where type AttrAllowedOps DOMEventDefaultPreventedPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMEventDefaultPreventedPropertyInfo = (~) () type AttrBaseTypeConstraint DOMEventDefaultPreventedPropertyInfo = DOMEventK type AttrGetType DOMEventDefaultPreventedPropertyInfo = Bool type AttrLabel DOMEventDefaultPreventedPropertyInfo = "DOMEvent::default-prevented" attrGet _ = getDOMEventDefaultPrevented attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "event-phase" -- Type: TBasicType TUInt32 -- Flags: [PropertyReadable] getDOMEventEventPhase :: (MonadIO m, DOMEventK o) => o -> m Word32 getDOMEventEventPhase obj = liftIO $ getObjectPropertyCUInt obj "event-phase" data DOMEventEventPhasePropertyInfo instance AttrInfo DOMEventEventPhasePropertyInfo where type AttrAllowedOps DOMEventEventPhasePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMEventEventPhasePropertyInfo = (~) () type AttrBaseTypeConstraint DOMEventEventPhasePropertyInfo = DOMEventK type AttrGetType DOMEventEventPhasePropertyInfo = Word32 type AttrLabel DOMEventEventPhasePropertyInfo = "DOMEvent::event-phase" attrGet _ = getDOMEventEventPhase attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "return-value" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMEventReturnValue :: (MonadIO m, DOMEventK o) => o -> m Bool getDOMEventReturnValue obj = liftIO $ getObjectPropertyBool obj "return-value" setDOMEventReturnValue :: (MonadIO m, DOMEventK o) => o -> Bool -> m () setDOMEventReturnValue obj val = liftIO $ setObjectPropertyBool obj "return-value" val constructDOMEventReturnValue :: Bool -> IO ([Char], GValue) constructDOMEventReturnValue val = constructObjectPropertyBool "return-value" val data DOMEventReturnValuePropertyInfo instance AttrInfo DOMEventReturnValuePropertyInfo where type AttrAllowedOps DOMEventReturnValuePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMEventReturnValuePropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMEventReturnValuePropertyInfo = DOMEventK type AttrGetType DOMEventReturnValuePropertyInfo = Bool type AttrLabel DOMEventReturnValuePropertyInfo = "DOMEvent::return-value" attrGet _ = getDOMEventReturnValue attrSet _ = setDOMEventReturnValue attrConstruct _ = constructDOMEventReturnValue -- VVV Prop "src-element" -- Type: TInterface "WebKit" "DOMEventTarget" -- Flags: [PropertyReadable] getDOMEventSrcElement :: (MonadIO m, DOMEventK o) => o -> m DOMEventTarget getDOMEventSrcElement obj = liftIO $ getObjectPropertyObject obj "src-element" DOMEventTarget data DOMEventSrcElementPropertyInfo instance AttrInfo DOMEventSrcElementPropertyInfo where type AttrAllowedOps DOMEventSrcElementPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMEventSrcElementPropertyInfo = (~) () type AttrBaseTypeConstraint DOMEventSrcElementPropertyInfo = DOMEventK type AttrGetType DOMEventSrcElementPropertyInfo = DOMEventTarget type AttrLabel DOMEventSrcElementPropertyInfo = "DOMEvent::src-element" attrGet _ = getDOMEventSrcElement attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "target" -- Type: TInterface "WebKit" "DOMEventTarget" -- Flags: [PropertyReadable] getDOMEventTarget :: (MonadIO m, DOMEventK o) => o -> m DOMEventTarget getDOMEventTarget obj = liftIO $ getObjectPropertyObject obj "target" DOMEventTarget data DOMEventTargetPropertyInfo instance AttrInfo DOMEventTargetPropertyInfo where type AttrAllowedOps DOMEventTargetPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMEventTargetPropertyInfo = (~) () type AttrBaseTypeConstraint DOMEventTargetPropertyInfo = DOMEventK type AttrGetType DOMEventTargetPropertyInfo = DOMEventTarget type AttrLabel DOMEventTargetPropertyInfo = "DOMEvent::target" attrGet _ = getDOMEventTarget attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "time-stamp" -- Type: TBasicType TUInt32 -- Flags: [PropertyReadable] getDOMEventTimeStamp :: (MonadIO m, DOMEventK o) => o -> m Word32 getDOMEventTimeStamp obj = liftIO $ getObjectPropertyCUInt obj "time-stamp" data DOMEventTimeStampPropertyInfo instance AttrInfo DOMEventTimeStampPropertyInfo where type AttrAllowedOps DOMEventTimeStampPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMEventTimeStampPropertyInfo = (~) () type AttrBaseTypeConstraint DOMEventTimeStampPropertyInfo = DOMEventK type AttrGetType DOMEventTimeStampPropertyInfo = Word32 type AttrLabel DOMEventTimeStampPropertyInfo = "DOMEvent::time-stamp" attrGet _ = getDOMEventTimeStamp attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "type" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMEventType :: (MonadIO m, DOMEventK o) => o -> m T.Text getDOMEventType obj = liftIO $ getObjectPropertyString obj "type" data DOMEventTypePropertyInfo instance AttrInfo DOMEventTypePropertyInfo where type AttrAllowedOps DOMEventTypePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMEventTypePropertyInfo = (~) () type AttrBaseTypeConstraint DOMEventTypePropertyInfo = DOMEventK type AttrGetType DOMEventTypePropertyInfo = T.Text type AttrLabel DOMEventTypePropertyInfo = "DOMEvent::type" attrGet _ = getDOMEventType attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMEvent = '[ '("bubbles", DOMEventBubblesPropertyInfo), '("cancel-bubble", DOMEventCancelBubblePropertyInfo), '("cancelable", DOMEventCancelablePropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("current-target", DOMEventCurrentTargetPropertyInfo), '("default-prevented", DOMEventDefaultPreventedPropertyInfo), '("event-phase", DOMEventEventPhasePropertyInfo), '("return-value", DOMEventReturnValuePropertyInfo), '("src-element", DOMEventSrcElementPropertyInfo), '("target", DOMEventTargetPropertyInfo), '("time-stamp", DOMEventTimeStampPropertyInfo), '("type", DOMEventTypePropertyInfo)] type instance AttributeList DOMEventTarget = '[ ] -- VVV Prop "name" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMFileName :: (MonadIO m, DOMFileK o) => o -> m T.Text getDOMFileName obj = liftIO $ getObjectPropertyString obj "name" data DOMFileNamePropertyInfo instance AttrInfo DOMFileNamePropertyInfo where type AttrAllowedOps DOMFileNamePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMFileNamePropertyInfo = (~) () type AttrBaseTypeConstraint DOMFileNamePropertyInfo = DOMFileK type AttrGetType DOMFileNamePropertyInfo = T.Text type AttrLabel DOMFileNamePropertyInfo = "DOMFile::name" attrGet _ = getDOMFileName attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "webkit-relative-path" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMFileWebkitRelativePath :: (MonadIO m, DOMFileK o) => o -> m T.Text getDOMFileWebkitRelativePath obj = liftIO $ getObjectPropertyString obj "webkit-relative-path" data DOMFileWebkitRelativePathPropertyInfo instance AttrInfo DOMFileWebkitRelativePathPropertyInfo where type AttrAllowedOps DOMFileWebkitRelativePathPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMFileWebkitRelativePathPropertyInfo = (~) () type AttrBaseTypeConstraint DOMFileWebkitRelativePathPropertyInfo = DOMFileK type AttrGetType DOMFileWebkitRelativePathPropertyInfo = T.Text type AttrLabel DOMFileWebkitRelativePathPropertyInfo = "DOMFile::webkit-relative-path" attrGet _ = getDOMFileWebkitRelativePath attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMFile = '[ '("core-object", DOMObjectCoreObjectPropertyInfo), '("name", DOMFileNamePropertyInfo), '("size", DOMBlobSizePropertyInfo), '("type", DOMBlobTypePropertyInfo), '("webkit-relative-path", DOMFileWebkitRelativePathPropertyInfo)] -- VVV Prop "length" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMFileListLength :: (MonadIO m, DOMFileListK o) => o -> m Word64 getDOMFileListLength obj = liftIO $ getObjectPropertyUInt64 obj "length" data DOMFileListLengthPropertyInfo instance AttrInfo DOMFileListLengthPropertyInfo where type AttrAllowedOps DOMFileListLengthPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMFileListLengthPropertyInfo = (~) () type AttrBaseTypeConstraint DOMFileListLengthPropertyInfo = DOMFileListK type AttrGetType DOMFileListLengthPropertyInfo = Word64 type AttrLabel DOMFileListLengthPropertyInfo = "DOMFileList::length" attrGet _ = getDOMFileListLength attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMFileList = '[ '("core-object", DOMObjectCoreObjectPropertyInfo), '("length", DOMFileListLengthPropertyInfo)] -- VVV Prop "id" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMGamepadId :: (MonadIO m, DOMGamepadK o) => o -> m T.Text getDOMGamepadId obj = liftIO $ getObjectPropertyString obj "id" data DOMGamepadIdPropertyInfo instance AttrInfo DOMGamepadIdPropertyInfo where type AttrAllowedOps DOMGamepadIdPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMGamepadIdPropertyInfo = (~) () type AttrBaseTypeConstraint DOMGamepadIdPropertyInfo = DOMGamepadK type AttrGetType DOMGamepadIdPropertyInfo = T.Text type AttrLabel DOMGamepadIdPropertyInfo = "DOMGamepad::id" attrGet _ = getDOMGamepadId attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "index" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMGamepadIndex :: (MonadIO m, DOMGamepadK o) => o -> m Word64 getDOMGamepadIndex obj = liftIO $ getObjectPropertyUInt64 obj "index" data DOMGamepadIndexPropertyInfo instance AttrInfo DOMGamepadIndexPropertyInfo where type AttrAllowedOps DOMGamepadIndexPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMGamepadIndexPropertyInfo = (~) () type AttrBaseTypeConstraint DOMGamepadIndexPropertyInfo = DOMGamepadK type AttrGetType DOMGamepadIndexPropertyInfo = Word64 type AttrLabel DOMGamepadIndexPropertyInfo = "DOMGamepad::index" attrGet _ = getDOMGamepadIndex attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "timestamp" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMGamepadTimestamp :: (MonadIO m, DOMGamepadK o) => o -> m Word64 getDOMGamepadTimestamp obj = liftIO $ getObjectPropertyUInt64 obj "timestamp" data DOMGamepadTimestampPropertyInfo instance AttrInfo DOMGamepadTimestampPropertyInfo where type AttrAllowedOps DOMGamepadTimestampPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMGamepadTimestampPropertyInfo = (~) () type AttrBaseTypeConstraint DOMGamepadTimestampPropertyInfo = DOMGamepadK type AttrGetType DOMGamepadTimestampPropertyInfo = Word64 type AttrLabel DOMGamepadTimestampPropertyInfo = "DOMGamepad::timestamp" attrGet _ = getDOMGamepadTimestamp attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMGamepad = '[ '("core-object", DOMObjectCoreObjectPropertyInfo), '("id", DOMGamepadIdPropertyInfo), '("index", DOMGamepadIndexPropertyInfo), '("timestamp", DOMGamepadTimestampPropertyInfo)] -- VVV Prop "length" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMGamepadListLength :: (MonadIO m, DOMGamepadListK o) => o -> m Word64 getDOMGamepadListLength obj = liftIO $ getObjectPropertyUInt64 obj "length" data DOMGamepadListLengthPropertyInfo instance AttrInfo DOMGamepadListLengthPropertyInfo where type AttrAllowedOps DOMGamepadListLengthPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMGamepadListLengthPropertyInfo = (~) () type AttrBaseTypeConstraint DOMGamepadListLengthPropertyInfo = DOMGamepadListK type AttrGetType DOMGamepadListLengthPropertyInfo = Word64 type AttrLabel DOMGamepadListLengthPropertyInfo = "DOMGamepadList::length" attrGet _ = getDOMGamepadListLength attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMGamepadList = '[ '("core-object", DOMObjectCoreObjectPropertyInfo), '("length", DOMGamepadListLengthPropertyInfo)] type instance AttributeList DOMGeolocation = '[ '("core-object", DOMObjectCoreObjectPropertyInfo)] -- VVV Prop "charset" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLAnchorElementCharset :: (MonadIO m, DOMHTMLAnchorElementK o) => o -> m T.Text getDOMHTMLAnchorElementCharset obj = liftIO $ getObjectPropertyString obj "charset" setDOMHTMLAnchorElementCharset :: (MonadIO m, DOMHTMLAnchorElementK o) => o -> T.Text -> m () setDOMHTMLAnchorElementCharset obj val = liftIO $ setObjectPropertyString obj "charset" val constructDOMHTMLAnchorElementCharset :: T.Text -> IO ([Char], GValue) constructDOMHTMLAnchorElementCharset val = constructObjectPropertyString "charset" val data DOMHTMLAnchorElementCharsetPropertyInfo instance AttrInfo DOMHTMLAnchorElementCharsetPropertyInfo where type AttrAllowedOps DOMHTMLAnchorElementCharsetPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLAnchorElementCharsetPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLAnchorElementCharsetPropertyInfo = DOMHTMLAnchorElementK type AttrGetType DOMHTMLAnchorElementCharsetPropertyInfo = T.Text type AttrLabel DOMHTMLAnchorElementCharsetPropertyInfo = "DOMHTMLAnchorElement::charset" attrGet _ = getDOMHTMLAnchorElementCharset attrSet _ = setDOMHTMLAnchorElementCharset attrConstruct _ = constructDOMHTMLAnchorElementCharset -- VVV Prop "coords" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLAnchorElementCoords :: (MonadIO m, DOMHTMLAnchorElementK o) => o -> m T.Text getDOMHTMLAnchorElementCoords obj = liftIO $ getObjectPropertyString obj "coords" setDOMHTMLAnchorElementCoords :: (MonadIO m, DOMHTMLAnchorElementK o) => o -> T.Text -> m () setDOMHTMLAnchorElementCoords obj val = liftIO $ setObjectPropertyString obj "coords" val constructDOMHTMLAnchorElementCoords :: T.Text -> IO ([Char], GValue) constructDOMHTMLAnchorElementCoords val = constructObjectPropertyString "coords" val data DOMHTMLAnchorElementCoordsPropertyInfo instance AttrInfo DOMHTMLAnchorElementCoordsPropertyInfo where type AttrAllowedOps DOMHTMLAnchorElementCoordsPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLAnchorElementCoordsPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLAnchorElementCoordsPropertyInfo = DOMHTMLAnchorElementK type AttrGetType DOMHTMLAnchorElementCoordsPropertyInfo = T.Text type AttrLabel DOMHTMLAnchorElementCoordsPropertyInfo = "DOMHTMLAnchorElement::coords" attrGet _ = getDOMHTMLAnchorElementCoords attrSet _ = setDOMHTMLAnchorElementCoords attrConstruct _ = constructDOMHTMLAnchorElementCoords -- VVV Prop "download" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLAnchorElementDownload :: (MonadIO m, DOMHTMLAnchorElementK o) => o -> m T.Text getDOMHTMLAnchorElementDownload obj = liftIO $ getObjectPropertyString obj "download" setDOMHTMLAnchorElementDownload :: (MonadIO m, DOMHTMLAnchorElementK o) => o -> T.Text -> m () setDOMHTMLAnchorElementDownload obj val = liftIO $ setObjectPropertyString obj "download" val constructDOMHTMLAnchorElementDownload :: T.Text -> IO ([Char], GValue) constructDOMHTMLAnchorElementDownload val = constructObjectPropertyString "download" val data DOMHTMLAnchorElementDownloadPropertyInfo instance AttrInfo DOMHTMLAnchorElementDownloadPropertyInfo where type AttrAllowedOps DOMHTMLAnchorElementDownloadPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLAnchorElementDownloadPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLAnchorElementDownloadPropertyInfo = DOMHTMLAnchorElementK type AttrGetType DOMHTMLAnchorElementDownloadPropertyInfo = T.Text type AttrLabel DOMHTMLAnchorElementDownloadPropertyInfo = "DOMHTMLAnchorElement::download" attrGet _ = getDOMHTMLAnchorElementDownload attrSet _ = setDOMHTMLAnchorElementDownload attrConstruct _ = constructDOMHTMLAnchorElementDownload -- VVV Prop "hash" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLAnchorElementHash :: (MonadIO m, DOMHTMLAnchorElementK o) => o -> m T.Text getDOMHTMLAnchorElementHash obj = liftIO $ getObjectPropertyString obj "hash" setDOMHTMLAnchorElementHash :: (MonadIO m, DOMHTMLAnchorElementK o) => o -> T.Text -> m () setDOMHTMLAnchorElementHash obj val = liftIO $ setObjectPropertyString obj "hash" val constructDOMHTMLAnchorElementHash :: T.Text -> IO ([Char], GValue) constructDOMHTMLAnchorElementHash val = constructObjectPropertyString "hash" val data DOMHTMLAnchorElementHashPropertyInfo instance AttrInfo DOMHTMLAnchorElementHashPropertyInfo where type AttrAllowedOps DOMHTMLAnchorElementHashPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLAnchorElementHashPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLAnchorElementHashPropertyInfo = DOMHTMLAnchorElementK type AttrGetType DOMHTMLAnchorElementHashPropertyInfo = T.Text type AttrLabel DOMHTMLAnchorElementHashPropertyInfo = "DOMHTMLAnchorElement::hash" attrGet _ = getDOMHTMLAnchorElementHash attrSet _ = setDOMHTMLAnchorElementHash attrConstruct _ = constructDOMHTMLAnchorElementHash -- VVV Prop "host" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLAnchorElementHost :: (MonadIO m, DOMHTMLAnchorElementK o) => o -> m T.Text getDOMHTMLAnchorElementHost obj = liftIO $ getObjectPropertyString obj "host" setDOMHTMLAnchorElementHost :: (MonadIO m, DOMHTMLAnchorElementK o) => o -> T.Text -> m () setDOMHTMLAnchorElementHost obj val = liftIO $ setObjectPropertyString obj "host" val constructDOMHTMLAnchorElementHost :: T.Text -> IO ([Char], GValue) constructDOMHTMLAnchorElementHost val = constructObjectPropertyString "host" val data DOMHTMLAnchorElementHostPropertyInfo instance AttrInfo DOMHTMLAnchorElementHostPropertyInfo where type AttrAllowedOps DOMHTMLAnchorElementHostPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLAnchorElementHostPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLAnchorElementHostPropertyInfo = DOMHTMLAnchorElementK type AttrGetType DOMHTMLAnchorElementHostPropertyInfo = T.Text type AttrLabel DOMHTMLAnchorElementHostPropertyInfo = "DOMHTMLAnchorElement::host" attrGet _ = getDOMHTMLAnchorElementHost attrSet _ = setDOMHTMLAnchorElementHost attrConstruct _ = constructDOMHTMLAnchorElementHost -- VVV Prop "hostname" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLAnchorElementHostname :: (MonadIO m, DOMHTMLAnchorElementK o) => o -> m T.Text getDOMHTMLAnchorElementHostname obj = liftIO $ getObjectPropertyString obj "hostname" setDOMHTMLAnchorElementHostname :: (MonadIO m, DOMHTMLAnchorElementK o) => o -> T.Text -> m () setDOMHTMLAnchorElementHostname obj val = liftIO $ setObjectPropertyString obj "hostname" val constructDOMHTMLAnchorElementHostname :: T.Text -> IO ([Char], GValue) constructDOMHTMLAnchorElementHostname val = constructObjectPropertyString "hostname" val data DOMHTMLAnchorElementHostnamePropertyInfo instance AttrInfo DOMHTMLAnchorElementHostnamePropertyInfo where type AttrAllowedOps DOMHTMLAnchorElementHostnamePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLAnchorElementHostnamePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLAnchorElementHostnamePropertyInfo = DOMHTMLAnchorElementK type AttrGetType DOMHTMLAnchorElementHostnamePropertyInfo = T.Text type AttrLabel DOMHTMLAnchorElementHostnamePropertyInfo = "DOMHTMLAnchorElement::hostname" attrGet _ = getDOMHTMLAnchorElementHostname attrSet _ = setDOMHTMLAnchorElementHostname attrConstruct _ = constructDOMHTMLAnchorElementHostname -- VVV Prop "href" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLAnchorElementHref :: (MonadIO m, DOMHTMLAnchorElementK o) => o -> m T.Text getDOMHTMLAnchorElementHref obj = liftIO $ getObjectPropertyString obj "href" setDOMHTMLAnchorElementHref :: (MonadIO m, DOMHTMLAnchorElementK o) => o -> T.Text -> m () setDOMHTMLAnchorElementHref obj val = liftIO $ setObjectPropertyString obj "href" val constructDOMHTMLAnchorElementHref :: T.Text -> IO ([Char], GValue) constructDOMHTMLAnchorElementHref val = constructObjectPropertyString "href" val data DOMHTMLAnchorElementHrefPropertyInfo instance AttrInfo DOMHTMLAnchorElementHrefPropertyInfo where type AttrAllowedOps DOMHTMLAnchorElementHrefPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLAnchorElementHrefPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLAnchorElementHrefPropertyInfo = DOMHTMLAnchorElementK type AttrGetType DOMHTMLAnchorElementHrefPropertyInfo = T.Text type AttrLabel DOMHTMLAnchorElementHrefPropertyInfo = "DOMHTMLAnchorElement::href" attrGet _ = getDOMHTMLAnchorElementHref attrSet _ = setDOMHTMLAnchorElementHref attrConstruct _ = constructDOMHTMLAnchorElementHref -- VVV Prop "hreflang" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLAnchorElementHreflang :: (MonadIO m, DOMHTMLAnchorElementK o) => o -> m T.Text getDOMHTMLAnchorElementHreflang obj = liftIO $ getObjectPropertyString obj "hreflang" setDOMHTMLAnchorElementHreflang :: (MonadIO m, DOMHTMLAnchorElementK o) => o -> T.Text -> m () setDOMHTMLAnchorElementHreflang obj val = liftIO $ setObjectPropertyString obj "hreflang" val constructDOMHTMLAnchorElementHreflang :: T.Text -> IO ([Char], GValue) constructDOMHTMLAnchorElementHreflang val = constructObjectPropertyString "hreflang" val data DOMHTMLAnchorElementHreflangPropertyInfo instance AttrInfo DOMHTMLAnchorElementHreflangPropertyInfo where type AttrAllowedOps DOMHTMLAnchorElementHreflangPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLAnchorElementHreflangPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLAnchorElementHreflangPropertyInfo = DOMHTMLAnchorElementK type AttrGetType DOMHTMLAnchorElementHreflangPropertyInfo = T.Text type AttrLabel DOMHTMLAnchorElementHreflangPropertyInfo = "DOMHTMLAnchorElement::hreflang" attrGet _ = getDOMHTMLAnchorElementHreflang attrSet _ = setDOMHTMLAnchorElementHreflang attrConstruct _ = constructDOMHTMLAnchorElementHreflang -- VVV Prop "name" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLAnchorElementName :: (MonadIO m, DOMHTMLAnchorElementK o) => o -> m T.Text getDOMHTMLAnchorElementName obj = liftIO $ getObjectPropertyString obj "name" setDOMHTMLAnchorElementName :: (MonadIO m, DOMHTMLAnchorElementK o) => o -> T.Text -> m () setDOMHTMLAnchorElementName obj val = liftIO $ setObjectPropertyString obj "name" val constructDOMHTMLAnchorElementName :: T.Text -> IO ([Char], GValue) constructDOMHTMLAnchorElementName val = constructObjectPropertyString "name" val data DOMHTMLAnchorElementNamePropertyInfo instance AttrInfo DOMHTMLAnchorElementNamePropertyInfo where type AttrAllowedOps DOMHTMLAnchorElementNamePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLAnchorElementNamePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLAnchorElementNamePropertyInfo = DOMHTMLAnchorElementK type AttrGetType DOMHTMLAnchorElementNamePropertyInfo = T.Text type AttrLabel DOMHTMLAnchorElementNamePropertyInfo = "DOMHTMLAnchorElement::name" attrGet _ = getDOMHTMLAnchorElementName attrSet _ = setDOMHTMLAnchorElementName attrConstruct _ = constructDOMHTMLAnchorElementName -- VVV Prop "origin" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMHTMLAnchorElementOrigin :: (MonadIO m, DOMHTMLAnchorElementK o) => o -> m T.Text getDOMHTMLAnchorElementOrigin obj = liftIO $ getObjectPropertyString obj "origin" data DOMHTMLAnchorElementOriginPropertyInfo instance AttrInfo DOMHTMLAnchorElementOriginPropertyInfo where type AttrAllowedOps DOMHTMLAnchorElementOriginPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLAnchorElementOriginPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLAnchorElementOriginPropertyInfo = DOMHTMLAnchorElementK type AttrGetType DOMHTMLAnchorElementOriginPropertyInfo = T.Text type AttrLabel DOMHTMLAnchorElementOriginPropertyInfo = "DOMHTMLAnchorElement::origin" attrGet _ = getDOMHTMLAnchorElementOrigin attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "pathname" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLAnchorElementPathname :: (MonadIO m, DOMHTMLAnchorElementK o) => o -> m T.Text getDOMHTMLAnchorElementPathname obj = liftIO $ getObjectPropertyString obj "pathname" setDOMHTMLAnchorElementPathname :: (MonadIO m, DOMHTMLAnchorElementK o) => o -> T.Text -> m () setDOMHTMLAnchorElementPathname obj val = liftIO $ setObjectPropertyString obj "pathname" val constructDOMHTMLAnchorElementPathname :: T.Text -> IO ([Char], GValue) constructDOMHTMLAnchorElementPathname val = constructObjectPropertyString "pathname" val data DOMHTMLAnchorElementPathnamePropertyInfo instance AttrInfo DOMHTMLAnchorElementPathnamePropertyInfo where type AttrAllowedOps DOMHTMLAnchorElementPathnamePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLAnchorElementPathnamePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLAnchorElementPathnamePropertyInfo = DOMHTMLAnchorElementK type AttrGetType DOMHTMLAnchorElementPathnamePropertyInfo = T.Text type AttrLabel DOMHTMLAnchorElementPathnamePropertyInfo = "DOMHTMLAnchorElement::pathname" attrGet _ = getDOMHTMLAnchorElementPathname attrSet _ = setDOMHTMLAnchorElementPathname attrConstruct _ = constructDOMHTMLAnchorElementPathname -- VVV Prop "ping" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLAnchorElementPing :: (MonadIO m, DOMHTMLAnchorElementK o) => o -> m T.Text getDOMHTMLAnchorElementPing obj = liftIO $ getObjectPropertyString obj "ping" setDOMHTMLAnchorElementPing :: (MonadIO m, DOMHTMLAnchorElementK o) => o -> T.Text -> m () setDOMHTMLAnchorElementPing obj val = liftIO $ setObjectPropertyString obj "ping" val constructDOMHTMLAnchorElementPing :: T.Text -> IO ([Char], GValue) constructDOMHTMLAnchorElementPing val = constructObjectPropertyString "ping" val data DOMHTMLAnchorElementPingPropertyInfo instance AttrInfo DOMHTMLAnchorElementPingPropertyInfo where type AttrAllowedOps DOMHTMLAnchorElementPingPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLAnchorElementPingPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLAnchorElementPingPropertyInfo = DOMHTMLAnchorElementK type AttrGetType DOMHTMLAnchorElementPingPropertyInfo = T.Text type AttrLabel DOMHTMLAnchorElementPingPropertyInfo = "DOMHTMLAnchorElement::ping" attrGet _ = getDOMHTMLAnchorElementPing attrSet _ = setDOMHTMLAnchorElementPing attrConstruct _ = constructDOMHTMLAnchorElementPing -- VVV Prop "port" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLAnchorElementPort :: (MonadIO m, DOMHTMLAnchorElementK o) => o -> m T.Text getDOMHTMLAnchorElementPort obj = liftIO $ getObjectPropertyString obj "port" setDOMHTMLAnchorElementPort :: (MonadIO m, DOMHTMLAnchorElementK o) => o -> T.Text -> m () setDOMHTMLAnchorElementPort obj val = liftIO $ setObjectPropertyString obj "port" val constructDOMHTMLAnchorElementPort :: T.Text -> IO ([Char], GValue) constructDOMHTMLAnchorElementPort val = constructObjectPropertyString "port" val data DOMHTMLAnchorElementPortPropertyInfo instance AttrInfo DOMHTMLAnchorElementPortPropertyInfo where type AttrAllowedOps DOMHTMLAnchorElementPortPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLAnchorElementPortPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLAnchorElementPortPropertyInfo = DOMHTMLAnchorElementK type AttrGetType DOMHTMLAnchorElementPortPropertyInfo = T.Text type AttrLabel DOMHTMLAnchorElementPortPropertyInfo = "DOMHTMLAnchorElement::port" attrGet _ = getDOMHTMLAnchorElementPort attrSet _ = setDOMHTMLAnchorElementPort attrConstruct _ = constructDOMHTMLAnchorElementPort -- VVV Prop "protocol" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLAnchorElementProtocol :: (MonadIO m, DOMHTMLAnchorElementK o) => o -> m T.Text getDOMHTMLAnchorElementProtocol obj = liftIO $ getObjectPropertyString obj "protocol" setDOMHTMLAnchorElementProtocol :: (MonadIO m, DOMHTMLAnchorElementK o) => o -> T.Text -> m () setDOMHTMLAnchorElementProtocol obj val = liftIO $ setObjectPropertyString obj "protocol" val constructDOMHTMLAnchorElementProtocol :: T.Text -> IO ([Char], GValue) constructDOMHTMLAnchorElementProtocol val = constructObjectPropertyString "protocol" val data DOMHTMLAnchorElementProtocolPropertyInfo instance AttrInfo DOMHTMLAnchorElementProtocolPropertyInfo where type AttrAllowedOps DOMHTMLAnchorElementProtocolPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLAnchorElementProtocolPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLAnchorElementProtocolPropertyInfo = DOMHTMLAnchorElementK type AttrGetType DOMHTMLAnchorElementProtocolPropertyInfo = T.Text type AttrLabel DOMHTMLAnchorElementProtocolPropertyInfo = "DOMHTMLAnchorElement::protocol" attrGet _ = getDOMHTMLAnchorElementProtocol attrSet _ = setDOMHTMLAnchorElementProtocol attrConstruct _ = constructDOMHTMLAnchorElementProtocol -- VVV Prop "rel" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLAnchorElementRel :: (MonadIO m, DOMHTMLAnchorElementK o) => o -> m T.Text getDOMHTMLAnchorElementRel obj = liftIO $ getObjectPropertyString obj "rel" setDOMHTMLAnchorElementRel :: (MonadIO m, DOMHTMLAnchorElementK o) => o -> T.Text -> m () setDOMHTMLAnchorElementRel obj val = liftIO $ setObjectPropertyString obj "rel" val constructDOMHTMLAnchorElementRel :: T.Text -> IO ([Char], GValue) constructDOMHTMLAnchorElementRel val = constructObjectPropertyString "rel" val data DOMHTMLAnchorElementRelPropertyInfo instance AttrInfo DOMHTMLAnchorElementRelPropertyInfo where type AttrAllowedOps DOMHTMLAnchorElementRelPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLAnchorElementRelPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLAnchorElementRelPropertyInfo = DOMHTMLAnchorElementK type AttrGetType DOMHTMLAnchorElementRelPropertyInfo = T.Text type AttrLabel DOMHTMLAnchorElementRelPropertyInfo = "DOMHTMLAnchorElement::rel" attrGet _ = getDOMHTMLAnchorElementRel attrSet _ = setDOMHTMLAnchorElementRel attrConstruct _ = constructDOMHTMLAnchorElementRel -- VVV Prop "rev" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLAnchorElementRev :: (MonadIO m, DOMHTMLAnchorElementK o) => o -> m T.Text getDOMHTMLAnchorElementRev obj = liftIO $ getObjectPropertyString obj "rev" setDOMHTMLAnchorElementRev :: (MonadIO m, DOMHTMLAnchorElementK o) => o -> T.Text -> m () setDOMHTMLAnchorElementRev obj val = liftIO $ setObjectPropertyString obj "rev" val constructDOMHTMLAnchorElementRev :: T.Text -> IO ([Char], GValue) constructDOMHTMLAnchorElementRev val = constructObjectPropertyString "rev" val data DOMHTMLAnchorElementRevPropertyInfo instance AttrInfo DOMHTMLAnchorElementRevPropertyInfo where type AttrAllowedOps DOMHTMLAnchorElementRevPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLAnchorElementRevPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLAnchorElementRevPropertyInfo = DOMHTMLAnchorElementK type AttrGetType DOMHTMLAnchorElementRevPropertyInfo = T.Text type AttrLabel DOMHTMLAnchorElementRevPropertyInfo = "DOMHTMLAnchorElement::rev" attrGet _ = getDOMHTMLAnchorElementRev attrSet _ = setDOMHTMLAnchorElementRev attrConstruct _ = constructDOMHTMLAnchorElementRev -- VVV Prop "search" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLAnchorElementSearch :: (MonadIO m, DOMHTMLAnchorElementK o) => o -> m T.Text getDOMHTMLAnchorElementSearch obj = liftIO $ getObjectPropertyString obj "search" setDOMHTMLAnchorElementSearch :: (MonadIO m, DOMHTMLAnchorElementK o) => o -> T.Text -> m () setDOMHTMLAnchorElementSearch obj val = liftIO $ setObjectPropertyString obj "search" val constructDOMHTMLAnchorElementSearch :: T.Text -> IO ([Char], GValue) constructDOMHTMLAnchorElementSearch val = constructObjectPropertyString "search" val data DOMHTMLAnchorElementSearchPropertyInfo instance AttrInfo DOMHTMLAnchorElementSearchPropertyInfo where type AttrAllowedOps DOMHTMLAnchorElementSearchPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLAnchorElementSearchPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLAnchorElementSearchPropertyInfo = DOMHTMLAnchorElementK type AttrGetType DOMHTMLAnchorElementSearchPropertyInfo = T.Text type AttrLabel DOMHTMLAnchorElementSearchPropertyInfo = "DOMHTMLAnchorElement::search" attrGet _ = getDOMHTMLAnchorElementSearch attrSet _ = setDOMHTMLAnchorElementSearch attrConstruct _ = constructDOMHTMLAnchorElementSearch -- VVV Prop "shape" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLAnchorElementShape :: (MonadIO m, DOMHTMLAnchorElementK o) => o -> m T.Text getDOMHTMLAnchorElementShape obj = liftIO $ getObjectPropertyString obj "shape" setDOMHTMLAnchorElementShape :: (MonadIO m, DOMHTMLAnchorElementK o) => o -> T.Text -> m () setDOMHTMLAnchorElementShape obj val = liftIO $ setObjectPropertyString obj "shape" val constructDOMHTMLAnchorElementShape :: T.Text -> IO ([Char], GValue) constructDOMHTMLAnchorElementShape val = constructObjectPropertyString "shape" val data DOMHTMLAnchorElementShapePropertyInfo instance AttrInfo DOMHTMLAnchorElementShapePropertyInfo where type AttrAllowedOps DOMHTMLAnchorElementShapePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLAnchorElementShapePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLAnchorElementShapePropertyInfo = DOMHTMLAnchorElementK type AttrGetType DOMHTMLAnchorElementShapePropertyInfo = T.Text type AttrLabel DOMHTMLAnchorElementShapePropertyInfo = "DOMHTMLAnchorElement::shape" attrGet _ = getDOMHTMLAnchorElementShape attrSet _ = setDOMHTMLAnchorElementShape attrConstruct _ = constructDOMHTMLAnchorElementShape -- VVV Prop "target" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLAnchorElementTarget :: (MonadIO m, DOMHTMLAnchorElementK o) => o -> m T.Text getDOMHTMLAnchorElementTarget obj = liftIO $ getObjectPropertyString obj "target" setDOMHTMLAnchorElementTarget :: (MonadIO m, DOMHTMLAnchorElementK o) => o -> T.Text -> m () setDOMHTMLAnchorElementTarget obj val = liftIO $ setObjectPropertyString obj "target" val constructDOMHTMLAnchorElementTarget :: T.Text -> IO ([Char], GValue) constructDOMHTMLAnchorElementTarget val = constructObjectPropertyString "target" val data DOMHTMLAnchorElementTargetPropertyInfo instance AttrInfo DOMHTMLAnchorElementTargetPropertyInfo where type AttrAllowedOps DOMHTMLAnchorElementTargetPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLAnchorElementTargetPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLAnchorElementTargetPropertyInfo = DOMHTMLAnchorElementK type AttrGetType DOMHTMLAnchorElementTargetPropertyInfo = T.Text type AttrLabel DOMHTMLAnchorElementTargetPropertyInfo = "DOMHTMLAnchorElement::target" attrGet _ = getDOMHTMLAnchorElementTarget attrSet _ = setDOMHTMLAnchorElementTarget attrConstruct _ = constructDOMHTMLAnchorElementTarget -- VVV Prop "text" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMHTMLAnchorElementText :: (MonadIO m, DOMHTMLAnchorElementK o) => o -> m T.Text getDOMHTMLAnchorElementText obj = liftIO $ getObjectPropertyString obj "text" data DOMHTMLAnchorElementTextPropertyInfo instance AttrInfo DOMHTMLAnchorElementTextPropertyInfo where type AttrAllowedOps DOMHTMLAnchorElementTextPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLAnchorElementTextPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLAnchorElementTextPropertyInfo = DOMHTMLAnchorElementK type AttrGetType DOMHTMLAnchorElementTextPropertyInfo = T.Text type AttrLabel DOMHTMLAnchorElementTextPropertyInfo = "DOMHTMLAnchorElement::text" attrGet _ = getDOMHTMLAnchorElementText attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "type" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLAnchorElementType :: (MonadIO m, DOMHTMLAnchorElementK o) => o -> m T.Text getDOMHTMLAnchorElementType obj = liftIO $ getObjectPropertyString obj "type" setDOMHTMLAnchorElementType :: (MonadIO m, DOMHTMLAnchorElementK o) => o -> T.Text -> m () setDOMHTMLAnchorElementType obj val = liftIO $ setObjectPropertyString obj "type" val constructDOMHTMLAnchorElementType :: T.Text -> IO ([Char], GValue) constructDOMHTMLAnchorElementType val = constructObjectPropertyString "type" val data DOMHTMLAnchorElementTypePropertyInfo instance AttrInfo DOMHTMLAnchorElementTypePropertyInfo where type AttrAllowedOps DOMHTMLAnchorElementTypePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLAnchorElementTypePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLAnchorElementTypePropertyInfo = DOMHTMLAnchorElementK type AttrGetType DOMHTMLAnchorElementTypePropertyInfo = T.Text type AttrLabel DOMHTMLAnchorElementTypePropertyInfo = "DOMHTMLAnchorElement::type" attrGet _ = getDOMHTMLAnchorElementType attrSet _ = setDOMHTMLAnchorElementType attrConstruct _ = constructDOMHTMLAnchorElementType type instance AttributeList DOMHTMLAnchorElement = '[ '("access-key", DOMHTMLElementAccessKeyPropertyInfo), '("attributes", DOMElementAttributesPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("charset", DOMHTMLAnchorElementCharsetPropertyInfo), '("child-element-count", DOMElementChildElementCountPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("children", DOMHTMLElementChildrenPropertyInfo), '("class-list", DOMElementClassListPropertyInfo), '("class-name", DOMElementClassNamePropertyInfo), '("client-height", DOMElementClientHeightPropertyInfo), '("client-left", DOMElementClientLeftPropertyInfo), '("client-top", DOMElementClientTopPropertyInfo), '("client-width", DOMElementClientWidthPropertyInfo), '("content-editable", DOMHTMLElementContentEditablePropertyInfo), '("coords", DOMHTMLAnchorElementCoordsPropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("dir", DOMHTMLElementDirPropertyInfo), '("download", DOMHTMLAnchorElementDownloadPropertyInfo), '("draggable", DOMHTMLElementDraggablePropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("first-element-child", DOMElementFirstElementChildPropertyInfo), '("hash", DOMHTMLAnchorElementHashPropertyInfo), '("hidden", DOMHTMLElementHiddenPropertyInfo), '("host", DOMHTMLAnchorElementHostPropertyInfo), '("hostname", DOMHTMLAnchorElementHostnamePropertyInfo), '("href", DOMHTMLAnchorElementHrefPropertyInfo), '("hreflang", DOMHTMLAnchorElementHreflangPropertyInfo), '("id", DOMElementIdPropertyInfo), '("inner-html", DOMHTMLElementInnerHtmlPropertyInfo), '("inner-text", DOMHTMLElementInnerTextPropertyInfo), '("is-content-editable", DOMHTMLElementIsContentEditablePropertyInfo), '("lang", DOMHTMLElementLangPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-element-child", DOMElementLastElementChildPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("name", DOMHTMLAnchorElementNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-element-sibling", DOMElementNextElementSiblingPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("offset-height", DOMElementOffsetHeightPropertyInfo), '("offset-left", DOMElementOffsetLeftPropertyInfo), '("offset-parent", DOMElementOffsetParentPropertyInfo), '("offset-top", DOMElementOffsetTopPropertyInfo), '("offset-width", DOMElementOffsetWidthPropertyInfo), '("origin", DOMHTMLAnchorElementOriginPropertyInfo), '("outer-html", DOMHTMLElementOuterHtmlPropertyInfo), '("outer-text", DOMHTMLElementOuterTextPropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("pathname", DOMHTMLAnchorElementPathnamePropertyInfo), '("ping", DOMHTMLAnchorElementPingPropertyInfo), '("port", DOMHTMLAnchorElementPortPropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-element-sibling", DOMElementPreviousElementSiblingPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("protocol", DOMHTMLAnchorElementProtocolPropertyInfo), '("rel", DOMHTMLAnchorElementRelPropertyInfo), '("rev", DOMHTMLAnchorElementRevPropertyInfo), '("scroll-height", DOMElementScrollHeightPropertyInfo), '("scroll-left", DOMElementScrollLeftPropertyInfo), '("scroll-top", DOMElementScrollTopPropertyInfo), '("scroll-width", DOMElementScrollWidthPropertyInfo), '("search", DOMHTMLAnchorElementSearchPropertyInfo), '("shape", DOMHTMLAnchorElementShapePropertyInfo), '("spellcheck", DOMHTMLElementSpellcheckPropertyInfo), '("style", DOMElementStylePropertyInfo), '("tab-index", DOMHTMLElementTabIndexPropertyInfo), '("tag-name", DOMElementTagNamePropertyInfo), '("target", DOMHTMLAnchorElementTargetPropertyInfo), '("text", DOMHTMLAnchorElementTextPropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("title", DOMHTMLElementTitlePropertyInfo), '("translate", DOMHTMLElementTranslatePropertyInfo), '("type", DOMHTMLAnchorElementTypePropertyInfo), '("webkit-region-overset", DOMElementWebkitRegionOversetPropertyInfo), '("webkitdropzone", DOMHTMLElementWebkitdropzonePropertyInfo)] -- VVV Prop "align" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLAppletElementAlign :: (MonadIO m, DOMHTMLAppletElementK o) => o -> m T.Text getDOMHTMLAppletElementAlign obj = liftIO $ getObjectPropertyString obj "align" setDOMHTMLAppletElementAlign :: (MonadIO m, DOMHTMLAppletElementK o) => o -> T.Text -> m () setDOMHTMLAppletElementAlign obj val = liftIO $ setObjectPropertyString obj "align" val constructDOMHTMLAppletElementAlign :: T.Text -> IO ([Char], GValue) constructDOMHTMLAppletElementAlign val = constructObjectPropertyString "align" val data DOMHTMLAppletElementAlignPropertyInfo instance AttrInfo DOMHTMLAppletElementAlignPropertyInfo where type AttrAllowedOps DOMHTMLAppletElementAlignPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLAppletElementAlignPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLAppletElementAlignPropertyInfo = DOMHTMLAppletElementK type AttrGetType DOMHTMLAppletElementAlignPropertyInfo = T.Text type AttrLabel DOMHTMLAppletElementAlignPropertyInfo = "DOMHTMLAppletElement::align" attrGet _ = getDOMHTMLAppletElementAlign attrSet _ = setDOMHTMLAppletElementAlign attrConstruct _ = constructDOMHTMLAppletElementAlign -- VVV Prop "alt" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLAppletElementAlt :: (MonadIO m, DOMHTMLAppletElementK o) => o -> m T.Text getDOMHTMLAppletElementAlt obj = liftIO $ getObjectPropertyString obj "alt" setDOMHTMLAppletElementAlt :: (MonadIO m, DOMHTMLAppletElementK o) => o -> T.Text -> m () setDOMHTMLAppletElementAlt obj val = liftIO $ setObjectPropertyString obj "alt" val constructDOMHTMLAppletElementAlt :: T.Text -> IO ([Char], GValue) constructDOMHTMLAppletElementAlt val = constructObjectPropertyString "alt" val data DOMHTMLAppletElementAltPropertyInfo instance AttrInfo DOMHTMLAppletElementAltPropertyInfo where type AttrAllowedOps DOMHTMLAppletElementAltPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLAppletElementAltPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLAppletElementAltPropertyInfo = DOMHTMLAppletElementK type AttrGetType DOMHTMLAppletElementAltPropertyInfo = T.Text type AttrLabel DOMHTMLAppletElementAltPropertyInfo = "DOMHTMLAppletElement::alt" attrGet _ = getDOMHTMLAppletElementAlt attrSet _ = setDOMHTMLAppletElementAlt attrConstruct _ = constructDOMHTMLAppletElementAlt -- VVV Prop "archive" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLAppletElementArchive :: (MonadIO m, DOMHTMLAppletElementK o) => o -> m T.Text getDOMHTMLAppletElementArchive obj = liftIO $ getObjectPropertyString obj "archive" setDOMHTMLAppletElementArchive :: (MonadIO m, DOMHTMLAppletElementK o) => o -> T.Text -> m () setDOMHTMLAppletElementArchive obj val = liftIO $ setObjectPropertyString obj "archive" val constructDOMHTMLAppletElementArchive :: T.Text -> IO ([Char], GValue) constructDOMHTMLAppletElementArchive val = constructObjectPropertyString "archive" val data DOMHTMLAppletElementArchivePropertyInfo instance AttrInfo DOMHTMLAppletElementArchivePropertyInfo where type AttrAllowedOps DOMHTMLAppletElementArchivePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLAppletElementArchivePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLAppletElementArchivePropertyInfo = DOMHTMLAppletElementK type AttrGetType DOMHTMLAppletElementArchivePropertyInfo = T.Text type AttrLabel DOMHTMLAppletElementArchivePropertyInfo = "DOMHTMLAppletElement::archive" attrGet _ = getDOMHTMLAppletElementArchive attrSet _ = setDOMHTMLAppletElementArchive attrConstruct _ = constructDOMHTMLAppletElementArchive -- VVV Prop "code" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLAppletElementCode :: (MonadIO m, DOMHTMLAppletElementK o) => o -> m T.Text getDOMHTMLAppletElementCode obj = liftIO $ getObjectPropertyString obj "code" setDOMHTMLAppletElementCode :: (MonadIO m, DOMHTMLAppletElementK o) => o -> T.Text -> m () setDOMHTMLAppletElementCode obj val = liftIO $ setObjectPropertyString obj "code" val constructDOMHTMLAppletElementCode :: T.Text -> IO ([Char], GValue) constructDOMHTMLAppletElementCode val = constructObjectPropertyString "code" val data DOMHTMLAppletElementCodePropertyInfo instance AttrInfo DOMHTMLAppletElementCodePropertyInfo where type AttrAllowedOps DOMHTMLAppletElementCodePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLAppletElementCodePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLAppletElementCodePropertyInfo = DOMHTMLAppletElementK type AttrGetType DOMHTMLAppletElementCodePropertyInfo = T.Text type AttrLabel DOMHTMLAppletElementCodePropertyInfo = "DOMHTMLAppletElement::code" attrGet _ = getDOMHTMLAppletElementCode attrSet _ = setDOMHTMLAppletElementCode attrConstruct _ = constructDOMHTMLAppletElementCode -- VVV Prop "code-base" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLAppletElementCodeBase :: (MonadIO m, DOMHTMLAppletElementK o) => o -> m T.Text getDOMHTMLAppletElementCodeBase obj = liftIO $ getObjectPropertyString obj "code-base" setDOMHTMLAppletElementCodeBase :: (MonadIO m, DOMHTMLAppletElementK o) => o -> T.Text -> m () setDOMHTMLAppletElementCodeBase obj val = liftIO $ setObjectPropertyString obj "code-base" val constructDOMHTMLAppletElementCodeBase :: T.Text -> IO ([Char], GValue) constructDOMHTMLAppletElementCodeBase val = constructObjectPropertyString "code-base" val data DOMHTMLAppletElementCodeBasePropertyInfo instance AttrInfo DOMHTMLAppletElementCodeBasePropertyInfo where type AttrAllowedOps DOMHTMLAppletElementCodeBasePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLAppletElementCodeBasePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLAppletElementCodeBasePropertyInfo = DOMHTMLAppletElementK type AttrGetType DOMHTMLAppletElementCodeBasePropertyInfo = T.Text type AttrLabel DOMHTMLAppletElementCodeBasePropertyInfo = "DOMHTMLAppletElement::code-base" attrGet _ = getDOMHTMLAppletElementCodeBase attrSet _ = setDOMHTMLAppletElementCodeBase attrConstruct _ = constructDOMHTMLAppletElementCodeBase -- VVV Prop "height" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLAppletElementHeight :: (MonadIO m, DOMHTMLAppletElementK o) => o -> m T.Text getDOMHTMLAppletElementHeight obj = liftIO $ getObjectPropertyString obj "height" setDOMHTMLAppletElementHeight :: (MonadIO m, DOMHTMLAppletElementK o) => o -> T.Text -> m () setDOMHTMLAppletElementHeight obj val = liftIO $ setObjectPropertyString obj "height" val constructDOMHTMLAppletElementHeight :: T.Text -> IO ([Char], GValue) constructDOMHTMLAppletElementHeight val = constructObjectPropertyString "height" val data DOMHTMLAppletElementHeightPropertyInfo instance AttrInfo DOMHTMLAppletElementHeightPropertyInfo where type AttrAllowedOps DOMHTMLAppletElementHeightPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLAppletElementHeightPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLAppletElementHeightPropertyInfo = DOMHTMLAppletElementK type AttrGetType DOMHTMLAppletElementHeightPropertyInfo = T.Text type AttrLabel DOMHTMLAppletElementHeightPropertyInfo = "DOMHTMLAppletElement::height" attrGet _ = getDOMHTMLAppletElementHeight attrSet _ = setDOMHTMLAppletElementHeight attrConstruct _ = constructDOMHTMLAppletElementHeight -- VVV Prop "hspace" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLAppletElementHspace :: (MonadIO m, DOMHTMLAppletElementK o) => o -> m Int64 getDOMHTMLAppletElementHspace obj = liftIO $ getObjectPropertyInt64 obj "hspace" setDOMHTMLAppletElementHspace :: (MonadIO m, DOMHTMLAppletElementK o) => o -> Int64 -> m () setDOMHTMLAppletElementHspace obj val = liftIO $ setObjectPropertyInt64 obj "hspace" val constructDOMHTMLAppletElementHspace :: Int64 -> IO ([Char], GValue) constructDOMHTMLAppletElementHspace val = constructObjectPropertyInt64 "hspace" val data DOMHTMLAppletElementHspacePropertyInfo instance AttrInfo DOMHTMLAppletElementHspacePropertyInfo where type AttrAllowedOps DOMHTMLAppletElementHspacePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLAppletElementHspacePropertyInfo = (~) Int64 type AttrBaseTypeConstraint DOMHTMLAppletElementHspacePropertyInfo = DOMHTMLAppletElementK type AttrGetType DOMHTMLAppletElementHspacePropertyInfo = Int64 type AttrLabel DOMHTMLAppletElementHspacePropertyInfo = "DOMHTMLAppletElement::hspace" attrGet _ = getDOMHTMLAppletElementHspace attrSet _ = setDOMHTMLAppletElementHspace attrConstruct _ = constructDOMHTMLAppletElementHspace -- VVV Prop "name" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLAppletElementName :: (MonadIO m, DOMHTMLAppletElementK o) => o -> m T.Text getDOMHTMLAppletElementName obj = liftIO $ getObjectPropertyString obj "name" setDOMHTMLAppletElementName :: (MonadIO m, DOMHTMLAppletElementK o) => o -> T.Text -> m () setDOMHTMLAppletElementName obj val = liftIO $ setObjectPropertyString obj "name" val constructDOMHTMLAppletElementName :: T.Text -> IO ([Char], GValue) constructDOMHTMLAppletElementName val = constructObjectPropertyString "name" val data DOMHTMLAppletElementNamePropertyInfo instance AttrInfo DOMHTMLAppletElementNamePropertyInfo where type AttrAllowedOps DOMHTMLAppletElementNamePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLAppletElementNamePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLAppletElementNamePropertyInfo = DOMHTMLAppletElementK type AttrGetType DOMHTMLAppletElementNamePropertyInfo = T.Text type AttrLabel DOMHTMLAppletElementNamePropertyInfo = "DOMHTMLAppletElement::name" attrGet _ = getDOMHTMLAppletElementName attrSet _ = setDOMHTMLAppletElementName attrConstruct _ = constructDOMHTMLAppletElementName -- VVV Prop "object" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLAppletElementObject :: (MonadIO m, DOMHTMLAppletElementK o) => o -> m T.Text getDOMHTMLAppletElementObject obj = liftIO $ getObjectPropertyString obj "object" setDOMHTMLAppletElementObject :: (MonadIO m, DOMHTMLAppletElementK o) => o -> T.Text -> m () setDOMHTMLAppletElementObject obj val = liftIO $ setObjectPropertyString obj "object" val constructDOMHTMLAppletElementObject :: T.Text -> IO ([Char], GValue) constructDOMHTMLAppletElementObject val = constructObjectPropertyString "object" val data DOMHTMLAppletElementObjectPropertyInfo instance AttrInfo DOMHTMLAppletElementObjectPropertyInfo where type AttrAllowedOps DOMHTMLAppletElementObjectPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLAppletElementObjectPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLAppletElementObjectPropertyInfo = DOMHTMLAppletElementK type AttrGetType DOMHTMLAppletElementObjectPropertyInfo = T.Text type AttrLabel DOMHTMLAppletElementObjectPropertyInfo = "DOMHTMLAppletElement::object" attrGet _ = getDOMHTMLAppletElementObject attrSet _ = setDOMHTMLAppletElementObject attrConstruct _ = constructDOMHTMLAppletElementObject -- VVV Prop "vspace" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLAppletElementVspace :: (MonadIO m, DOMHTMLAppletElementK o) => o -> m Int64 getDOMHTMLAppletElementVspace obj = liftIO $ getObjectPropertyInt64 obj "vspace" setDOMHTMLAppletElementVspace :: (MonadIO m, DOMHTMLAppletElementK o) => o -> Int64 -> m () setDOMHTMLAppletElementVspace obj val = liftIO $ setObjectPropertyInt64 obj "vspace" val constructDOMHTMLAppletElementVspace :: Int64 -> IO ([Char], GValue) constructDOMHTMLAppletElementVspace val = constructObjectPropertyInt64 "vspace" val data DOMHTMLAppletElementVspacePropertyInfo instance AttrInfo DOMHTMLAppletElementVspacePropertyInfo where type AttrAllowedOps DOMHTMLAppletElementVspacePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLAppletElementVspacePropertyInfo = (~) Int64 type AttrBaseTypeConstraint DOMHTMLAppletElementVspacePropertyInfo = DOMHTMLAppletElementK type AttrGetType DOMHTMLAppletElementVspacePropertyInfo = Int64 type AttrLabel DOMHTMLAppletElementVspacePropertyInfo = "DOMHTMLAppletElement::vspace" attrGet _ = getDOMHTMLAppletElementVspace attrSet _ = setDOMHTMLAppletElementVspace attrConstruct _ = constructDOMHTMLAppletElementVspace -- VVV Prop "width" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLAppletElementWidth :: (MonadIO m, DOMHTMLAppletElementK o) => o -> m T.Text getDOMHTMLAppletElementWidth obj = liftIO $ getObjectPropertyString obj "width" setDOMHTMLAppletElementWidth :: (MonadIO m, DOMHTMLAppletElementK o) => o -> T.Text -> m () setDOMHTMLAppletElementWidth obj val = liftIO $ setObjectPropertyString obj "width" val constructDOMHTMLAppletElementWidth :: T.Text -> IO ([Char], GValue) constructDOMHTMLAppletElementWidth val = constructObjectPropertyString "width" val data DOMHTMLAppletElementWidthPropertyInfo instance AttrInfo DOMHTMLAppletElementWidthPropertyInfo where type AttrAllowedOps DOMHTMLAppletElementWidthPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLAppletElementWidthPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLAppletElementWidthPropertyInfo = DOMHTMLAppletElementK type AttrGetType DOMHTMLAppletElementWidthPropertyInfo = T.Text type AttrLabel DOMHTMLAppletElementWidthPropertyInfo = "DOMHTMLAppletElement::width" attrGet _ = getDOMHTMLAppletElementWidth attrSet _ = setDOMHTMLAppletElementWidth attrConstruct _ = constructDOMHTMLAppletElementWidth type instance AttributeList DOMHTMLAppletElement = '[ '("access-key", DOMHTMLElementAccessKeyPropertyInfo), '("align", DOMHTMLAppletElementAlignPropertyInfo), '("alt", DOMHTMLAppletElementAltPropertyInfo), '("archive", DOMHTMLAppletElementArchivePropertyInfo), '("attributes", DOMElementAttributesPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("child-element-count", DOMElementChildElementCountPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("children", DOMHTMLElementChildrenPropertyInfo), '("class-list", DOMElementClassListPropertyInfo), '("class-name", DOMElementClassNamePropertyInfo), '("client-height", DOMElementClientHeightPropertyInfo), '("client-left", DOMElementClientLeftPropertyInfo), '("client-top", DOMElementClientTopPropertyInfo), '("client-width", DOMElementClientWidthPropertyInfo), '("code", DOMHTMLAppletElementCodePropertyInfo), '("code-base", DOMHTMLAppletElementCodeBasePropertyInfo), '("content-editable", DOMHTMLElementContentEditablePropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("dir", DOMHTMLElementDirPropertyInfo), '("draggable", DOMHTMLElementDraggablePropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("first-element-child", DOMElementFirstElementChildPropertyInfo), '("height", DOMHTMLAppletElementHeightPropertyInfo), '("hidden", DOMHTMLElementHiddenPropertyInfo), '("hspace", DOMHTMLAppletElementHspacePropertyInfo), '("id", DOMElementIdPropertyInfo), '("inner-html", DOMHTMLElementInnerHtmlPropertyInfo), '("inner-text", DOMHTMLElementInnerTextPropertyInfo), '("is-content-editable", DOMHTMLElementIsContentEditablePropertyInfo), '("lang", DOMHTMLElementLangPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-element-child", DOMElementLastElementChildPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("name", DOMHTMLAppletElementNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-element-sibling", DOMElementNextElementSiblingPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("object", DOMHTMLAppletElementObjectPropertyInfo), '("offset-height", DOMElementOffsetHeightPropertyInfo), '("offset-left", DOMElementOffsetLeftPropertyInfo), '("offset-parent", DOMElementOffsetParentPropertyInfo), '("offset-top", DOMElementOffsetTopPropertyInfo), '("offset-width", DOMElementOffsetWidthPropertyInfo), '("outer-html", DOMHTMLElementOuterHtmlPropertyInfo), '("outer-text", DOMHTMLElementOuterTextPropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-element-sibling", DOMElementPreviousElementSiblingPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("scroll-height", DOMElementScrollHeightPropertyInfo), '("scroll-left", DOMElementScrollLeftPropertyInfo), '("scroll-top", DOMElementScrollTopPropertyInfo), '("scroll-width", DOMElementScrollWidthPropertyInfo), '("spellcheck", DOMHTMLElementSpellcheckPropertyInfo), '("style", DOMElementStylePropertyInfo), '("tab-index", DOMHTMLElementTabIndexPropertyInfo), '("tag-name", DOMElementTagNamePropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("title", DOMHTMLElementTitlePropertyInfo), '("translate", DOMHTMLElementTranslatePropertyInfo), '("vspace", DOMHTMLAppletElementVspacePropertyInfo), '("webkit-region-overset", DOMElementWebkitRegionOversetPropertyInfo), '("webkitdropzone", DOMHTMLElementWebkitdropzonePropertyInfo), '("width", DOMHTMLAppletElementWidthPropertyInfo)] -- VVV Prop "alt" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLAreaElementAlt :: (MonadIO m, DOMHTMLAreaElementK o) => o -> m T.Text getDOMHTMLAreaElementAlt obj = liftIO $ getObjectPropertyString obj "alt" setDOMHTMLAreaElementAlt :: (MonadIO m, DOMHTMLAreaElementK o) => o -> T.Text -> m () setDOMHTMLAreaElementAlt obj val = liftIO $ setObjectPropertyString obj "alt" val constructDOMHTMLAreaElementAlt :: T.Text -> IO ([Char], GValue) constructDOMHTMLAreaElementAlt val = constructObjectPropertyString "alt" val data DOMHTMLAreaElementAltPropertyInfo instance AttrInfo DOMHTMLAreaElementAltPropertyInfo where type AttrAllowedOps DOMHTMLAreaElementAltPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLAreaElementAltPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLAreaElementAltPropertyInfo = DOMHTMLAreaElementK type AttrGetType DOMHTMLAreaElementAltPropertyInfo = T.Text type AttrLabel DOMHTMLAreaElementAltPropertyInfo = "DOMHTMLAreaElement::alt" attrGet _ = getDOMHTMLAreaElementAlt attrSet _ = setDOMHTMLAreaElementAlt attrConstruct _ = constructDOMHTMLAreaElementAlt -- VVV Prop "coords" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLAreaElementCoords :: (MonadIO m, DOMHTMLAreaElementK o) => o -> m T.Text getDOMHTMLAreaElementCoords obj = liftIO $ getObjectPropertyString obj "coords" setDOMHTMLAreaElementCoords :: (MonadIO m, DOMHTMLAreaElementK o) => o -> T.Text -> m () setDOMHTMLAreaElementCoords obj val = liftIO $ setObjectPropertyString obj "coords" val constructDOMHTMLAreaElementCoords :: T.Text -> IO ([Char], GValue) constructDOMHTMLAreaElementCoords val = constructObjectPropertyString "coords" val data DOMHTMLAreaElementCoordsPropertyInfo instance AttrInfo DOMHTMLAreaElementCoordsPropertyInfo where type AttrAllowedOps DOMHTMLAreaElementCoordsPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLAreaElementCoordsPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLAreaElementCoordsPropertyInfo = DOMHTMLAreaElementK type AttrGetType DOMHTMLAreaElementCoordsPropertyInfo = T.Text type AttrLabel DOMHTMLAreaElementCoordsPropertyInfo = "DOMHTMLAreaElement::coords" attrGet _ = getDOMHTMLAreaElementCoords attrSet _ = setDOMHTMLAreaElementCoords attrConstruct _ = constructDOMHTMLAreaElementCoords -- VVV Prop "hash" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMHTMLAreaElementHash :: (MonadIO m, DOMHTMLAreaElementK o) => o -> m T.Text getDOMHTMLAreaElementHash obj = liftIO $ getObjectPropertyString obj "hash" data DOMHTMLAreaElementHashPropertyInfo instance AttrInfo DOMHTMLAreaElementHashPropertyInfo where type AttrAllowedOps DOMHTMLAreaElementHashPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLAreaElementHashPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLAreaElementHashPropertyInfo = DOMHTMLAreaElementK type AttrGetType DOMHTMLAreaElementHashPropertyInfo = T.Text type AttrLabel DOMHTMLAreaElementHashPropertyInfo = "DOMHTMLAreaElement::hash" attrGet _ = getDOMHTMLAreaElementHash attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "host" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMHTMLAreaElementHost :: (MonadIO m, DOMHTMLAreaElementK o) => o -> m T.Text getDOMHTMLAreaElementHost obj = liftIO $ getObjectPropertyString obj "host" data DOMHTMLAreaElementHostPropertyInfo instance AttrInfo DOMHTMLAreaElementHostPropertyInfo where type AttrAllowedOps DOMHTMLAreaElementHostPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLAreaElementHostPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLAreaElementHostPropertyInfo = DOMHTMLAreaElementK type AttrGetType DOMHTMLAreaElementHostPropertyInfo = T.Text type AttrLabel DOMHTMLAreaElementHostPropertyInfo = "DOMHTMLAreaElement::host" attrGet _ = getDOMHTMLAreaElementHost attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "hostname" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMHTMLAreaElementHostname :: (MonadIO m, DOMHTMLAreaElementK o) => o -> m T.Text getDOMHTMLAreaElementHostname obj = liftIO $ getObjectPropertyString obj "hostname" data DOMHTMLAreaElementHostnamePropertyInfo instance AttrInfo DOMHTMLAreaElementHostnamePropertyInfo where type AttrAllowedOps DOMHTMLAreaElementHostnamePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLAreaElementHostnamePropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLAreaElementHostnamePropertyInfo = DOMHTMLAreaElementK type AttrGetType DOMHTMLAreaElementHostnamePropertyInfo = T.Text type AttrLabel DOMHTMLAreaElementHostnamePropertyInfo = "DOMHTMLAreaElement::hostname" attrGet _ = getDOMHTMLAreaElementHostname attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "href" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLAreaElementHref :: (MonadIO m, DOMHTMLAreaElementK o) => o -> m T.Text getDOMHTMLAreaElementHref obj = liftIO $ getObjectPropertyString obj "href" setDOMHTMLAreaElementHref :: (MonadIO m, DOMHTMLAreaElementK o) => o -> T.Text -> m () setDOMHTMLAreaElementHref obj val = liftIO $ setObjectPropertyString obj "href" val constructDOMHTMLAreaElementHref :: T.Text -> IO ([Char], GValue) constructDOMHTMLAreaElementHref val = constructObjectPropertyString "href" val data DOMHTMLAreaElementHrefPropertyInfo instance AttrInfo DOMHTMLAreaElementHrefPropertyInfo where type AttrAllowedOps DOMHTMLAreaElementHrefPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLAreaElementHrefPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLAreaElementHrefPropertyInfo = DOMHTMLAreaElementK type AttrGetType DOMHTMLAreaElementHrefPropertyInfo = T.Text type AttrLabel DOMHTMLAreaElementHrefPropertyInfo = "DOMHTMLAreaElement::href" attrGet _ = getDOMHTMLAreaElementHref attrSet _ = setDOMHTMLAreaElementHref attrConstruct _ = constructDOMHTMLAreaElementHref -- VVV Prop "no-href" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLAreaElementNoHref :: (MonadIO m, DOMHTMLAreaElementK o) => o -> m Bool getDOMHTMLAreaElementNoHref obj = liftIO $ getObjectPropertyBool obj "no-href" setDOMHTMLAreaElementNoHref :: (MonadIO m, DOMHTMLAreaElementK o) => o -> Bool -> m () setDOMHTMLAreaElementNoHref obj val = liftIO $ setObjectPropertyBool obj "no-href" val constructDOMHTMLAreaElementNoHref :: Bool -> IO ([Char], GValue) constructDOMHTMLAreaElementNoHref val = constructObjectPropertyBool "no-href" val data DOMHTMLAreaElementNoHrefPropertyInfo instance AttrInfo DOMHTMLAreaElementNoHrefPropertyInfo where type AttrAllowedOps DOMHTMLAreaElementNoHrefPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLAreaElementNoHrefPropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLAreaElementNoHrefPropertyInfo = DOMHTMLAreaElementK type AttrGetType DOMHTMLAreaElementNoHrefPropertyInfo = Bool type AttrLabel DOMHTMLAreaElementNoHrefPropertyInfo = "DOMHTMLAreaElement::no-href" attrGet _ = getDOMHTMLAreaElementNoHref attrSet _ = setDOMHTMLAreaElementNoHref attrConstruct _ = constructDOMHTMLAreaElementNoHref -- VVV Prop "pathname" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMHTMLAreaElementPathname :: (MonadIO m, DOMHTMLAreaElementK o) => o -> m T.Text getDOMHTMLAreaElementPathname obj = liftIO $ getObjectPropertyString obj "pathname" data DOMHTMLAreaElementPathnamePropertyInfo instance AttrInfo DOMHTMLAreaElementPathnamePropertyInfo where type AttrAllowedOps DOMHTMLAreaElementPathnamePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLAreaElementPathnamePropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLAreaElementPathnamePropertyInfo = DOMHTMLAreaElementK type AttrGetType DOMHTMLAreaElementPathnamePropertyInfo = T.Text type AttrLabel DOMHTMLAreaElementPathnamePropertyInfo = "DOMHTMLAreaElement::pathname" attrGet _ = getDOMHTMLAreaElementPathname attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "ping" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLAreaElementPing :: (MonadIO m, DOMHTMLAreaElementK o) => o -> m T.Text getDOMHTMLAreaElementPing obj = liftIO $ getObjectPropertyString obj "ping" setDOMHTMLAreaElementPing :: (MonadIO m, DOMHTMLAreaElementK o) => o -> T.Text -> m () setDOMHTMLAreaElementPing obj val = liftIO $ setObjectPropertyString obj "ping" val constructDOMHTMLAreaElementPing :: T.Text -> IO ([Char], GValue) constructDOMHTMLAreaElementPing val = constructObjectPropertyString "ping" val data DOMHTMLAreaElementPingPropertyInfo instance AttrInfo DOMHTMLAreaElementPingPropertyInfo where type AttrAllowedOps DOMHTMLAreaElementPingPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLAreaElementPingPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLAreaElementPingPropertyInfo = DOMHTMLAreaElementK type AttrGetType DOMHTMLAreaElementPingPropertyInfo = T.Text type AttrLabel DOMHTMLAreaElementPingPropertyInfo = "DOMHTMLAreaElement::ping" attrGet _ = getDOMHTMLAreaElementPing attrSet _ = setDOMHTMLAreaElementPing attrConstruct _ = constructDOMHTMLAreaElementPing -- VVV Prop "port" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMHTMLAreaElementPort :: (MonadIO m, DOMHTMLAreaElementK o) => o -> m T.Text getDOMHTMLAreaElementPort obj = liftIO $ getObjectPropertyString obj "port" data DOMHTMLAreaElementPortPropertyInfo instance AttrInfo DOMHTMLAreaElementPortPropertyInfo where type AttrAllowedOps DOMHTMLAreaElementPortPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLAreaElementPortPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLAreaElementPortPropertyInfo = DOMHTMLAreaElementK type AttrGetType DOMHTMLAreaElementPortPropertyInfo = T.Text type AttrLabel DOMHTMLAreaElementPortPropertyInfo = "DOMHTMLAreaElement::port" attrGet _ = getDOMHTMLAreaElementPort attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "protocol" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMHTMLAreaElementProtocol :: (MonadIO m, DOMHTMLAreaElementK o) => o -> m T.Text getDOMHTMLAreaElementProtocol obj = liftIO $ getObjectPropertyString obj "protocol" data DOMHTMLAreaElementProtocolPropertyInfo instance AttrInfo DOMHTMLAreaElementProtocolPropertyInfo where type AttrAllowedOps DOMHTMLAreaElementProtocolPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLAreaElementProtocolPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLAreaElementProtocolPropertyInfo = DOMHTMLAreaElementK type AttrGetType DOMHTMLAreaElementProtocolPropertyInfo = T.Text type AttrLabel DOMHTMLAreaElementProtocolPropertyInfo = "DOMHTMLAreaElement::protocol" attrGet _ = getDOMHTMLAreaElementProtocol attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "search" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMHTMLAreaElementSearch :: (MonadIO m, DOMHTMLAreaElementK o) => o -> m T.Text getDOMHTMLAreaElementSearch obj = liftIO $ getObjectPropertyString obj "search" data DOMHTMLAreaElementSearchPropertyInfo instance AttrInfo DOMHTMLAreaElementSearchPropertyInfo where type AttrAllowedOps DOMHTMLAreaElementSearchPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLAreaElementSearchPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLAreaElementSearchPropertyInfo = DOMHTMLAreaElementK type AttrGetType DOMHTMLAreaElementSearchPropertyInfo = T.Text type AttrLabel DOMHTMLAreaElementSearchPropertyInfo = "DOMHTMLAreaElement::search" attrGet _ = getDOMHTMLAreaElementSearch attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "shape" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLAreaElementShape :: (MonadIO m, DOMHTMLAreaElementK o) => o -> m T.Text getDOMHTMLAreaElementShape obj = liftIO $ getObjectPropertyString obj "shape" setDOMHTMLAreaElementShape :: (MonadIO m, DOMHTMLAreaElementK o) => o -> T.Text -> m () setDOMHTMLAreaElementShape obj val = liftIO $ setObjectPropertyString obj "shape" val constructDOMHTMLAreaElementShape :: T.Text -> IO ([Char], GValue) constructDOMHTMLAreaElementShape val = constructObjectPropertyString "shape" val data DOMHTMLAreaElementShapePropertyInfo instance AttrInfo DOMHTMLAreaElementShapePropertyInfo where type AttrAllowedOps DOMHTMLAreaElementShapePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLAreaElementShapePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLAreaElementShapePropertyInfo = DOMHTMLAreaElementK type AttrGetType DOMHTMLAreaElementShapePropertyInfo = T.Text type AttrLabel DOMHTMLAreaElementShapePropertyInfo = "DOMHTMLAreaElement::shape" attrGet _ = getDOMHTMLAreaElementShape attrSet _ = setDOMHTMLAreaElementShape attrConstruct _ = constructDOMHTMLAreaElementShape -- VVV Prop "target" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLAreaElementTarget :: (MonadIO m, DOMHTMLAreaElementK o) => o -> m T.Text getDOMHTMLAreaElementTarget obj = liftIO $ getObjectPropertyString obj "target" setDOMHTMLAreaElementTarget :: (MonadIO m, DOMHTMLAreaElementK o) => o -> T.Text -> m () setDOMHTMLAreaElementTarget obj val = liftIO $ setObjectPropertyString obj "target" val constructDOMHTMLAreaElementTarget :: T.Text -> IO ([Char], GValue) constructDOMHTMLAreaElementTarget val = constructObjectPropertyString "target" val data DOMHTMLAreaElementTargetPropertyInfo instance AttrInfo DOMHTMLAreaElementTargetPropertyInfo where type AttrAllowedOps DOMHTMLAreaElementTargetPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLAreaElementTargetPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLAreaElementTargetPropertyInfo = DOMHTMLAreaElementK type AttrGetType DOMHTMLAreaElementTargetPropertyInfo = T.Text type AttrLabel DOMHTMLAreaElementTargetPropertyInfo = "DOMHTMLAreaElement::target" attrGet _ = getDOMHTMLAreaElementTarget attrSet _ = setDOMHTMLAreaElementTarget attrConstruct _ = constructDOMHTMLAreaElementTarget type instance AttributeList DOMHTMLAreaElement = '[ '("access-key", DOMHTMLElementAccessKeyPropertyInfo), '("alt", DOMHTMLAreaElementAltPropertyInfo), '("attributes", DOMElementAttributesPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("child-element-count", DOMElementChildElementCountPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("children", DOMHTMLElementChildrenPropertyInfo), '("class-list", DOMElementClassListPropertyInfo), '("class-name", DOMElementClassNamePropertyInfo), '("client-height", DOMElementClientHeightPropertyInfo), '("client-left", DOMElementClientLeftPropertyInfo), '("client-top", DOMElementClientTopPropertyInfo), '("client-width", DOMElementClientWidthPropertyInfo), '("content-editable", DOMHTMLElementContentEditablePropertyInfo), '("coords", DOMHTMLAreaElementCoordsPropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("dir", DOMHTMLElementDirPropertyInfo), '("draggable", DOMHTMLElementDraggablePropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("first-element-child", DOMElementFirstElementChildPropertyInfo), '("hash", DOMHTMLAreaElementHashPropertyInfo), '("hidden", DOMHTMLElementHiddenPropertyInfo), '("host", DOMHTMLAreaElementHostPropertyInfo), '("hostname", DOMHTMLAreaElementHostnamePropertyInfo), '("href", DOMHTMLAreaElementHrefPropertyInfo), '("id", DOMElementIdPropertyInfo), '("inner-html", DOMHTMLElementInnerHtmlPropertyInfo), '("inner-text", DOMHTMLElementInnerTextPropertyInfo), '("is-content-editable", DOMHTMLElementIsContentEditablePropertyInfo), '("lang", DOMHTMLElementLangPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-element-child", DOMElementLastElementChildPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-element-sibling", DOMElementNextElementSiblingPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("no-href", DOMHTMLAreaElementNoHrefPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("offset-height", DOMElementOffsetHeightPropertyInfo), '("offset-left", DOMElementOffsetLeftPropertyInfo), '("offset-parent", DOMElementOffsetParentPropertyInfo), '("offset-top", DOMElementOffsetTopPropertyInfo), '("offset-width", DOMElementOffsetWidthPropertyInfo), '("outer-html", DOMHTMLElementOuterHtmlPropertyInfo), '("outer-text", DOMHTMLElementOuterTextPropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("pathname", DOMHTMLAreaElementPathnamePropertyInfo), '("ping", DOMHTMLAreaElementPingPropertyInfo), '("port", DOMHTMLAreaElementPortPropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-element-sibling", DOMElementPreviousElementSiblingPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("protocol", DOMHTMLAreaElementProtocolPropertyInfo), '("scroll-height", DOMElementScrollHeightPropertyInfo), '("scroll-left", DOMElementScrollLeftPropertyInfo), '("scroll-top", DOMElementScrollTopPropertyInfo), '("scroll-width", DOMElementScrollWidthPropertyInfo), '("search", DOMHTMLAreaElementSearchPropertyInfo), '("shape", DOMHTMLAreaElementShapePropertyInfo), '("spellcheck", DOMHTMLElementSpellcheckPropertyInfo), '("style", DOMElementStylePropertyInfo), '("tab-index", DOMHTMLElementTabIndexPropertyInfo), '("tag-name", DOMElementTagNamePropertyInfo), '("target", DOMHTMLAreaElementTargetPropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("title", DOMHTMLElementTitlePropertyInfo), '("translate", DOMHTMLElementTranslatePropertyInfo), '("webkit-region-overset", DOMElementWebkitRegionOversetPropertyInfo), '("webkitdropzone", DOMHTMLElementWebkitdropzonePropertyInfo)] type instance AttributeList DOMHTMLAudioElement = '[ '("access-key", DOMHTMLElementAccessKeyPropertyInfo), '("attributes", DOMElementAttributesPropertyInfo), '("audio-tracks", DOMHTMLMediaElementAudioTracksPropertyInfo), '("autoplay", DOMHTMLMediaElementAutoplayPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("buffered", DOMHTMLMediaElementBufferedPropertyInfo), '("child-element-count", DOMElementChildElementCountPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("children", DOMHTMLElementChildrenPropertyInfo), '("class-list", DOMElementClassListPropertyInfo), '("class-name", DOMElementClassNamePropertyInfo), '("client-height", DOMElementClientHeightPropertyInfo), '("client-left", DOMElementClientLeftPropertyInfo), '("client-top", DOMElementClientTopPropertyInfo), '("client-width", DOMElementClientWidthPropertyInfo), '("content-editable", DOMHTMLElementContentEditablePropertyInfo), '("controller", DOMHTMLMediaElementControllerPropertyInfo), '("controls", DOMHTMLMediaElementControlsPropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("current-src", DOMHTMLMediaElementCurrentSrcPropertyInfo), '("current-time", DOMHTMLMediaElementCurrentTimePropertyInfo), '("default-muted", DOMHTMLMediaElementDefaultMutedPropertyInfo), '("default-playback-rate", DOMHTMLMediaElementDefaultPlaybackRatePropertyInfo), '("dir", DOMHTMLElementDirPropertyInfo), '("draggable", DOMHTMLElementDraggablePropertyInfo), '("duration", DOMHTMLMediaElementDurationPropertyInfo), '("ended", DOMHTMLMediaElementEndedPropertyInfo), '("error", DOMHTMLMediaElementErrorPropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("first-element-child", DOMElementFirstElementChildPropertyInfo), '("hidden", DOMHTMLElementHiddenPropertyInfo), '("id", DOMElementIdPropertyInfo), '("inner-html", DOMHTMLElementInnerHtmlPropertyInfo), '("inner-text", DOMHTMLElementInnerTextPropertyInfo), '("is-content-editable", DOMHTMLElementIsContentEditablePropertyInfo), '("lang", DOMHTMLElementLangPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-element-child", DOMElementLastElementChildPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("loop", DOMHTMLMediaElementLoopPropertyInfo), '("media-group", DOMHTMLMediaElementMediaGroupPropertyInfo), '("muted", DOMHTMLMediaElementMutedPropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("network-state", DOMHTMLMediaElementNetworkStatePropertyInfo), '("next-element-sibling", DOMElementNextElementSiblingPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("offset-height", DOMElementOffsetHeightPropertyInfo), '("offset-left", DOMElementOffsetLeftPropertyInfo), '("offset-parent", DOMElementOffsetParentPropertyInfo), '("offset-top", DOMElementOffsetTopPropertyInfo), '("offset-width", DOMElementOffsetWidthPropertyInfo), '("outer-html", DOMHTMLElementOuterHtmlPropertyInfo), '("outer-text", DOMHTMLElementOuterTextPropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("paused", DOMHTMLMediaElementPausedPropertyInfo), '("playback-rate", DOMHTMLMediaElementPlaybackRatePropertyInfo), '("played", DOMHTMLMediaElementPlayedPropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("preload", DOMHTMLMediaElementPreloadPropertyInfo), '("previous-element-sibling", DOMElementPreviousElementSiblingPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("ready-state", DOMHTMLMediaElementReadyStatePropertyInfo), '("scroll-height", DOMElementScrollHeightPropertyInfo), '("scroll-left", DOMElementScrollLeftPropertyInfo), '("scroll-top", DOMElementScrollTopPropertyInfo), '("scroll-width", DOMElementScrollWidthPropertyInfo), '("seekable", DOMHTMLMediaElementSeekablePropertyInfo), '("seeking", DOMHTMLMediaElementSeekingPropertyInfo), '("spellcheck", DOMHTMLElementSpellcheckPropertyInfo), '("src", DOMHTMLMediaElementSrcPropertyInfo), '("style", DOMElementStylePropertyInfo), '("tab-index", DOMHTMLElementTabIndexPropertyInfo), '("tag-name", DOMElementTagNamePropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("text-tracks", DOMHTMLMediaElementTextTracksPropertyInfo), '("title", DOMHTMLElementTitlePropertyInfo), '("translate", DOMHTMLElementTranslatePropertyInfo), '("video-tracks", DOMHTMLMediaElementVideoTracksPropertyInfo), '("volume", DOMHTMLMediaElementVolumePropertyInfo), '("webkit-audio-decoded-byte-count", DOMHTMLMediaElementWebkitAudioDecodedByteCountPropertyInfo), '("webkit-closed-captions-visible", DOMHTMLMediaElementWebkitClosedCaptionsVisiblePropertyInfo), '("webkit-current-playback-target-is-wireless", DOMHTMLMediaElementWebkitCurrentPlaybackTargetIsWirelessPropertyInfo), '("webkit-has-closed-captions", DOMHTMLMediaElementWebkitHasClosedCaptionsPropertyInfo), '("webkit-preserves-pitch", DOMHTMLMediaElementWebkitPreservesPitchPropertyInfo), '("webkit-region-overset", DOMElementWebkitRegionOversetPropertyInfo), '("webkit-video-decoded-byte-count", DOMHTMLMediaElementWebkitVideoDecodedByteCountPropertyInfo), '("webkitdropzone", DOMHTMLElementWebkitdropzonePropertyInfo)] -- VVV Prop "clear" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLBRElementClear :: (MonadIO m, DOMHTMLBRElementK o) => o -> m T.Text getDOMHTMLBRElementClear obj = liftIO $ getObjectPropertyString obj "clear" setDOMHTMLBRElementClear :: (MonadIO m, DOMHTMLBRElementK o) => o -> T.Text -> m () setDOMHTMLBRElementClear obj val = liftIO $ setObjectPropertyString obj "clear" val constructDOMHTMLBRElementClear :: T.Text -> IO ([Char], GValue) constructDOMHTMLBRElementClear val = constructObjectPropertyString "clear" val data DOMHTMLBRElementClearPropertyInfo instance AttrInfo DOMHTMLBRElementClearPropertyInfo where type AttrAllowedOps DOMHTMLBRElementClearPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLBRElementClearPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLBRElementClearPropertyInfo = DOMHTMLBRElementK type AttrGetType DOMHTMLBRElementClearPropertyInfo = T.Text type AttrLabel DOMHTMLBRElementClearPropertyInfo = "DOMHTMLBRElement::clear" attrGet _ = getDOMHTMLBRElementClear attrSet _ = setDOMHTMLBRElementClear attrConstruct _ = constructDOMHTMLBRElementClear type instance AttributeList DOMHTMLBRElement = '[ '("access-key", DOMHTMLElementAccessKeyPropertyInfo), '("attributes", DOMElementAttributesPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("child-element-count", DOMElementChildElementCountPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("children", DOMHTMLElementChildrenPropertyInfo), '("class-list", DOMElementClassListPropertyInfo), '("class-name", DOMElementClassNamePropertyInfo), '("clear", DOMHTMLBRElementClearPropertyInfo), '("client-height", DOMElementClientHeightPropertyInfo), '("client-left", DOMElementClientLeftPropertyInfo), '("client-top", DOMElementClientTopPropertyInfo), '("client-width", DOMElementClientWidthPropertyInfo), '("content-editable", DOMHTMLElementContentEditablePropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("dir", DOMHTMLElementDirPropertyInfo), '("draggable", DOMHTMLElementDraggablePropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("first-element-child", DOMElementFirstElementChildPropertyInfo), '("hidden", DOMHTMLElementHiddenPropertyInfo), '("id", DOMElementIdPropertyInfo), '("inner-html", DOMHTMLElementInnerHtmlPropertyInfo), '("inner-text", DOMHTMLElementInnerTextPropertyInfo), '("is-content-editable", DOMHTMLElementIsContentEditablePropertyInfo), '("lang", DOMHTMLElementLangPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-element-child", DOMElementLastElementChildPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-element-sibling", DOMElementNextElementSiblingPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("offset-height", DOMElementOffsetHeightPropertyInfo), '("offset-left", DOMElementOffsetLeftPropertyInfo), '("offset-parent", DOMElementOffsetParentPropertyInfo), '("offset-top", DOMElementOffsetTopPropertyInfo), '("offset-width", DOMElementOffsetWidthPropertyInfo), '("outer-html", DOMHTMLElementOuterHtmlPropertyInfo), '("outer-text", DOMHTMLElementOuterTextPropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-element-sibling", DOMElementPreviousElementSiblingPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("scroll-height", DOMElementScrollHeightPropertyInfo), '("scroll-left", DOMElementScrollLeftPropertyInfo), '("scroll-top", DOMElementScrollTopPropertyInfo), '("scroll-width", DOMElementScrollWidthPropertyInfo), '("spellcheck", DOMHTMLElementSpellcheckPropertyInfo), '("style", DOMElementStylePropertyInfo), '("tab-index", DOMHTMLElementTabIndexPropertyInfo), '("tag-name", DOMElementTagNamePropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("title", DOMHTMLElementTitlePropertyInfo), '("translate", DOMHTMLElementTranslatePropertyInfo), '("webkit-region-overset", DOMElementWebkitRegionOversetPropertyInfo), '("webkitdropzone", DOMHTMLElementWebkitdropzonePropertyInfo)] -- VVV Prop "href" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLBaseElementHref :: (MonadIO m, DOMHTMLBaseElementK o) => o -> m T.Text getDOMHTMLBaseElementHref obj = liftIO $ getObjectPropertyString obj "href" setDOMHTMLBaseElementHref :: (MonadIO m, DOMHTMLBaseElementK o) => o -> T.Text -> m () setDOMHTMLBaseElementHref obj val = liftIO $ setObjectPropertyString obj "href" val constructDOMHTMLBaseElementHref :: T.Text -> IO ([Char], GValue) constructDOMHTMLBaseElementHref val = constructObjectPropertyString "href" val data DOMHTMLBaseElementHrefPropertyInfo instance AttrInfo DOMHTMLBaseElementHrefPropertyInfo where type AttrAllowedOps DOMHTMLBaseElementHrefPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLBaseElementHrefPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLBaseElementHrefPropertyInfo = DOMHTMLBaseElementK type AttrGetType DOMHTMLBaseElementHrefPropertyInfo = T.Text type AttrLabel DOMHTMLBaseElementHrefPropertyInfo = "DOMHTMLBaseElement::href" attrGet _ = getDOMHTMLBaseElementHref attrSet _ = setDOMHTMLBaseElementHref attrConstruct _ = constructDOMHTMLBaseElementHref -- VVV Prop "target" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLBaseElementTarget :: (MonadIO m, DOMHTMLBaseElementK o) => o -> m T.Text getDOMHTMLBaseElementTarget obj = liftIO $ getObjectPropertyString obj "target" setDOMHTMLBaseElementTarget :: (MonadIO m, DOMHTMLBaseElementK o) => o -> T.Text -> m () setDOMHTMLBaseElementTarget obj val = liftIO $ setObjectPropertyString obj "target" val constructDOMHTMLBaseElementTarget :: T.Text -> IO ([Char], GValue) constructDOMHTMLBaseElementTarget val = constructObjectPropertyString "target" val data DOMHTMLBaseElementTargetPropertyInfo instance AttrInfo DOMHTMLBaseElementTargetPropertyInfo where type AttrAllowedOps DOMHTMLBaseElementTargetPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLBaseElementTargetPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLBaseElementTargetPropertyInfo = DOMHTMLBaseElementK type AttrGetType DOMHTMLBaseElementTargetPropertyInfo = T.Text type AttrLabel DOMHTMLBaseElementTargetPropertyInfo = "DOMHTMLBaseElement::target" attrGet _ = getDOMHTMLBaseElementTarget attrSet _ = setDOMHTMLBaseElementTarget attrConstruct _ = constructDOMHTMLBaseElementTarget type instance AttributeList DOMHTMLBaseElement = '[ '("access-key", DOMHTMLElementAccessKeyPropertyInfo), '("attributes", DOMElementAttributesPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("child-element-count", DOMElementChildElementCountPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("children", DOMHTMLElementChildrenPropertyInfo), '("class-list", DOMElementClassListPropertyInfo), '("class-name", DOMElementClassNamePropertyInfo), '("client-height", DOMElementClientHeightPropertyInfo), '("client-left", DOMElementClientLeftPropertyInfo), '("client-top", DOMElementClientTopPropertyInfo), '("client-width", DOMElementClientWidthPropertyInfo), '("content-editable", DOMHTMLElementContentEditablePropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("dir", DOMHTMLElementDirPropertyInfo), '("draggable", DOMHTMLElementDraggablePropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("first-element-child", DOMElementFirstElementChildPropertyInfo), '("hidden", DOMHTMLElementHiddenPropertyInfo), '("href", DOMHTMLBaseElementHrefPropertyInfo), '("id", DOMElementIdPropertyInfo), '("inner-html", DOMHTMLElementInnerHtmlPropertyInfo), '("inner-text", DOMHTMLElementInnerTextPropertyInfo), '("is-content-editable", DOMHTMLElementIsContentEditablePropertyInfo), '("lang", DOMHTMLElementLangPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-element-child", DOMElementLastElementChildPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-element-sibling", DOMElementNextElementSiblingPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("offset-height", DOMElementOffsetHeightPropertyInfo), '("offset-left", DOMElementOffsetLeftPropertyInfo), '("offset-parent", DOMElementOffsetParentPropertyInfo), '("offset-top", DOMElementOffsetTopPropertyInfo), '("offset-width", DOMElementOffsetWidthPropertyInfo), '("outer-html", DOMHTMLElementOuterHtmlPropertyInfo), '("outer-text", DOMHTMLElementOuterTextPropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-element-sibling", DOMElementPreviousElementSiblingPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("scroll-height", DOMElementScrollHeightPropertyInfo), '("scroll-left", DOMElementScrollLeftPropertyInfo), '("scroll-top", DOMElementScrollTopPropertyInfo), '("scroll-width", DOMElementScrollWidthPropertyInfo), '("spellcheck", DOMHTMLElementSpellcheckPropertyInfo), '("style", DOMElementStylePropertyInfo), '("tab-index", DOMHTMLElementTabIndexPropertyInfo), '("tag-name", DOMElementTagNamePropertyInfo), '("target", DOMHTMLBaseElementTargetPropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("title", DOMHTMLElementTitlePropertyInfo), '("translate", DOMHTMLElementTranslatePropertyInfo), '("webkit-region-overset", DOMElementWebkitRegionOversetPropertyInfo), '("webkitdropzone", DOMHTMLElementWebkitdropzonePropertyInfo)] -- VVV Prop "color" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLBaseFontElementColor :: (MonadIO m, DOMHTMLBaseFontElementK o) => o -> m T.Text getDOMHTMLBaseFontElementColor obj = liftIO $ getObjectPropertyString obj "color" setDOMHTMLBaseFontElementColor :: (MonadIO m, DOMHTMLBaseFontElementK o) => o -> T.Text -> m () setDOMHTMLBaseFontElementColor obj val = liftIO $ setObjectPropertyString obj "color" val constructDOMHTMLBaseFontElementColor :: T.Text -> IO ([Char], GValue) constructDOMHTMLBaseFontElementColor val = constructObjectPropertyString "color" val data DOMHTMLBaseFontElementColorPropertyInfo instance AttrInfo DOMHTMLBaseFontElementColorPropertyInfo where type AttrAllowedOps DOMHTMLBaseFontElementColorPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLBaseFontElementColorPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLBaseFontElementColorPropertyInfo = DOMHTMLBaseFontElementK type AttrGetType DOMHTMLBaseFontElementColorPropertyInfo = T.Text type AttrLabel DOMHTMLBaseFontElementColorPropertyInfo = "DOMHTMLBaseFontElement::color" attrGet _ = getDOMHTMLBaseFontElementColor attrSet _ = setDOMHTMLBaseFontElementColor attrConstruct _ = constructDOMHTMLBaseFontElementColor -- VVV Prop "face" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLBaseFontElementFace :: (MonadIO m, DOMHTMLBaseFontElementK o) => o -> m T.Text getDOMHTMLBaseFontElementFace obj = liftIO $ getObjectPropertyString obj "face" setDOMHTMLBaseFontElementFace :: (MonadIO m, DOMHTMLBaseFontElementK o) => o -> T.Text -> m () setDOMHTMLBaseFontElementFace obj val = liftIO $ setObjectPropertyString obj "face" val constructDOMHTMLBaseFontElementFace :: T.Text -> IO ([Char], GValue) constructDOMHTMLBaseFontElementFace val = constructObjectPropertyString "face" val data DOMHTMLBaseFontElementFacePropertyInfo instance AttrInfo DOMHTMLBaseFontElementFacePropertyInfo where type AttrAllowedOps DOMHTMLBaseFontElementFacePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLBaseFontElementFacePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLBaseFontElementFacePropertyInfo = DOMHTMLBaseFontElementK type AttrGetType DOMHTMLBaseFontElementFacePropertyInfo = T.Text type AttrLabel DOMHTMLBaseFontElementFacePropertyInfo = "DOMHTMLBaseFontElement::face" attrGet _ = getDOMHTMLBaseFontElementFace attrSet _ = setDOMHTMLBaseFontElementFace attrConstruct _ = constructDOMHTMLBaseFontElementFace -- VVV Prop "size" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLBaseFontElementSize :: (MonadIO m, DOMHTMLBaseFontElementK o) => o -> m Int64 getDOMHTMLBaseFontElementSize obj = liftIO $ getObjectPropertyInt64 obj "size" setDOMHTMLBaseFontElementSize :: (MonadIO m, DOMHTMLBaseFontElementK o) => o -> Int64 -> m () setDOMHTMLBaseFontElementSize obj val = liftIO $ setObjectPropertyInt64 obj "size" val constructDOMHTMLBaseFontElementSize :: Int64 -> IO ([Char], GValue) constructDOMHTMLBaseFontElementSize val = constructObjectPropertyInt64 "size" val data DOMHTMLBaseFontElementSizePropertyInfo instance AttrInfo DOMHTMLBaseFontElementSizePropertyInfo where type AttrAllowedOps DOMHTMLBaseFontElementSizePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLBaseFontElementSizePropertyInfo = (~) Int64 type AttrBaseTypeConstraint DOMHTMLBaseFontElementSizePropertyInfo = DOMHTMLBaseFontElementK type AttrGetType DOMHTMLBaseFontElementSizePropertyInfo = Int64 type AttrLabel DOMHTMLBaseFontElementSizePropertyInfo = "DOMHTMLBaseFontElement::size" attrGet _ = getDOMHTMLBaseFontElementSize attrSet _ = setDOMHTMLBaseFontElementSize attrConstruct _ = constructDOMHTMLBaseFontElementSize type instance AttributeList DOMHTMLBaseFontElement = '[ '("access-key", DOMHTMLElementAccessKeyPropertyInfo), '("attributes", DOMElementAttributesPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("child-element-count", DOMElementChildElementCountPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("children", DOMHTMLElementChildrenPropertyInfo), '("class-list", DOMElementClassListPropertyInfo), '("class-name", DOMElementClassNamePropertyInfo), '("client-height", DOMElementClientHeightPropertyInfo), '("client-left", DOMElementClientLeftPropertyInfo), '("client-top", DOMElementClientTopPropertyInfo), '("client-width", DOMElementClientWidthPropertyInfo), '("color", DOMHTMLBaseFontElementColorPropertyInfo), '("content-editable", DOMHTMLElementContentEditablePropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("dir", DOMHTMLElementDirPropertyInfo), '("draggable", DOMHTMLElementDraggablePropertyInfo), '("face", DOMHTMLBaseFontElementFacePropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("first-element-child", DOMElementFirstElementChildPropertyInfo), '("hidden", DOMHTMLElementHiddenPropertyInfo), '("id", DOMElementIdPropertyInfo), '("inner-html", DOMHTMLElementInnerHtmlPropertyInfo), '("inner-text", DOMHTMLElementInnerTextPropertyInfo), '("is-content-editable", DOMHTMLElementIsContentEditablePropertyInfo), '("lang", DOMHTMLElementLangPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-element-child", DOMElementLastElementChildPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-element-sibling", DOMElementNextElementSiblingPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("offset-height", DOMElementOffsetHeightPropertyInfo), '("offset-left", DOMElementOffsetLeftPropertyInfo), '("offset-parent", DOMElementOffsetParentPropertyInfo), '("offset-top", DOMElementOffsetTopPropertyInfo), '("offset-width", DOMElementOffsetWidthPropertyInfo), '("outer-html", DOMHTMLElementOuterHtmlPropertyInfo), '("outer-text", DOMHTMLElementOuterTextPropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-element-sibling", DOMElementPreviousElementSiblingPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("scroll-height", DOMElementScrollHeightPropertyInfo), '("scroll-left", DOMElementScrollLeftPropertyInfo), '("scroll-top", DOMElementScrollTopPropertyInfo), '("scroll-width", DOMElementScrollWidthPropertyInfo), '("size", DOMHTMLBaseFontElementSizePropertyInfo), '("spellcheck", DOMHTMLElementSpellcheckPropertyInfo), '("style", DOMElementStylePropertyInfo), '("tab-index", DOMHTMLElementTabIndexPropertyInfo), '("tag-name", DOMElementTagNamePropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("title", DOMHTMLElementTitlePropertyInfo), '("translate", DOMHTMLElementTranslatePropertyInfo), '("webkit-region-overset", DOMElementWebkitRegionOversetPropertyInfo), '("webkitdropzone", DOMHTMLElementWebkitdropzonePropertyInfo)] -- VVV Prop "a-link" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLBodyElementALink :: (MonadIO m, DOMHTMLBodyElementK o) => o -> m T.Text getDOMHTMLBodyElementALink obj = liftIO $ getObjectPropertyString obj "a-link" setDOMHTMLBodyElementALink :: (MonadIO m, DOMHTMLBodyElementK o) => o -> T.Text -> m () setDOMHTMLBodyElementALink obj val = liftIO $ setObjectPropertyString obj "a-link" val constructDOMHTMLBodyElementALink :: T.Text -> IO ([Char], GValue) constructDOMHTMLBodyElementALink val = constructObjectPropertyString "a-link" val data DOMHTMLBodyElementALinkPropertyInfo instance AttrInfo DOMHTMLBodyElementALinkPropertyInfo where type AttrAllowedOps DOMHTMLBodyElementALinkPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLBodyElementALinkPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLBodyElementALinkPropertyInfo = DOMHTMLBodyElementK type AttrGetType DOMHTMLBodyElementALinkPropertyInfo = T.Text type AttrLabel DOMHTMLBodyElementALinkPropertyInfo = "DOMHTMLBodyElement::a-link" attrGet _ = getDOMHTMLBodyElementALink attrSet _ = setDOMHTMLBodyElementALink attrConstruct _ = constructDOMHTMLBodyElementALink -- VVV Prop "background" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLBodyElementBackground :: (MonadIO m, DOMHTMLBodyElementK o) => o -> m T.Text getDOMHTMLBodyElementBackground obj = liftIO $ getObjectPropertyString obj "background" setDOMHTMLBodyElementBackground :: (MonadIO m, DOMHTMLBodyElementK o) => o -> T.Text -> m () setDOMHTMLBodyElementBackground obj val = liftIO $ setObjectPropertyString obj "background" val constructDOMHTMLBodyElementBackground :: T.Text -> IO ([Char], GValue) constructDOMHTMLBodyElementBackground val = constructObjectPropertyString "background" val data DOMHTMLBodyElementBackgroundPropertyInfo instance AttrInfo DOMHTMLBodyElementBackgroundPropertyInfo where type AttrAllowedOps DOMHTMLBodyElementBackgroundPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLBodyElementBackgroundPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLBodyElementBackgroundPropertyInfo = DOMHTMLBodyElementK type AttrGetType DOMHTMLBodyElementBackgroundPropertyInfo = T.Text type AttrLabel DOMHTMLBodyElementBackgroundPropertyInfo = "DOMHTMLBodyElement::background" attrGet _ = getDOMHTMLBodyElementBackground attrSet _ = setDOMHTMLBodyElementBackground attrConstruct _ = constructDOMHTMLBodyElementBackground -- VVV Prop "bg-color" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLBodyElementBgColor :: (MonadIO m, DOMHTMLBodyElementK o) => o -> m T.Text getDOMHTMLBodyElementBgColor obj = liftIO $ getObjectPropertyString obj "bg-color" setDOMHTMLBodyElementBgColor :: (MonadIO m, DOMHTMLBodyElementK o) => o -> T.Text -> m () setDOMHTMLBodyElementBgColor obj val = liftIO $ setObjectPropertyString obj "bg-color" val constructDOMHTMLBodyElementBgColor :: T.Text -> IO ([Char], GValue) constructDOMHTMLBodyElementBgColor val = constructObjectPropertyString "bg-color" val data DOMHTMLBodyElementBgColorPropertyInfo instance AttrInfo DOMHTMLBodyElementBgColorPropertyInfo where type AttrAllowedOps DOMHTMLBodyElementBgColorPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLBodyElementBgColorPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLBodyElementBgColorPropertyInfo = DOMHTMLBodyElementK type AttrGetType DOMHTMLBodyElementBgColorPropertyInfo = T.Text type AttrLabel DOMHTMLBodyElementBgColorPropertyInfo = "DOMHTMLBodyElement::bg-color" attrGet _ = getDOMHTMLBodyElementBgColor attrSet _ = setDOMHTMLBodyElementBgColor attrConstruct _ = constructDOMHTMLBodyElementBgColor -- VVV Prop "link" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLBodyElementLink :: (MonadIO m, DOMHTMLBodyElementK o) => o -> m T.Text getDOMHTMLBodyElementLink obj = liftIO $ getObjectPropertyString obj "link" setDOMHTMLBodyElementLink :: (MonadIO m, DOMHTMLBodyElementK o) => o -> T.Text -> m () setDOMHTMLBodyElementLink obj val = liftIO $ setObjectPropertyString obj "link" val constructDOMHTMLBodyElementLink :: T.Text -> IO ([Char], GValue) constructDOMHTMLBodyElementLink val = constructObjectPropertyString "link" val data DOMHTMLBodyElementLinkPropertyInfo instance AttrInfo DOMHTMLBodyElementLinkPropertyInfo where type AttrAllowedOps DOMHTMLBodyElementLinkPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLBodyElementLinkPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLBodyElementLinkPropertyInfo = DOMHTMLBodyElementK type AttrGetType DOMHTMLBodyElementLinkPropertyInfo = T.Text type AttrLabel DOMHTMLBodyElementLinkPropertyInfo = "DOMHTMLBodyElement::link" attrGet _ = getDOMHTMLBodyElementLink attrSet _ = setDOMHTMLBodyElementLink attrConstruct _ = constructDOMHTMLBodyElementLink -- VVV Prop "text" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLBodyElementText :: (MonadIO m, DOMHTMLBodyElementK o) => o -> m T.Text getDOMHTMLBodyElementText obj = liftIO $ getObjectPropertyString obj "text" setDOMHTMLBodyElementText :: (MonadIO m, DOMHTMLBodyElementK o) => o -> T.Text -> m () setDOMHTMLBodyElementText obj val = liftIO $ setObjectPropertyString obj "text" val constructDOMHTMLBodyElementText :: T.Text -> IO ([Char], GValue) constructDOMHTMLBodyElementText val = constructObjectPropertyString "text" val data DOMHTMLBodyElementTextPropertyInfo instance AttrInfo DOMHTMLBodyElementTextPropertyInfo where type AttrAllowedOps DOMHTMLBodyElementTextPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLBodyElementTextPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLBodyElementTextPropertyInfo = DOMHTMLBodyElementK type AttrGetType DOMHTMLBodyElementTextPropertyInfo = T.Text type AttrLabel DOMHTMLBodyElementTextPropertyInfo = "DOMHTMLBodyElement::text" attrGet _ = getDOMHTMLBodyElementText attrSet _ = setDOMHTMLBodyElementText attrConstruct _ = constructDOMHTMLBodyElementText -- VVV Prop "v-link" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLBodyElementVLink :: (MonadIO m, DOMHTMLBodyElementK o) => o -> m T.Text getDOMHTMLBodyElementVLink obj = liftIO $ getObjectPropertyString obj "v-link" setDOMHTMLBodyElementVLink :: (MonadIO m, DOMHTMLBodyElementK o) => o -> T.Text -> m () setDOMHTMLBodyElementVLink obj val = liftIO $ setObjectPropertyString obj "v-link" val constructDOMHTMLBodyElementVLink :: T.Text -> IO ([Char], GValue) constructDOMHTMLBodyElementVLink val = constructObjectPropertyString "v-link" val data DOMHTMLBodyElementVLinkPropertyInfo instance AttrInfo DOMHTMLBodyElementVLinkPropertyInfo where type AttrAllowedOps DOMHTMLBodyElementVLinkPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLBodyElementVLinkPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLBodyElementVLinkPropertyInfo = DOMHTMLBodyElementK type AttrGetType DOMHTMLBodyElementVLinkPropertyInfo = T.Text type AttrLabel DOMHTMLBodyElementVLinkPropertyInfo = "DOMHTMLBodyElement::v-link" attrGet _ = getDOMHTMLBodyElementVLink attrSet _ = setDOMHTMLBodyElementVLink attrConstruct _ = constructDOMHTMLBodyElementVLink type instance AttributeList DOMHTMLBodyElement = '[ '("a-link", DOMHTMLBodyElementALinkPropertyInfo), '("access-key", DOMHTMLElementAccessKeyPropertyInfo), '("attributes", DOMElementAttributesPropertyInfo), '("background", DOMHTMLBodyElementBackgroundPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("bg-color", DOMHTMLBodyElementBgColorPropertyInfo), '("child-element-count", DOMElementChildElementCountPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("children", DOMHTMLElementChildrenPropertyInfo), '("class-list", DOMElementClassListPropertyInfo), '("class-name", DOMElementClassNamePropertyInfo), '("client-height", DOMElementClientHeightPropertyInfo), '("client-left", DOMElementClientLeftPropertyInfo), '("client-top", DOMElementClientTopPropertyInfo), '("client-width", DOMElementClientWidthPropertyInfo), '("content-editable", DOMHTMLElementContentEditablePropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("dir", DOMHTMLElementDirPropertyInfo), '("draggable", DOMHTMLElementDraggablePropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("first-element-child", DOMElementFirstElementChildPropertyInfo), '("hidden", DOMHTMLElementHiddenPropertyInfo), '("id", DOMElementIdPropertyInfo), '("inner-html", DOMHTMLElementInnerHtmlPropertyInfo), '("inner-text", DOMHTMLElementInnerTextPropertyInfo), '("is-content-editable", DOMHTMLElementIsContentEditablePropertyInfo), '("lang", DOMHTMLElementLangPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-element-child", DOMElementLastElementChildPropertyInfo), '("link", DOMHTMLBodyElementLinkPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-element-sibling", DOMElementNextElementSiblingPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("offset-height", DOMElementOffsetHeightPropertyInfo), '("offset-left", DOMElementOffsetLeftPropertyInfo), '("offset-parent", DOMElementOffsetParentPropertyInfo), '("offset-top", DOMElementOffsetTopPropertyInfo), '("offset-width", DOMElementOffsetWidthPropertyInfo), '("outer-html", DOMHTMLElementOuterHtmlPropertyInfo), '("outer-text", DOMHTMLElementOuterTextPropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-element-sibling", DOMElementPreviousElementSiblingPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("scroll-height", DOMElementScrollHeightPropertyInfo), '("scroll-left", DOMElementScrollLeftPropertyInfo), '("scroll-top", DOMElementScrollTopPropertyInfo), '("scroll-width", DOMElementScrollWidthPropertyInfo), '("spellcheck", DOMHTMLElementSpellcheckPropertyInfo), '("style", DOMElementStylePropertyInfo), '("tab-index", DOMHTMLElementTabIndexPropertyInfo), '("tag-name", DOMElementTagNamePropertyInfo), '("text", DOMHTMLBodyElementTextPropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("title", DOMHTMLElementTitlePropertyInfo), '("translate", DOMHTMLElementTranslatePropertyInfo), '("v-link", DOMHTMLBodyElementVLinkPropertyInfo), '("webkit-region-overset", DOMElementWebkitRegionOversetPropertyInfo), '("webkitdropzone", DOMHTMLElementWebkitdropzonePropertyInfo)] -- VVV Prop "autofocus" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLButtonElementAutofocus :: (MonadIO m, DOMHTMLButtonElementK o) => o -> m Bool getDOMHTMLButtonElementAutofocus obj = liftIO $ getObjectPropertyBool obj "autofocus" setDOMHTMLButtonElementAutofocus :: (MonadIO m, DOMHTMLButtonElementK o) => o -> Bool -> m () setDOMHTMLButtonElementAutofocus obj val = liftIO $ setObjectPropertyBool obj "autofocus" val constructDOMHTMLButtonElementAutofocus :: Bool -> IO ([Char], GValue) constructDOMHTMLButtonElementAutofocus val = constructObjectPropertyBool "autofocus" val data DOMHTMLButtonElementAutofocusPropertyInfo instance AttrInfo DOMHTMLButtonElementAutofocusPropertyInfo where type AttrAllowedOps DOMHTMLButtonElementAutofocusPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLButtonElementAutofocusPropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLButtonElementAutofocusPropertyInfo = DOMHTMLButtonElementK type AttrGetType DOMHTMLButtonElementAutofocusPropertyInfo = Bool type AttrLabel DOMHTMLButtonElementAutofocusPropertyInfo = "DOMHTMLButtonElement::autofocus" attrGet _ = getDOMHTMLButtonElementAutofocus attrSet _ = setDOMHTMLButtonElementAutofocus attrConstruct _ = constructDOMHTMLButtonElementAutofocus -- VVV Prop "disabled" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLButtonElementDisabled :: (MonadIO m, DOMHTMLButtonElementK o) => o -> m Bool getDOMHTMLButtonElementDisabled obj = liftIO $ getObjectPropertyBool obj "disabled" setDOMHTMLButtonElementDisabled :: (MonadIO m, DOMHTMLButtonElementK o) => o -> Bool -> m () setDOMHTMLButtonElementDisabled obj val = liftIO $ setObjectPropertyBool obj "disabled" val constructDOMHTMLButtonElementDisabled :: Bool -> IO ([Char], GValue) constructDOMHTMLButtonElementDisabled val = constructObjectPropertyBool "disabled" val data DOMHTMLButtonElementDisabledPropertyInfo instance AttrInfo DOMHTMLButtonElementDisabledPropertyInfo where type AttrAllowedOps DOMHTMLButtonElementDisabledPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLButtonElementDisabledPropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLButtonElementDisabledPropertyInfo = DOMHTMLButtonElementK type AttrGetType DOMHTMLButtonElementDisabledPropertyInfo = Bool type AttrLabel DOMHTMLButtonElementDisabledPropertyInfo = "DOMHTMLButtonElement::disabled" attrGet _ = getDOMHTMLButtonElementDisabled attrSet _ = setDOMHTMLButtonElementDisabled attrConstruct _ = constructDOMHTMLButtonElementDisabled -- VVV Prop "form" -- Type: TInterface "WebKit" "DOMHTMLFormElement" -- Flags: [PropertyReadable] getDOMHTMLButtonElementForm :: (MonadIO m, DOMHTMLButtonElementK o) => o -> m DOMHTMLFormElement getDOMHTMLButtonElementForm obj = liftIO $ getObjectPropertyObject obj "form" DOMHTMLFormElement data DOMHTMLButtonElementFormPropertyInfo instance AttrInfo DOMHTMLButtonElementFormPropertyInfo where type AttrAllowedOps DOMHTMLButtonElementFormPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLButtonElementFormPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLButtonElementFormPropertyInfo = DOMHTMLButtonElementK type AttrGetType DOMHTMLButtonElementFormPropertyInfo = DOMHTMLFormElement type AttrLabel DOMHTMLButtonElementFormPropertyInfo = "DOMHTMLButtonElement::form" attrGet _ = getDOMHTMLButtonElementForm attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "form-action" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLButtonElementFormAction :: (MonadIO m, DOMHTMLButtonElementK o) => o -> m T.Text getDOMHTMLButtonElementFormAction obj = liftIO $ getObjectPropertyString obj "form-action" setDOMHTMLButtonElementFormAction :: (MonadIO m, DOMHTMLButtonElementK o) => o -> T.Text -> m () setDOMHTMLButtonElementFormAction obj val = liftIO $ setObjectPropertyString obj "form-action" val constructDOMHTMLButtonElementFormAction :: T.Text -> IO ([Char], GValue) constructDOMHTMLButtonElementFormAction val = constructObjectPropertyString "form-action" val data DOMHTMLButtonElementFormActionPropertyInfo instance AttrInfo DOMHTMLButtonElementFormActionPropertyInfo where type AttrAllowedOps DOMHTMLButtonElementFormActionPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLButtonElementFormActionPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLButtonElementFormActionPropertyInfo = DOMHTMLButtonElementK type AttrGetType DOMHTMLButtonElementFormActionPropertyInfo = T.Text type AttrLabel DOMHTMLButtonElementFormActionPropertyInfo = "DOMHTMLButtonElement::form-action" attrGet _ = getDOMHTMLButtonElementFormAction attrSet _ = setDOMHTMLButtonElementFormAction attrConstruct _ = constructDOMHTMLButtonElementFormAction -- VVV Prop "form-enctype" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLButtonElementFormEnctype :: (MonadIO m, DOMHTMLButtonElementK o) => o -> m T.Text getDOMHTMLButtonElementFormEnctype obj = liftIO $ getObjectPropertyString obj "form-enctype" setDOMHTMLButtonElementFormEnctype :: (MonadIO m, DOMHTMLButtonElementK o) => o -> T.Text -> m () setDOMHTMLButtonElementFormEnctype obj val = liftIO $ setObjectPropertyString obj "form-enctype" val constructDOMHTMLButtonElementFormEnctype :: T.Text -> IO ([Char], GValue) constructDOMHTMLButtonElementFormEnctype val = constructObjectPropertyString "form-enctype" val data DOMHTMLButtonElementFormEnctypePropertyInfo instance AttrInfo DOMHTMLButtonElementFormEnctypePropertyInfo where type AttrAllowedOps DOMHTMLButtonElementFormEnctypePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLButtonElementFormEnctypePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLButtonElementFormEnctypePropertyInfo = DOMHTMLButtonElementK type AttrGetType DOMHTMLButtonElementFormEnctypePropertyInfo = T.Text type AttrLabel DOMHTMLButtonElementFormEnctypePropertyInfo = "DOMHTMLButtonElement::form-enctype" attrGet _ = getDOMHTMLButtonElementFormEnctype attrSet _ = setDOMHTMLButtonElementFormEnctype attrConstruct _ = constructDOMHTMLButtonElementFormEnctype -- VVV Prop "form-method" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLButtonElementFormMethod :: (MonadIO m, DOMHTMLButtonElementK o) => o -> m T.Text getDOMHTMLButtonElementFormMethod obj = liftIO $ getObjectPropertyString obj "form-method" setDOMHTMLButtonElementFormMethod :: (MonadIO m, DOMHTMLButtonElementK o) => o -> T.Text -> m () setDOMHTMLButtonElementFormMethod obj val = liftIO $ setObjectPropertyString obj "form-method" val constructDOMHTMLButtonElementFormMethod :: T.Text -> IO ([Char], GValue) constructDOMHTMLButtonElementFormMethod val = constructObjectPropertyString "form-method" val data DOMHTMLButtonElementFormMethodPropertyInfo instance AttrInfo DOMHTMLButtonElementFormMethodPropertyInfo where type AttrAllowedOps DOMHTMLButtonElementFormMethodPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLButtonElementFormMethodPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLButtonElementFormMethodPropertyInfo = DOMHTMLButtonElementK type AttrGetType DOMHTMLButtonElementFormMethodPropertyInfo = T.Text type AttrLabel DOMHTMLButtonElementFormMethodPropertyInfo = "DOMHTMLButtonElement::form-method" attrGet _ = getDOMHTMLButtonElementFormMethod attrSet _ = setDOMHTMLButtonElementFormMethod attrConstruct _ = constructDOMHTMLButtonElementFormMethod -- VVV Prop "form-no-validate" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLButtonElementFormNoValidate :: (MonadIO m, DOMHTMLButtonElementK o) => o -> m Bool getDOMHTMLButtonElementFormNoValidate obj = liftIO $ getObjectPropertyBool obj "form-no-validate" setDOMHTMLButtonElementFormNoValidate :: (MonadIO m, DOMHTMLButtonElementK o) => o -> Bool -> m () setDOMHTMLButtonElementFormNoValidate obj val = liftIO $ setObjectPropertyBool obj "form-no-validate" val constructDOMHTMLButtonElementFormNoValidate :: Bool -> IO ([Char], GValue) constructDOMHTMLButtonElementFormNoValidate val = constructObjectPropertyBool "form-no-validate" val data DOMHTMLButtonElementFormNoValidatePropertyInfo instance AttrInfo DOMHTMLButtonElementFormNoValidatePropertyInfo where type AttrAllowedOps DOMHTMLButtonElementFormNoValidatePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLButtonElementFormNoValidatePropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLButtonElementFormNoValidatePropertyInfo = DOMHTMLButtonElementK type AttrGetType DOMHTMLButtonElementFormNoValidatePropertyInfo = Bool type AttrLabel DOMHTMLButtonElementFormNoValidatePropertyInfo = "DOMHTMLButtonElement::form-no-validate" attrGet _ = getDOMHTMLButtonElementFormNoValidate attrSet _ = setDOMHTMLButtonElementFormNoValidate attrConstruct _ = constructDOMHTMLButtonElementFormNoValidate -- VVV Prop "form-target" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLButtonElementFormTarget :: (MonadIO m, DOMHTMLButtonElementK o) => o -> m T.Text getDOMHTMLButtonElementFormTarget obj = liftIO $ getObjectPropertyString obj "form-target" setDOMHTMLButtonElementFormTarget :: (MonadIO m, DOMHTMLButtonElementK o) => o -> T.Text -> m () setDOMHTMLButtonElementFormTarget obj val = liftIO $ setObjectPropertyString obj "form-target" val constructDOMHTMLButtonElementFormTarget :: T.Text -> IO ([Char], GValue) constructDOMHTMLButtonElementFormTarget val = constructObjectPropertyString "form-target" val data DOMHTMLButtonElementFormTargetPropertyInfo instance AttrInfo DOMHTMLButtonElementFormTargetPropertyInfo where type AttrAllowedOps DOMHTMLButtonElementFormTargetPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLButtonElementFormTargetPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLButtonElementFormTargetPropertyInfo = DOMHTMLButtonElementK type AttrGetType DOMHTMLButtonElementFormTargetPropertyInfo = T.Text type AttrLabel DOMHTMLButtonElementFormTargetPropertyInfo = "DOMHTMLButtonElement::form-target" attrGet _ = getDOMHTMLButtonElementFormTarget attrSet _ = setDOMHTMLButtonElementFormTarget attrConstruct _ = constructDOMHTMLButtonElementFormTarget -- VVV Prop "labels" -- Type: TInterface "WebKit" "DOMNodeList" -- Flags: [PropertyReadable] getDOMHTMLButtonElementLabels :: (MonadIO m, DOMHTMLButtonElementK o) => o -> m DOMNodeList getDOMHTMLButtonElementLabels obj = liftIO $ getObjectPropertyObject obj "labels" DOMNodeList data DOMHTMLButtonElementLabelsPropertyInfo instance AttrInfo DOMHTMLButtonElementLabelsPropertyInfo where type AttrAllowedOps DOMHTMLButtonElementLabelsPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLButtonElementLabelsPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLButtonElementLabelsPropertyInfo = DOMHTMLButtonElementK type AttrGetType DOMHTMLButtonElementLabelsPropertyInfo = DOMNodeList type AttrLabel DOMHTMLButtonElementLabelsPropertyInfo = "DOMHTMLButtonElement::labels" attrGet _ = getDOMHTMLButtonElementLabels attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "name" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLButtonElementName :: (MonadIO m, DOMHTMLButtonElementK o) => o -> m T.Text getDOMHTMLButtonElementName obj = liftIO $ getObjectPropertyString obj "name" setDOMHTMLButtonElementName :: (MonadIO m, DOMHTMLButtonElementK o) => o -> T.Text -> m () setDOMHTMLButtonElementName obj val = liftIO $ setObjectPropertyString obj "name" val constructDOMHTMLButtonElementName :: T.Text -> IO ([Char], GValue) constructDOMHTMLButtonElementName val = constructObjectPropertyString "name" val data DOMHTMLButtonElementNamePropertyInfo instance AttrInfo DOMHTMLButtonElementNamePropertyInfo where type AttrAllowedOps DOMHTMLButtonElementNamePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLButtonElementNamePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLButtonElementNamePropertyInfo = DOMHTMLButtonElementK type AttrGetType DOMHTMLButtonElementNamePropertyInfo = T.Text type AttrLabel DOMHTMLButtonElementNamePropertyInfo = "DOMHTMLButtonElement::name" attrGet _ = getDOMHTMLButtonElementName attrSet _ = setDOMHTMLButtonElementName attrConstruct _ = constructDOMHTMLButtonElementName -- VVV Prop "type" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLButtonElementType :: (MonadIO m, DOMHTMLButtonElementK o) => o -> m T.Text getDOMHTMLButtonElementType obj = liftIO $ getObjectPropertyString obj "type" setDOMHTMLButtonElementType :: (MonadIO m, DOMHTMLButtonElementK o) => o -> T.Text -> m () setDOMHTMLButtonElementType obj val = liftIO $ setObjectPropertyString obj "type" val constructDOMHTMLButtonElementType :: T.Text -> IO ([Char], GValue) constructDOMHTMLButtonElementType val = constructObjectPropertyString "type" val data DOMHTMLButtonElementTypePropertyInfo instance AttrInfo DOMHTMLButtonElementTypePropertyInfo where type AttrAllowedOps DOMHTMLButtonElementTypePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLButtonElementTypePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLButtonElementTypePropertyInfo = DOMHTMLButtonElementK type AttrGetType DOMHTMLButtonElementTypePropertyInfo = T.Text type AttrLabel DOMHTMLButtonElementTypePropertyInfo = "DOMHTMLButtonElement::type" attrGet _ = getDOMHTMLButtonElementType attrSet _ = setDOMHTMLButtonElementType attrConstruct _ = constructDOMHTMLButtonElementType -- VVV Prop "validation-message" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMHTMLButtonElementValidationMessage :: (MonadIO m, DOMHTMLButtonElementK o) => o -> m T.Text getDOMHTMLButtonElementValidationMessage obj = liftIO $ getObjectPropertyString obj "validation-message" data DOMHTMLButtonElementValidationMessagePropertyInfo instance AttrInfo DOMHTMLButtonElementValidationMessagePropertyInfo where type AttrAllowedOps DOMHTMLButtonElementValidationMessagePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLButtonElementValidationMessagePropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLButtonElementValidationMessagePropertyInfo = DOMHTMLButtonElementK type AttrGetType DOMHTMLButtonElementValidationMessagePropertyInfo = T.Text type AttrLabel DOMHTMLButtonElementValidationMessagePropertyInfo = "DOMHTMLButtonElement::validation-message" attrGet _ = getDOMHTMLButtonElementValidationMessage attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "validity" -- Type: TInterface "WebKit" "DOMValidityState" -- Flags: [PropertyReadable] getDOMHTMLButtonElementValidity :: (MonadIO m, DOMHTMLButtonElementK o) => o -> m DOMValidityState getDOMHTMLButtonElementValidity obj = liftIO $ getObjectPropertyObject obj "validity" DOMValidityState data DOMHTMLButtonElementValidityPropertyInfo instance AttrInfo DOMHTMLButtonElementValidityPropertyInfo where type AttrAllowedOps DOMHTMLButtonElementValidityPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLButtonElementValidityPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLButtonElementValidityPropertyInfo = DOMHTMLButtonElementK type AttrGetType DOMHTMLButtonElementValidityPropertyInfo = DOMValidityState type AttrLabel DOMHTMLButtonElementValidityPropertyInfo = "DOMHTMLButtonElement::validity" attrGet _ = getDOMHTMLButtonElementValidity attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "value" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLButtonElementValue :: (MonadIO m, DOMHTMLButtonElementK o) => o -> m T.Text getDOMHTMLButtonElementValue obj = liftIO $ getObjectPropertyString obj "value" setDOMHTMLButtonElementValue :: (MonadIO m, DOMHTMLButtonElementK o) => o -> T.Text -> m () setDOMHTMLButtonElementValue obj val = liftIO $ setObjectPropertyString obj "value" val constructDOMHTMLButtonElementValue :: T.Text -> IO ([Char], GValue) constructDOMHTMLButtonElementValue val = constructObjectPropertyString "value" val data DOMHTMLButtonElementValuePropertyInfo instance AttrInfo DOMHTMLButtonElementValuePropertyInfo where type AttrAllowedOps DOMHTMLButtonElementValuePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLButtonElementValuePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLButtonElementValuePropertyInfo = DOMHTMLButtonElementK type AttrGetType DOMHTMLButtonElementValuePropertyInfo = T.Text type AttrLabel DOMHTMLButtonElementValuePropertyInfo = "DOMHTMLButtonElement::value" attrGet _ = getDOMHTMLButtonElementValue attrSet _ = setDOMHTMLButtonElementValue attrConstruct _ = constructDOMHTMLButtonElementValue -- VVV Prop "will-validate" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMHTMLButtonElementWillValidate :: (MonadIO m, DOMHTMLButtonElementK o) => o -> m Bool getDOMHTMLButtonElementWillValidate obj = liftIO $ getObjectPropertyBool obj "will-validate" data DOMHTMLButtonElementWillValidatePropertyInfo instance AttrInfo DOMHTMLButtonElementWillValidatePropertyInfo where type AttrAllowedOps DOMHTMLButtonElementWillValidatePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLButtonElementWillValidatePropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLButtonElementWillValidatePropertyInfo = DOMHTMLButtonElementK type AttrGetType DOMHTMLButtonElementWillValidatePropertyInfo = Bool type AttrLabel DOMHTMLButtonElementWillValidatePropertyInfo = "DOMHTMLButtonElement::will-validate" attrGet _ = getDOMHTMLButtonElementWillValidate attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMHTMLButtonElement = '[ '("access-key", DOMHTMLElementAccessKeyPropertyInfo), '("attributes", DOMElementAttributesPropertyInfo), '("autofocus", DOMHTMLButtonElementAutofocusPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("child-element-count", DOMElementChildElementCountPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("children", DOMHTMLElementChildrenPropertyInfo), '("class-list", DOMElementClassListPropertyInfo), '("class-name", DOMElementClassNamePropertyInfo), '("client-height", DOMElementClientHeightPropertyInfo), '("client-left", DOMElementClientLeftPropertyInfo), '("client-top", DOMElementClientTopPropertyInfo), '("client-width", DOMElementClientWidthPropertyInfo), '("content-editable", DOMHTMLElementContentEditablePropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("dir", DOMHTMLElementDirPropertyInfo), '("disabled", DOMHTMLButtonElementDisabledPropertyInfo), '("draggable", DOMHTMLElementDraggablePropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("first-element-child", DOMElementFirstElementChildPropertyInfo), '("form", DOMHTMLButtonElementFormPropertyInfo), '("form-action", DOMHTMLButtonElementFormActionPropertyInfo), '("form-enctype", DOMHTMLButtonElementFormEnctypePropertyInfo), '("form-method", DOMHTMLButtonElementFormMethodPropertyInfo), '("form-no-validate", DOMHTMLButtonElementFormNoValidatePropertyInfo), '("form-target", DOMHTMLButtonElementFormTargetPropertyInfo), '("hidden", DOMHTMLElementHiddenPropertyInfo), '("id", DOMElementIdPropertyInfo), '("inner-html", DOMHTMLElementInnerHtmlPropertyInfo), '("inner-text", DOMHTMLElementInnerTextPropertyInfo), '("is-content-editable", DOMHTMLElementIsContentEditablePropertyInfo), '("labels", DOMHTMLButtonElementLabelsPropertyInfo), '("lang", DOMHTMLElementLangPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-element-child", DOMElementLastElementChildPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("name", DOMHTMLButtonElementNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-element-sibling", DOMElementNextElementSiblingPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("offset-height", DOMElementOffsetHeightPropertyInfo), '("offset-left", DOMElementOffsetLeftPropertyInfo), '("offset-parent", DOMElementOffsetParentPropertyInfo), '("offset-top", DOMElementOffsetTopPropertyInfo), '("offset-width", DOMElementOffsetWidthPropertyInfo), '("outer-html", DOMHTMLElementOuterHtmlPropertyInfo), '("outer-text", DOMHTMLElementOuterTextPropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-element-sibling", DOMElementPreviousElementSiblingPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("scroll-height", DOMElementScrollHeightPropertyInfo), '("scroll-left", DOMElementScrollLeftPropertyInfo), '("scroll-top", DOMElementScrollTopPropertyInfo), '("scroll-width", DOMElementScrollWidthPropertyInfo), '("spellcheck", DOMHTMLElementSpellcheckPropertyInfo), '("style", DOMElementStylePropertyInfo), '("tab-index", DOMHTMLElementTabIndexPropertyInfo), '("tag-name", DOMElementTagNamePropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("title", DOMHTMLElementTitlePropertyInfo), '("translate", DOMHTMLElementTranslatePropertyInfo), '("type", DOMHTMLButtonElementTypePropertyInfo), '("validation-message", DOMHTMLButtonElementValidationMessagePropertyInfo), '("validity", DOMHTMLButtonElementValidityPropertyInfo), '("value", DOMHTMLButtonElementValuePropertyInfo), '("webkit-region-overset", DOMElementWebkitRegionOversetPropertyInfo), '("webkitdropzone", DOMHTMLElementWebkitdropzonePropertyInfo), '("will-validate", DOMHTMLButtonElementWillValidatePropertyInfo)] -- VVV Prop "height" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLCanvasElementHeight :: (MonadIO m, DOMHTMLCanvasElementK o) => o -> m Int64 getDOMHTMLCanvasElementHeight obj = liftIO $ getObjectPropertyInt64 obj "height" setDOMHTMLCanvasElementHeight :: (MonadIO m, DOMHTMLCanvasElementK o) => o -> Int64 -> m () setDOMHTMLCanvasElementHeight obj val = liftIO $ setObjectPropertyInt64 obj "height" val constructDOMHTMLCanvasElementHeight :: Int64 -> IO ([Char], GValue) constructDOMHTMLCanvasElementHeight val = constructObjectPropertyInt64 "height" val data DOMHTMLCanvasElementHeightPropertyInfo instance AttrInfo DOMHTMLCanvasElementHeightPropertyInfo where type AttrAllowedOps DOMHTMLCanvasElementHeightPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLCanvasElementHeightPropertyInfo = (~) Int64 type AttrBaseTypeConstraint DOMHTMLCanvasElementHeightPropertyInfo = DOMHTMLCanvasElementK type AttrGetType DOMHTMLCanvasElementHeightPropertyInfo = Int64 type AttrLabel DOMHTMLCanvasElementHeightPropertyInfo = "DOMHTMLCanvasElement::height" attrGet _ = getDOMHTMLCanvasElementHeight attrSet _ = setDOMHTMLCanvasElementHeight attrConstruct _ = constructDOMHTMLCanvasElementHeight -- VVV Prop "width" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLCanvasElementWidth :: (MonadIO m, DOMHTMLCanvasElementK o) => o -> m Int64 getDOMHTMLCanvasElementWidth obj = liftIO $ getObjectPropertyInt64 obj "width" setDOMHTMLCanvasElementWidth :: (MonadIO m, DOMHTMLCanvasElementK o) => o -> Int64 -> m () setDOMHTMLCanvasElementWidth obj val = liftIO $ setObjectPropertyInt64 obj "width" val constructDOMHTMLCanvasElementWidth :: Int64 -> IO ([Char], GValue) constructDOMHTMLCanvasElementWidth val = constructObjectPropertyInt64 "width" val data DOMHTMLCanvasElementWidthPropertyInfo instance AttrInfo DOMHTMLCanvasElementWidthPropertyInfo where type AttrAllowedOps DOMHTMLCanvasElementWidthPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLCanvasElementWidthPropertyInfo = (~) Int64 type AttrBaseTypeConstraint DOMHTMLCanvasElementWidthPropertyInfo = DOMHTMLCanvasElementK type AttrGetType DOMHTMLCanvasElementWidthPropertyInfo = Int64 type AttrLabel DOMHTMLCanvasElementWidthPropertyInfo = "DOMHTMLCanvasElement::width" attrGet _ = getDOMHTMLCanvasElementWidth attrSet _ = setDOMHTMLCanvasElementWidth attrConstruct _ = constructDOMHTMLCanvasElementWidth type instance AttributeList DOMHTMLCanvasElement = '[ '("access-key", DOMHTMLElementAccessKeyPropertyInfo), '("attributes", DOMElementAttributesPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("child-element-count", DOMElementChildElementCountPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("children", DOMHTMLElementChildrenPropertyInfo), '("class-list", DOMElementClassListPropertyInfo), '("class-name", DOMElementClassNamePropertyInfo), '("client-height", DOMElementClientHeightPropertyInfo), '("client-left", DOMElementClientLeftPropertyInfo), '("client-top", DOMElementClientTopPropertyInfo), '("client-width", DOMElementClientWidthPropertyInfo), '("content-editable", DOMHTMLElementContentEditablePropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("dir", DOMHTMLElementDirPropertyInfo), '("draggable", DOMHTMLElementDraggablePropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("first-element-child", DOMElementFirstElementChildPropertyInfo), '("height", DOMHTMLCanvasElementHeightPropertyInfo), '("hidden", DOMHTMLElementHiddenPropertyInfo), '("id", DOMElementIdPropertyInfo), '("inner-html", DOMHTMLElementInnerHtmlPropertyInfo), '("inner-text", DOMHTMLElementInnerTextPropertyInfo), '("is-content-editable", DOMHTMLElementIsContentEditablePropertyInfo), '("lang", DOMHTMLElementLangPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-element-child", DOMElementLastElementChildPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-element-sibling", DOMElementNextElementSiblingPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("offset-height", DOMElementOffsetHeightPropertyInfo), '("offset-left", DOMElementOffsetLeftPropertyInfo), '("offset-parent", DOMElementOffsetParentPropertyInfo), '("offset-top", DOMElementOffsetTopPropertyInfo), '("offset-width", DOMElementOffsetWidthPropertyInfo), '("outer-html", DOMHTMLElementOuterHtmlPropertyInfo), '("outer-text", DOMHTMLElementOuterTextPropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-element-sibling", DOMElementPreviousElementSiblingPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("scroll-height", DOMElementScrollHeightPropertyInfo), '("scroll-left", DOMElementScrollLeftPropertyInfo), '("scroll-top", DOMElementScrollTopPropertyInfo), '("scroll-width", DOMElementScrollWidthPropertyInfo), '("spellcheck", DOMHTMLElementSpellcheckPropertyInfo), '("style", DOMElementStylePropertyInfo), '("tab-index", DOMHTMLElementTabIndexPropertyInfo), '("tag-name", DOMElementTagNamePropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("title", DOMHTMLElementTitlePropertyInfo), '("translate", DOMHTMLElementTranslatePropertyInfo), '("webkit-region-overset", DOMElementWebkitRegionOversetPropertyInfo), '("webkitdropzone", DOMHTMLElementWebkitdropzonePropertyInfo), '("width", DOMHTMLCanvasElementWidthPropertyInfo)] -- VVV Prop "length" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMHTMLCollectionLength :: (MonadIO m, DOMHTMLCollectionK o) => o -> m Word64 getDOMHTMLCollectionLength obj = liftIO $ getObjectPropertyUInt64 obj "length" data DOMHTMLCollectionLengthPropertyInfo instance AttrInfo DOMHTMLCollectionLengthPropertyInfo where type AttrAllowedOps DOMHTMLCollectionLengthPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLCollectionLengthPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLCollectionLengthPropertyInfo = DOMHTMLCollectionK type AttrGetType DOMHTMLCollectionLengthPropertyInfo = Word64 type AttrLabel DOMHTMLCollectionLengthPropertyInfo = "DOMHTMLCollection::length" attrGet _ = getDOMHTMLCollectionLength attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMHTMLCollection = '[ '("core-object", DOMObjectCoreObjectPropertyInfo), '("length", DOMHTMLCollectionLengthPropertyInfo)] -- VVV Prop "compact" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLDListElementCompact :: (MonadIO m, DOMHTMLDListElementK o) => o -> m Bool getDOMHTMLDListElementCompact obj = liftIO $ getObjectPropertyBool obj "compact" setDOMHTMLDListElementCompact :: (MonadIO m, DOMHTMLDListElementK o) => o -> Bool -> m () setDOMHTMLDListElementCompact obj val = liftIO $ setObjectPropertyBool obj "compact" val constructDOMHTMLDListElementCompact :: Bool -> IO ([Char], GValue) constructDOMHTMLDListElementCompact val = constructObjectPropertyBool "compact" val data DOMHTMLDListElementCompactPropertyInfo instance AttrInfo DOMHTMLDListElementCompactPropertyInfo where type AttrAllowedOps DOMHTMLDListElementCompactPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLDListElementCompactPropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLDListElementCompactPropertyInfo = DOMHTMLDListElementK type AttrGetType DOMHTMLDListElementCompactPropertyInfo = Bool type AttrLabel DOMHTMLDListElementCompactPropertyInfo = "DOMHTMLDListElement::compact" attrGet _ = getDOMHTMLDListElementCompact attrSet _ = setDOMHTMLDListElementCompact attrConstruct _ = constructDOMHTMLDListElementCompact type instance AttributeList DOMHTMLDListElement = '[ '("access-key", DOMHTMLElementAccessKeyPropertyInfo), '("attributes", DOMElementAttributesPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("child-element-count", DOMElementChildElementCountPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("children", DOMHTMLElementChildrenPropertyInfo), '("class-list", DOMElementClassListPropertyInfo), '("class-name", DOMElementClassNamePropertyInfo), '("client-height", DOMElementClientHeightPropertyInfo), '("client-left", DOMElementClientLeftPropertyInfo), '("client-top", DOMElementClientTopPropertyInfo), '("client-width", DOMElementClientWidthPropertyInfo), '("compact", DOMHTMLDListElementCompactPropertyInfo), '("content-editable", DOMHTMLElementContentEditablePropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("dir", DOMHTMLElementDirPropertyInfo), '("draggable", DOMHTMLElementDraggablePropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("first-element-child", DOMElementFirstElementChildPropertyInfo), '("hidden", DOMHTMLElementHiddenPropertyInfo), '("id", DOMElementIdPropertyInfo), '("inner-html", DOMHTMLElementInnerHtmlPropertyInfo), '("inner-text", DOMHTMLElementInnerTextPropertyInfo), '("is-content-editable", DOMHTMLElementIsContentEditablePropertyInfo), '("lang", DOMHTMLElementLangPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-element-child", DOMElementLastElementChildPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-element-sibling", DOMElementNextElementSiblingPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("offset-height", DOMElementOffsetHeightPropertyInfo), '("offset-left", DOMElementOffsetLeftPropertyInfo), '("offset-parent", DOMElementOffsetParentPropertyInfo), '("offset-top", DOMElementOffsetTopPropertyInfo), '("offset-width", DOMElementOffsetWidthPropertyInfo), '("outer-html", DOMHTMLElementOuterHtmlPropertyInfo), '("outer-text", DOMHTMLElementOuterTextPropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-element-sibling", DOMElementPreviousElementSiblingPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("scroll-height", DOMElementScrollHeightPropertyInfo), '("scroll-left", DOMElementScrollLeftPropertyInfo), '("scroll-top", DOMElementScrollTopPropertyInfo), '("scroll-width", DOMElementScrollWidthPropertyInfo), '("spellcheck", DOMHTMLElementSpellcheckPropertyInfo), '("style", DOMElementStylePropertyInfo), '("tab-index", DOMHTMLElementTabIndexPropertyInfo), '("tag-name", DOMElementTagNamePropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("title", DOMHTMLElementTitlePropertyInfo), '("translate", DOMHTMLElementTranslatePropertyInfo), '("webkit-region-overset", DOMElementWebkitRegionOversetPropertyInfo), '("webkitdropzone", DOMHTMLElementWebkitdropzonePropertyInfo)] -- VVV Prop "open" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLDetailsElementOpen :: (MonadIO m, DOMHTMLDetailsElementK o) => o -> m Bool getDOMHTMLDetailsElementOpen obj = liftIO $ getObjectPropertyBool obj "open" setDOMHTMLDetailsElementOpen :: (MonadIO m, DOMHTMLDetailsElementK o) => o -> Bool -> m () setDOMHTMLDetailsElementOpen obj val = liftIO $ setObjectPropertyBool obj "open" val constructDOMHTMLDetailsElementOpen :: Bool -> IO ([Char], GValue) constructDOMHTMLDetailsElementOpen val = constructObjectPropertyBool "open" val data DOMHTMLDetailsElementOpenPropertyInfo instance AttrInfo DOMHTMLDetailsElementOpenPropertyInfo where type AttrAllowedOps DOMHTMLDetailsElementOpenPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLDetailsElementOpenPropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLDetailsElementOpenPropertyInfo = DOMHTMLDetailsElementK type AttrGetType DOMHTMLDetailsElementOpenPropertyInfo = Bool type AttrLabel DOMHTMLDetailsElementOpenPropertyInfo = "DOMHTMLDetailsElement::open" attrGet _ = getDOMHTMLDetailsElementOpen attrSet _ = setDOMHTMLDetailsElementOpen attrConstruct _ = constructDOMHTMLDetailsElementOpen type instance AttributeList DOMHTMLDetailsElement = '[ '("access-key", DOMHTMLElementAccessKeyPropertyInfo), '("attributes", DOMElementAttributesPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("child-element-count", DOMElementChildElementCountPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("children", DOMHTMLElementChildrenPropertyInfo), '("class-list", DOMElementClassListPropertyInfo), '("class-name", DOMElementClassNamePropertyInfo), '("client-height", DOMElementClientHeightPropertyInfo), '("client-left", DOMElementClientLeftPropertyInfo), '("client-top", DOMElementClientTopPropertyInfo), '("client-width", DOMElementClientWidthPropertyInfo), '("content-editable", DOMHTMLElementContentEditablePropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("dir", DOMHTMLElementDirPropertyInfo), '("draggable", DOMHTMLElementDraggablePropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("first-element-child", DOMElementFirstElementChildPropertyInfo), '("hidden", DOMHTMLElementHiddenPropertyInfo), '("id", DOMElementIdPropertyInfo), '("inner-html", DOMHTMLElementInnerHtmlPropertyInfo), '("inner-text", DOMHTMLElementInnerTextPropertyInfo), '("is-content-editable", DOMHTMLElementIsContentEditablePropertyInfo), '("lang", DOMHTMLElementLangPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-element-child", DOMElementLastElementChildPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-element-sibling", DOMElementNextElementSiblingPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("offset-height", DOMElementOffsetHeightPropertyInfo), '("offset-left", DOMElementOffsetLeftPropertyInfo), '("offset-parent", DOMElementOffsetParentPropertyInfo), '("offset-top", DOMElementOffsetTopPropertyInfo), '("offset-width", DOMElementOffsetWidthPropertyInfo), '("open", DOMHTMLDetailsElementOpenPropertyInfo), '("outer-html", DOMHTMLElementOuterHtmlPropertyInfo), '("outer-text", DOMHTMLElementOuterTextPropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-element-sibling", DOMElementPreviousElementSiblingPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("scroll-height", DOMElementScrollHeightPropertyInfo), '("scroll-left", DOMElementScrollLeftPropertyInfo), '("scroll-top", DOMElementScrollTopPropertyInfo), '("scroll-width", DOMElementScrollWidthPropertyInfo), '("spellcheck", DOMHTMLElementSpellcheckPropertyInfo), '("style", DOMElementStylePropertyInfo), '("tab-index", DOMHTMLElementTabIndexPropertyInfo), '("tag-name", DOMElementTagNamePropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("title", DOMHTMLElementTitlePropertyInfo), '("translate", DOMHTMLElementTranslatePropertyInfo), '("webkit-region-overset", DOMElementWebkitRegionOversetPropertyInfo), '("webkitdropzone", DOMHTMLElementWebkitdropzonePropertyInfo)] -- VVV Prop "compact" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLDirectoryElementCompact :: (MonadIO m, DOMHTMLDirectoryElementK o) => o -> m Bool getDOMHTMLDirectoryElementCompact obj = liftIO $ getObjectPropertyBool obj "compact" setDOMHTMLDirectoryElementCompact :: (MonadIO m, DOMHTMLDirectoryElementK o) => o -> Bool -> m () setDOMHTMLDirectoryElementCompact obj val = liftIO $ setObjectPropertyBool obj "compact" val constructDOMHTMLDirectoryElementCompact :: Bool -> IO ([Char], GValue) constructDOMHTMLDirectoryElementCompact val = constructObjectPropertyBool "compact" val data DOMHTMLDirectoryElementCompactPropertyInfo instance AttrInfo DOMHTMLDirectoryElementCompactPropertyInfo where type AttrAllowedOps DOMHTMLDirectoryElementCompactPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLDirectoryElementCompactPropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLDirectoryElementCompactPropertyInfo = DOMHTMLDirectoryElementK type AttrGetType DOMHTMLDirectoryElementCompactPropertyInfo = Bool type AttrLabel DOMHTMLDirectoryElementCompactPropertyInfo = "DOMHTMLDirectoryElement::compact" attrGet _ = getDOMHTMLDirectoryElementCompact attrSet _ = setDOMHTMLDirectoryElementCompact attrConstruct _ = constructDOMHTMLDirectoryElementCompact type instance AttributeList DOMHTMLDirectoryElement = '[ '("access-key", DOMHTMLElementAccessKeyPropertyInfo), '("attributes", DOMElementAttributesPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("child-element-count", DOMElementChildElementCountPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("children", DOMHTMLElementChildrenPropertyInfo), '("class-list", DOMElementClassListPropertyInfo), '("class-name", DOMElementClassNamePropertyInfo), '("client-height", DOMElementClientHeightPropertyInfo), '("client-left", DOMElementClientLeftPropertyInfo), '("client-top", DOMElementClientTopPropertyInfo), '("client-width", DOMElementClientWidthPropertyInfo), '("compact", DOMHTMLDirectoryElementCompactPropertyInfo), '("content-editable", DOMHTMLElementContentEditablePropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("dir", DOMHTMLElementDirPropertyInfo), '("draggable", DOMHTMLElementDraggablePropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("first-element-child", DOMElementFirstElementChildPropertyInfo), '("hidden", DOMHTMLElementHiddenPropertyInfo), '("id", DOMElementIdPropertyInfo), '("inner-html", DOMHTMLElementInnerHtmlPropertyInfo), '("inner-text", DOMHTMLElementInnerTextPropertyInfo), '("is-content-editable", DOMHTMLElementIsContentEditablePropertyInfo), '("lang", DOMHTMLElementLangPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-element-child", DOMElementLastElementChildPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-element-sibling", DOMElementNextElementSiblingPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("offset-height", DOMElementOffsetHeightPropertyInfo), '("offset-left", DOMElementOffsetLeftPropertyInfo), '("offset-parent", DOMElementOffsetParentPropertyInfo), '("offset-top", DOMElementOffsetTopPropertyInfo), '("offset-width", DOMElementOffsetWidthPropertyInfo), '("outer-html", DOMHTMLElementOuterHtmlPropertyInfo), '("outer-text", DOMHTMLElementOuterTextPropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-element-sibling", DOMElementPreviousElementSiblingPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("scroll-height", DOMElementScrollHeightPropertyInfo), '("scroll-left", DOMElementScrollLeftPropertyInfo), '("scroll-top", DOMElementScrollTopPropertyInfo), '("scroll-width", DOMElementScrollWidthPropertyInfo), '("spellcheck", DOMHTMLElementSpellcheckPropertyInfo), '("style", DOMElementStylePropertyInfo), '("tab-index", DOMHTMLElementTabIndexPropertyInfo), '("tag-name", DOMElementTagNamePropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("title", DOMHTMLElementTitlePropertyInfo), '("translate", DOMHTMLElementTranslatePropertyInfo), '("webkit-region-overset", DOMElementWebkitRegionOversetPropertyInfo), '("webkitdropzone", DOMHTMLElementWebkitdropzonePropertyInfo)] -- VVV Prop "align" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLDivElementAlign :: (MonadIO m, DOMHTMLDivElementK o) => o -> m T.Text getDOMHTMLDivElementAlign obj = liftIO $ getObjectPropertyString obj "align" setDOMHTMLDivElementAlign :: (MonadIO m, DOMHTMLDivElementK o) => o -> T.Text -> m () setDOMHTMLDivElementAlign obj val = liftIO $ setObjectPropertyString obj "align" val constructDOMHTMLDivElementAlign :: T.Text -> IO ([Char], GValue) constructDOMHTMLDivElementAlign val = constructObjectPropertyString "align" val data DOMHTMLDivElementAlignPropertyInfo instance AttrInfo DOMHTMLDivElementAlignPropertyInfo where type AttrAllowedOps DOMHTMLDivElementAlignPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLDivElementAlignPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLDivElementAlignPropertyInfo = DOMHTMLDivElementK type AttrGetType DOMHTMLDivElementAlignPropertyInfo = T.Text type AttrLabel DOMHTMLDivElementAlignPropertyInfo = "DOMHTMLDivElement::align" attrGet _ = getDOMHTMLDivElementAlign attrSet _ = setDOMHTMLDivElementAlign attrConstruct _ = constructDOMHTMLDivElementAlign type instance AttributeList DOMHTMLDivElement = '[ '("access-key", DOMHTMLElementAccessKeyPropertyInfo), '("align", DOMHTMLDivElementAlignPropertyInfo), '("attributes", DOMElementAttributesPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("child-element-count", DOMElementChildElementCountPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("children", DOMHTMLElementChildrenPropertyInfo), '("class-list", DOMElementClassListPropertyInfo), '("class-name", DOMElementClassNamePropertyInfo), '("client-height", DOMElementClientHeightPropertyInfo), '("client-left", DOMElementClientLeftPropertyInfo), '("client-top", DOMElementClientTopPropertyInfo), '("client-width", DOMElementClientWidthPropertyInfo), '("content-editable", DOMHTMLElementContentEditablePropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("dir", DOMHTMLElementDirPropertyInfo), '("draggable", DOMHTMLElementDraggablePropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("first-element-child", DOMElementFirstElementChildPropertyInfo), '("hidden", DOMHTMLElementHiddenPropertyInfo), '("id", DOMElementIdPropertyInfo), '("inner-html", DOMHTMLElementInnerHtmlPropertyInfo), '("inner-text", DOMHTMLElementInnerTextPropertyInfo), '("is-content-editable", DOMHTMLElementIsContentEditablePropertyInfo), '("lang", DOMHTMLElementLangPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-element-child", DOMElementLastElementChildPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-element-sibling", DOMElementNextElementSiblingPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("offset-height", DOMElementOffsetHeightPropertyInfo), '("offset-left", DOMElementOffsetLeftPropertyInfo), '("offset-parent", DOMElementOffsetParentPropertyInfo), '("offset-top", DOMElementOffsetTopPropertyInfo), '("offset-width", DOMElementOffsetWidthPropertyInfo), '("outer-html", DOMHTMLElementOuterHtmlPropertyInfo), '("outer-text", DOMHTMLElementOuterTextPropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-element-sibling", DOMElementPreviousElementSiblingPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("scroll-height", DOMElementScrollHeightPropertyInfo), '("scroll-left", DOMElementScrollLeftPropertyInfo), '("scroll-top", DOMElementScrollTopPropertyInfo), '("scroll-width", DOMElementScrollWidthPropertyInfo), '("spellcheck", DOMHTMLElementSpellcheckPropertyInfo), '("style", DOMElementStylePropertyInfo), '("tab-index", DOMHTMLElementTabIndexPropertyInfo), '("tag-name", DOMElementTagNamePropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("title", DOMHTMLElementTitlePropertyInfo), '("translate", DOMHTMLElementTranslatePropertyInfo), '("webkit-region-overset", DOMElementWebkitRegionOversetPropertyInfo), '("webkitdropzone", DOMHTMLElementWebkitdropzonePropertyInfo)] -- VVV Prop "active-element" -- Type: TInterface "WebKit" "DOMElement" -- Flags: [PropertyReadable] getDOMHTMLDocumentActiveElement :: (MonadIO m, DOMHTMLDocumentK o) => o -> m DOMElement getDOMHTMLDocumentActiveElement obj = liftIO $ getObjectPropertyObject obj "active-element" DOMElement data DOMHTMLDocumentActiveElementPropertyInfo instance AttrInfo DOMHTMLDocumentActiveElementPropertyInfo where type AttrAllowedOps DOMHTMLDocumentActiveElementPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLDocumentActiveElementPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLDocumentActiveElementPropertyInfo = DOMHTMLDocumentK type AttrGetType DOMHTMLDocumentActiveElementPropertyInfo = DOMElement type AttrLabel DOMHTMLDocumentActiveElementPropertyInfo = "DOMHTMLDocument::active-element" attrGet _ = getDOMHTMLDocumentActiveElement attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "alink-color" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLDocumentAlinkColor :: (MonadIO m, DOMHTMLDocumentK o) => o -> m T.Text getDOMHTMLDocumentAlinkColor obj = liftIO $ getObjectPropertyString obj "alink-color" setDOMHTMLDocumentAlinkColor :: (MonadIO m, DOMHTMLDocumentK o) => o -> T.Text -> m () setDOMHTMLDocumentAlinkColor obj val = liftIO $ setObjectPropertyString obj "alink-color" val constructDOMHTMLDocumentAlinkColor :: T.Text -> IO ([Char], GValue) constructDOMHTMLDocumentAlinkColor val = constructObjectPropertyString "alink-color" val data DOMHTMLDocumentAlinkColorPropertyInfo instance AttrInfo DOMHTMLDocumentAlinkColorPropertyInfo where type AttrAllowedOps DOMHTMLDocumentAlinkColorPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLDocumentAlinkColorPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLDocumentAlinkColorPropertyInfo = DOMHTMLDocumentK type AttrGetType DOMHTMLDocumentAlinkColorPropertyInfo = T.Text type AttrLabel DOMHTMLDocumentAlinkColorPropertyInfo = "DOMHTMLDocument::alink-color" attrGet _ = getDOMHTMLDocumentAlinkColor attrSet _ = setDOMHTMLDocumentAlinkColor attrConstruct _ = constructDOMHTMLDocumentAlinkColor -- VVV Prop "bg-color" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLDocumentBgColor :: (MonadIO m, DOMHTMLDocumentK o) => o -> m T.Text getDOMHTMLDocumentBgColor obj = liftIO $ getObjectPropertyString obj "bg-color" setDOMHTMLDocumentBgColor :: (MonadIO m, DOMHTMLDocumentK o) => o -> T.Text -> m () setDOMHTMLDocumentBgColor obj val = liftIO $ setObjectPropertyString obj "bg-color" val constructDOMHTMLDocumentBgColor :: T.Text -> IO ([Char], GValue) constructDOMHTMLDocumentBgColor val = constructObjectPropertyString "bg-color" val data DOMHTMLDocumentBgColorPropertyInfo instance AttrInfo DOMHTMLDocumentBgColorPropertyInfo where type AttrAllowedOps DOMHTMLDocumentBgColorPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLDocumentBgColorPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLDocumentBgColorPropertyInfo = DOMHTMLDocumentK type AttrGetType DOMHTMLDocumentBgColorPropertyInfo = T.Text type AttrLabel DOMHTMLDocumentBgColorPropertyInfo = "DOMHTMLDocument::bg-color" attrGet _ = getDOMHTMLDocumentBgColor attrSet _ = setDOMHTMLDocumentBgColor attrConstruct _ = constructDOMHTMLDocumentBgColor -- VVV Prop "compat-mode" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMHTMLDocumentCompatMode :: (MonadIO m, DOMHTMLDocumentK o) => o -> m T.Text getDOMHTMLDocumentCompatMode obj = liftIO $ getObjectPropertyString obj "compat-mode" data DOMHTMLDocumentCompatModePropertyInfo instance AttrInfo DOMHTMLDocumentCompatModePropertyInfo where type AttrAllowedOps DOMHTMLDocumentCompatModePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLDocumentCompatModePropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLDocumentCompatModePropertyInfo = DOMHTMLDocumentK type AttrGetType DOMHTMLDocumentCompatModePropertyInfo = T.Text type AttrLabel DOMHTMLDocumentCompatModePropertyInfo = "DOMHTMLDocument::compat-mode" attrGet _ = getDOMHTMLDocumentCompatMode attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "design-mode" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLDocumentDesignMode :: (MonadIO m, DOMHTMLDocumentK o) => o -> m T.Text getDOMHTMLDocumentDesignMode obj = liftIO $ getObjectPropertyString obj "design-mode" setDOMHTMLDocumentDesignMode :: (MonadIO m, DOMHTMLDocumentK o) => o -> T.Text -> m () setDOMHTMLDocumentDesignMode obj val = liftIO $ setObjectPropertyString obj "design-mode" val constructDOMHTMLDocumentDesignMode :: T.Text -> IO ([Char], GValue) constructDOMHTMLDocumentDesignMode val = constructObjectPropertyString "design-mode" val data DOMHTMLDocumentDesignModePropertyInfo instance AttrInfo DOMHTMLDocumentDesignModePropertyInfo where type AttrAllowedOps DOMHTMLDocumentDesignModePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLDocumentDesignModePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLDocumentDesignModePropertyInfo = DOMHTMLDocumentK type AttrGetType DOMHTMLDocumentDesignModePropertyInfo = T.Text type AttrLabel DOMHTMLDocumentDesignModePropertyInfo = "DOMHTMLDocument::design-mode" attrGet _ = getDOMHTMLDocumentDesignMode attrSet _ = setDOMHTMLDocumentDesignMode attrConstruct _ = constructDOMHTMLDocumentDesignMode -- VVV Prop "dir" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLDocumentDir :: (MonadIO m, DOMHTMLDocumentK o) => o -> m T.Text getDOMHTMLDocumentDir obj = liftIO $ getObjectPropertyString obj "dir" setDOMHTMLDocumentDir :: (MonadIO m, DOMHTMLDocumentK o) => o -> T.Text -> m () setDOMHTMLDocumentDir obj val = liftIO $ setObjectPropertyString obj "dir" val constructDOMHTMLDocumentDir :: T.Text -> IO ([Char], GValue) constructDOMHTMLDocumentDir val = constructObjectPropertyString "dir" val data DOMHTMLDocumentDirPropertyInfo instance AttrInfo DOMHTMLDocumentDirPropertyInfo where type AttrAllowedOps DOMHTMLDocumentDirPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLDocumentDirPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLDocumentDirPropertyInfo = DOMHTMLDocumentK type AttrGetType DOMHTMLDocumentDirPropertyInfo = T.Text type AttrLabel DOMHTMLDocumentDirPropertyInfo = "DOMHTMLDocument::dir" attrGet _ = getDOMHTMLDocumentDir attrSet _ = setDOMHTMLDocumentDir attrConstruct _ = constructDOMHTMLDocumentDir -- VVV Prop "embeds" -- Type: TInterface "WebKit" "DOMHTMLCollection" -- Flags: [PropertyReadable] getDOMHTMLDocumentEmbeds :: (MonadIO m, DOMHTMLDocumentK o) => o -> m DOMHTMLCollection getDOMHTMLDocumentEmbeds obj = liftIO $ getObjectPropertyObject obj "embeds" DOMHTMLCollection data DOMHTMLDocumentEmbedsPropertyInfo instance AttrInfo DOMHTMLDocumentEmbedsPropertyInfo where type AttrAllowedOps DOMHTMLDocumentEmbedsPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLDocumentEmbedsPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLDocumentEmbedsPropertyInfo = DOMHTMLDocumentK type AttrGetType DOMHTMLDocumentEmbedsPropertyInfo = DOMHTMLCollection type AttrLabel DOMHTMLDocumentEmbedsPropertyInfo = "DOMHTMLDocument::embeds" attrGet _ = getDOMHTMLDocumentEmbeds attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "fg-color" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLDocumentFgColor :: (MonadIO m, DOMHTMLDocumentK o) => o -> m T.Text getDOMHTMLDocumentFgColor obj = liftIO $ getObjectPropertyString obj "fg-color" setDOMHTMLDocumentFgColor :: (MonadIO m, DOMHTMLDocumentK o) => o -> T.Text -> m () setDOMHTMLDocumentFgColor obj val = liftIO $ setObjectPropertyString obj "fg-color" val constructDOMHTMLDocumentFgColor :: T.Text -> IO ([Char], GValue) constructDOMHTMLDocumentFgColor val = constructObjectPropertyString "fg-color" val data DOMHTMLDocumentFgColorPropertyInfo instance AttrInfo DOMHTMLDocumentFgColorPropertyInfo where type AttrAllowedOps DOMHTMLDocumentFgColorPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLDocumentFgColorPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLDocumentFgColorPropertyInfo = DOMHTMLDocumentK type AttrGetType DOMHTMLDocumentFgColorPropertyInfo = T.Text type AttrLabel DOMHTMLDocumentFgColorPropertyInfo = "DOMHTMLDocument::fg-color" attrGet _ = getDOMHTMLDocumentFgColor attrSet _ = setDOMHTMLDocumentFgColor attrConstruct _ = constructDOMHTMLDocumentFgColor -- VVV Prop "height" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMHTMLDocumentHeight :: (MonadIO m, DOMHTMLDocumentK o) => o -> m Int64 getDOMHTMLDocumentHeight obj = liftIO $ getObjectPropertyInt64 obj "height" data DOMHTMLDocumentHeightPropertyInfo instance AttrInfo DOMHTMLDocumentHeightPropertyInfo where type AttrAllowedOps DOMHTMLDocumentHeightPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLDocumentHeightPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLDocumentHeightPropertyInfo = DOMHTMLDocumentK type AttrGetType DOMHTMLDocumentHeightPropertyInfo = Int64 type AttrLabel DOMHTMLDocumentHeightPropertyInfo = "DOMHTMLDocument::height" attrGet _ = getDOMHTMLDocumentHeight attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "link-color" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLDocumentLinkColor :: (MonadIO m, DOMHTMLDocumentK o) => o -> m T.Text getDOMHTMLDocumentLinkColor obj = liftIO $ getObjectPropertyString obj "link-color" setDOMHTMLDocumentLinkColor :: (MonadIO m, DOMHTMLDocumentK o) => o -> T.Text -> m () setDOMHTMLDocumentLinkColor obj val = liftIO $ setObjectPropertyString obj "link-color" val constructDOMHTMLDocumentLinkColor :: T.Text -> IO ([Char], GValue) constructDOMHTMLDocumentLinkColor val = constructObjectPropertyString "link-color" val data DOMHTMLDocumentLinkColorPropertyInfo instance AttrInfo DOMHTMLDocumentLinkColorPropertyInfo where type AttrAllowedOps DOMHTMLDocumentLinkColorPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLDocumentLinkColorPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLDocumentLinkColorPropertyInfo = DOMHTMLDocumentK type AttrGetType DOMHTMLDocumentLinkColorPropertyInfo = T.Text type AttrLabel DOMHTMLDocumentLinkColorPropertyInfo = "DOMHTMLDocument::link-color" attrGet _ = getDOMHTMLDocumentLinkColor attrSet _ = setDOMHTMLDocumentLinkColor attrConstruct _ = constructDOMHTMLDocumentLinkColor -- VVV Prop "plugins" -- Type: TInterface "WebKit" "DOMHTMLCollection" -- Flags: [PropertyReadable] getDOMHTMLDocumentPlugins :: (MonadIO m, DOMHTMLDocumentK o) => o -> m DOMHTMLCollection getDOMHTMLDocumentPlugins obj = liftIO $ getObjectPropertyObject obj "plugins" DOMHTMLCollection data DOMHTMLDocumentPluginsPropertyInfo instance AttrInfo DOMHTMLDocumentPluginsPropertyInfo where type AttrAllowedOps DOMHTMLDocumentPluginsPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLDocumentPluginsPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLDocumentPluginsPropertyInfo = DOMHTMLDocumentK type AttrGetType DOMHTMLDocumentPluginsPropertyInfo = DOMHTMLCollection type AttrLabel DOMHTMLDocumentPluginsPropertyInfo = "DOMHTMLDocument::plugins" attrGet _ = getDOMHTMLDocumentPlugins attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "scripts" -- Type: TInterface "WebKit" "DOMHTMLCollection" -- Flags: [PropertyReadable] getDOMHTMLDocumentScripts :: (MonadIO m, DOMHTMLDocumentK o) => o -> m DOMHTMLCollection getDOMHTMLDocumentScripts obj = liftIO $ getObjectPropertyObject obj "scripts" DOMHTMLCollection data DOMHTMLDocumentScriptsPropertyInfo instance AttrInfo DOMHTMLDocumentScriptsPropertyInfo where type AttrAllowedOps DOMHTMLDocumentScriptsPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLDocumentScriptsPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLDocumentScriptsPropertyInfo = DOMHTMLDocumentK type AttrGetType DOMHTMLDocumentScriptsPropertyInfo = DOMHTMLCollection type AttrLabel DOMHTMLDocumentScriptsPropertyInfo = "DOMHTMLDocument::scripts" attrGet _ = getDOMHTMLDocumentScripts attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "vlink-color" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLDocumentVlinkColor :: (MonadIO m, DOMHTMLDocumentK o) => o -> m T.Text getDOMHTMLDocumentVlinkColor obj = liftIO $ getObjectPropertyString obj "vlink-color" setDOMHTMLDocumentVlinkColor :: (MonadIO m, DOMHTMLDocumentK o) => o -> T.Text -> m () setDOMHTMLDocumentVlinkColor obj val = liftIO $ setObjectPropertyString obj "vlink-color" val constructDOMHTMLDocumentVlinkColor :: T.Text -> IO ([Char], GValue) constructDOMHTMLDocumentVlinkColor val = constructObjectPropertyString "vlink-color" val data DOMHTMLDocumentVlinkColorPropertyInfo instance AttrInfo DOMHTMLDocumentVlinkColorPropertyInfo where type AttrAllowedOps DOMHTMLDocumentVlinkColorPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLDocumentVlinkColorPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLDocumentVlinkColorPropertyInfo = DOMHTMLDocumentK type AttrGetType DOMHTMLDocumentVlinkColorPropertyInfo = T.Text type AttrLabel DOMHTMLDocumentVlinkColorPropertyInfo = "DOMHTMLDocument::vlink-color" attrGet _ = getDOMHTMLDocumentVlinkColor attrSet _ = setDOMHTMLDocumentVlinkColor attrConstruct _ = constructDOMHTMLDocumentVlinkColor -- VVV Prop "width" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMHTMLDocumentWidth :: (MonadIO m, DOMHTMLDocumentK o) => o -> m Int64 getDOMHTMLDocumentWidth obj = liftIO $ getObjectPropertyInt64 obj "width" data DOMHTMLDocumentWidthPropertyInfo instance AttrInfo DOMHTMLDocumentWidthPropertyInfo where type AttrAllowedOps DOMHTMLDocumentWidthPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLDocumentWidthPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLDocumentWidthPropertyInfo = DOMHTMLDocumentK type AttrGetType DOMHTMLDocumentWidthPropertyInfo = Int64 type AttrLabel DOMHTMLDocumentWidthPropertyInfo = "DOMHTMLDocument::width" attrGet _ = getDOMHTMLDocumentWidth attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMHTMLDocument = '[ '("active-element", DOMHTMLDocumentActiveElementPropertyInfo), '("alink-color", DOMHTMLDocumentAlinkColorPropertyInfo), '("anchors", DOMDocumentAnchorsPropertyInfo), '("applets", DOMDocumentAppletsPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("bg-color", DOMHTMLDocumentBgColorPropertyInfo), '("body", DOMDocumentBodyPropertyInfo), '("character-set", DOMDocumentCharacterSetPropertyInfo), '("charset", DOMDocumentCharsetPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("compat-mode", DOMHTMLDocumentCompatModePropertyInfo), '("cookie", DOMDocumentCookiePropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("current-script", DOMDocumentCurrentScriptPropertyInfo), '("default-charset", DOMDocumentDefaultCharsetPropertyInfo), '("default-view", DOMDocumentDefaultViewPropertyInfo), '("design-mode", DOMHTMLDocumentDesignModePropertyInfo), '("dir", DOMHTMLDocumentDirPropertyInfo), '("doctype", DOMDocumentDoctypePropertyInfo), '("document-element", DOMDocumentDocumentElementPropertyInfo), '("document-uri", DOMDocumentDocumentUriPropertyInfo), '("domain", DOMDocumentDomainPropertyInfo), '("embeds", DOMHTMLDocumentEmbedsPropertyInfo), '("fg-color", DOMHTMLDocumentFgColorPropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("forms", DOMDocumentFormsPropertyInfo), '("head", DOMDocumentHeadPropertyInfo), '("height", DOMHTMLDocumentHeightPropertyInfo), '("hidden", DOMDocumentHiddenPropertyInfo), '("images", DOMDocumentImagesPropertyInfo), '("implementation", DOMDocumentImplementationPropertyInfo), '("input-encoding", DOMDocumentInputEncodingPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-modified", DOMDocumentLastModifiedPropertyInfo), '("link-color", DOMHTMLDocumentLinkColorPropertyInfo), '("links", DOMDocumentLinksPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("plugins", DOMHTMLDocumentPluginsPropertyInfo), '("preferred-stylesheet-set", DOMDocumentPreferredStylesheetSetPropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("ready-state", DOMDocumentReadyStatePropertyInfo), '("referrer", DOMDocumentReferrerPropertyInfo), '("scripts", DOMHTMLDocumentScriptsPropertyInfo), '("security-policy", DOMDocumentSecurityPolicyPropertyInfo), '("selected-stylesheet-set", DOMDocumentSelectedStylesheetSetPropertyInfo), '("style-sheets", DOMDocumentStyleSheetsPropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("title", DOMDocumentTitlePropertyInfo), '("url", DOMDocumentUrlPropertyInfo), '("visibility-state", DOMDocumentVisibilityStatePropertyInfo), '("vlink-color", DOMHTMLDocumentVlinkColorPropertyInfo), '("webkit-current-full-screen-element", DOMDocumentWebkitCurrentFullScreenElementPropertyInfo), '("webkit-full-screen-keyboard-input-allowed", DOMDocumentWebkitFullScreenKeyboardInputAllowedPropertyInfo), '("webkit-fullscreen-element", DOMDocumentWebkitFullscreenElementPropertyInfo), '("webkit-fullscreen-enabled", DOMDocumentWebkitFullscreenEnabledPropertyInfo), '("webkit-is-full-screen", DOMDocumentWebkitIsFullScreenPropertyInfo), '("webkit-pointer-lock-element", DOMDocumentWebkitPointerLockElementPropertyInfo), '("width", DOMHTMLDocumentWidthPropertyInfo), '("xml-encoding", DOMDocumentXmlEncodingPropertyInfo), '("xml-standalone", DOMDocumentXmlStandalonePropertyInfo), '("xml-version", DOMDocumentXmlVersionPropertyInfo)] -- VVV Prop "access-key" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLElementAccessKey :: (MonadIO m, DOMHTMLElementK o) => o -> m T.Text getDOMHTMLElementAccessKey obj = liftIO $ getObjectPropertyString obj "access-key" setDOMHTMLElementAccessKey :: (MonadIO m, DOMHTMLElementK o) => o -> T.Text -> m () setDOMHTMLElementAccessKey obj val = liftIO $ setObjectPropertyString obj "access-key" val constructDOMHTMLElementAccessKey :: T.Text -> IO ([Char], GValue) constructDOMHTMLElementAccessKey val = constructObjectPropertyString "access-key" val data DOMHTMLElementAccessKeyPropertyInfo instance AttrInfo DOMHTMLElementAccessKeyPropertyInfo where type AttrAllowedOps DOMHTMLElementAccessKeyPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLElementAccessKeyPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLElementAccessKeyPropertyInfo = DOMHTMLElementK type AttrGetType DOMHTMLElementAccessKeyPropertyInfo = T.Text type AttrLabel DOMHTMLElementAccessKeyPropertyInfo = "DOMHTMLElement::access-key" attrGet _ = getDOMHTMLElementAccessKey attrSet _ = setDOMHTMLElementAccessKey attrConstruct _ = constructDOMHTMLElementAccessKey -- VVV Prop "children" -- Type: TInterface "WebKit" "DOMHTMLCollection" -- Flags: [PropertyReadable] getDOMHTMLElementChildren :: (MonadIO m, DOMHTMLElementK o) => o -> m DOMHTMLCollection getDOMHTMLElementChildren obj = liftIO $ getObjectPropertyObject obj "children" DOMHTMLCollection data DOMHTMLElementChildrenPropertyInfo instance AttrInfo DOMHTMLElementChildrenPropertyInfo where type AttrAllowedOps DOMHTMLElementChildrenPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLElementChildrenPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLElementChildrenPropertyInfo = DOMHTMLElementK type AttrGetType DOMHTMLElementChildrenPropertyInfo = DOMHTMLCollection type AttrLabel DOMHTMLElementChildrenPropertyInfo = "DOMHTMLElement::children" attrGet _ = getDOMHTMLElementChildren attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "content-editable" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLElementContentEditable :: (MonadIO m, DOMHTMLElementK o) => o -> m T.Text getDOMHTMLElementContentEditable obj = liftIO $ getObjectPropertyString obj "content-editable" setDOMHTMLElementContentEditable :: (MonadIO m, DOMHTMLElementK o) => o -> T.Text -> m () setDOMHTMLElementContentEditable obj val = liftIO $ setObjectPropertyString obj "content-editable" val constructDOMHTMLElementContentEditable :: T.Text -> IO ([Char], GValue) constructDOMHTMLElementContentEditable val = constructObjectPropertyString "content-editable" val data DOMHTMLElementContentEditablePropertyInfo instance AttrInfo DOMHTMLElementContentEditablePropertyInfo where type AttrAllowedOps DOMHTMLElementContentEditablePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLElementContentEditablePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLElementContentEditablePropertyInfo = DOMHTMLElementK type AttrGetType DOMHTMLElementContentEditablePropertyInfo = T.Text type AttrLabel DOMHTMLElementContentEditablePropertyInfo = "DOMHTMLElement::content-editable" attrGet _ = getDOMHTMLElementContentEditable attrSet _ = setDOMHTMLElementContentEditable attrConstruct _ = constructDOMHTMLElementContentEditable -- VVV Prop "dir" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLElementDir :: (MonadIO m, DOMHTMLElementK o) => o -> m T.Text getDOMHTMLElementDir obj = liftIO $ getObjectPropertyString obj "dir" setDOMHTMLElementDir :: (MonadIO m, DOMHTMLElementK o) => o -> T.Text -> m () setDOMHTMLElementDir obj val = liftIO $ setObjectPropertyString obj "dir" val constructDOMHTMLElementDir :: T.Text -> IO ([Char], GValue) constructDOMHTMLElementDir val = constructObjectPropertyString "dir" val data DOMHTMLElementDirPropertyInfo instance AttrInfo DOMHTMLElementDirPropertyInfo where type AttrAllowedOps DOMHTMLElementDirPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLElementDirPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLElementDirPropertyInfo = DOMHTMLElementK type AttrGetType DOMHTMLElementDirPropertyInfo = T.Text type AttrLabel DOMHTMLElementDirPropertyInfo = "DOMHTMLElement::dir" attrGet _ = getDOMHTMLElementDir attrSet _ = setDOMHTMLElementDir attrConstruct _ = constructDOMHTMLElementDir -- VVV Prop "draggable" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLElementDraggable :: (MonadIO m, DOMHTMLElementK o) => o -> m Bool getDOMHTMLElementDraggable obj = liftIO $ getObjectPropertyBool obj "draggable" setDOMHTMLElementDraggable :: (MonadIO m, DOMHTMLElementK o) => o -> Bool -> m () setDOMHTMLElementDraggable obj val = liftIO $ setObjectPropertyBool obj "draggable" val constructDOMHTMLElementDraggable :: Bool -> IO ([Char], GValue) constructDOMHTMLElementDraggable val = constructObjectPropertyBool "draggable" val data DOMHTMLElementDraggablePropertyInfo instance AttrInfo DOMHTMLElementDraggablePropertyInfo where type AttrAllowedOps DOMHTMLElementDraggablePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLElementDraggablePropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLElementDraggablePropertyInfo = DOMHTMLElementK type AttrGetType DOMHTMLElementDraggablePropertyInfo = Bool type AttrLabel DOMHTMLElementDraggablePropertyInfo = "DOMHTMLElement::draggable" attrGet _ = getDOMHTMLElementDraggable attrSet _ = setDOMHTMLElementDraggable attrConstruct _ = constructDOMHTMLElementDraggable -- VVV Prop "hidden" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLElementHidden :: (MonadIO m, DOMHTMLElementK o) => o -> m Bool getDOMHTMLElementHidden obj = liftIO $ getObjectPropertyBool obj "hidden" setDOMHTMLElementHidden :: (MonadIO m, DOMHTMLElementK o) => o -> Bool -> m () setDOMHTMLElementHidden obj val = liftIO $ setObjectPropertyBool obj "hidden" val constructDOMHTMLElementHidden :: Bool -> IO ([Char], GValue) constructDOMHTMLElementHidden val = constructObjectPropertyBool "hidden" val data DOMHTMLElementHiddenPropertyInfo instance AttrInfo DOMHTMLElementHiddenPropertyInfo where type AttrAllowedOps DOMHTMLElementHiddenPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLElementHiddenPropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLElementHiddenPropertyInfo = DOMHTMLElementK type AttrGetType DOMHTMLElementHiddenPropertyInfo = Bool type AttrLabel DOMHTMLElementHiddenPropertyInfo = "DOMHTMLElement::hidden" attrGet _ = getDOMHTMLElementHidden attrSet _ = setDOMHTMLElementHidden attrConstruct _ = constructDOMHTMLElementHidden -- VVV Prop "inner-html" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLElementInnerHtml :: (MonadIO m, DOMHTMLElementK o) => o -> m T.Text getDOMHTMLElementInnerHtml obj = liftIO $ getObjectPropertyString obj "inner-html" setDOMHTMLElementInnerHtml :: (MonadIO m, DOMHTMLElementK o) => o -> T.Text -> m () setDOMHTMLElementInnerHtml obj val = liftIO $ setObjectPropertyString obj "inner-html" val constructDOMHTMLElementInnerHtml :: T.Text -> IO ([Char], GValue) constructDOMHTMLElementInnerHtml val = constructObjectPropertyString "inner-html" val data DOMHTMLElementInnerHtmlPropertyInfo instance AttrInfo DOMHTMLElementInnerHtmlPropertyInfo where type AttrAllowedOps DOMHTMLElementInnerHtmlPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLElementInnerHtmlPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLElementInnerHtmlPropertyInfo = DOMHTMLElementK type AttrGetType DOMHTMLElementInnerHtmlPropertyInfo = T.Text type AttrLabel DOMHTMLElementInnerHtmlPropertyInfo = "DOMHTMLElement::inner-html" attrGet _ = getDOMHTMLElementInnerHtml attrSet _ = setDOMHTMLElementInnerHtml attrConstruct _ = constructDOMHTMLElementInnerHtml -- VVV Prop "inner-text" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLElementInnerText :: (MonadIO m, DOMHTMLElementK o) => o -> m T.Text getDOMHTMLElementInnerText obj = liftIO $ getObjectPropertyString obj "inner-text" setDOMHTMLElementInnerText :: (MonadIO m, DOMHTMLElementK o) => o -> T.Text -> m () setDOMHTMLElementInnerText obj val = liftIO $ setObjectPropertyString obj "inner-text" val constructDOMHTMLElementInnerText :: T.Text -> IO ([Char], GValue) constructDOMHTMLElementInnerText val = constructObjectPropertyString "inner-text" val data DOMHTMLElementInnerTextPropertyInfo instance AttrInfo DOMHTMLElementInnerTextPropertyInfo where type AttrAllowedOps DOMHTMLElementInnerTextPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLElementInnerTextPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLElementInnerTextPropertyInfo = DOMHTMLElementK type AttrGetType DOMHTMLElementInnerTextPropertyInfo = T.Text type AttrLabel DOMHTMLElementInnerTextPropertyInfo = "DOMHTMLElement::inner-text" attrGet _ = getDOMHTMLElementInnerText attrSet _ = setDOMHTMLElementInnerText attrConstruct _ = constructDOMHTMLElementInnerText -- VVV Prop "is-content-editable" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMHTMLElementIsContentEditable :: (MonadIO m, DOMHTMLElementK o) => o -> m Bool getDOMHTMLElementIsContentEditable obj = liftIO $ getObjectPropertyBool obj "is-content-editable" data DOMHTMLElementIsContentEditablePropertyInfo instance AttrInfo DOMHTMLElementIsContentEditablePropertyInfo where type AttrAllowedOps DOMHTMLElementIsContentEditablePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLElementIsContentEditablePropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLElementIsContentEditablePropertyInfo = DOMHTMLElementK type AttrGetType DOMHTMLElementIsContentEditablePropertyInfo = Bool type AttrLabel DOMHTMLElementIsContentEditablePropertyInfo = "DOMHTMLElement::is-content-editable" attrGet _ = getDOMHTMLElementIsContentEditable attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "lang" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLElementLang :: (MonadIO m, DOMHTMLElementK o) => o -> m T.Text getDOMHTMLElementLang obj = liftIO $ getObjectPropertyString obj "lang" setDOMHTMLElementLang :: (MonadIO m, DOMHTMLElementK o) => o -> T.Text -> m () setDOMHTMLElementLang obj val = liftIO $ setObjectPropertyString obj "lang" val constructDOMHTMLElementLang :: T.Text -> IO ([Char], GValue) constructDOMHTMLElementLang val = constructObjectPropertyString "lang" val data DOMHTMLElementLangPropertyInfo instance AttrInfo DOMHTMLElementLangPropertyInfo where type AttrAllowedOps DOMHTMLElementLangPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLElementLangPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLElementLangPropertyInfo = DOMHTMLElementK type AttrGetType DOMHTMLElementLangPropertyInfo = T.Text type AttrLabel DOMHTMLElementLangPropertyInfo = "DOMHTMLElement::lang" attrGet _ = getDOMHTMLElementLang attrSet _ = setDOMHTMLElementLang attrConstruct _ = constructDOMHTMLElementLang -- VVV Prop "outer-html" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLElementOuterHtml :: (MonadIO m, DOMHTMLElementK o) => o -> m T.Text getDOMHTMLElementOuterHtml obj = liftIO $ getObjectPropertyString obj "outer-html" setDOMHTMLElementOuterHtml :: (MonadIO m, DOMHTMLElementK o) => o -> T.Text -> m () setDOMHTMLElementOuterHtml obj val = liftIO $ setObjectPropertyString obj "outer-html" val constructDOMHTMLElementOuterHtml :: T.Text -> IO ([Char], GValue) constructDOMHTMLElementOuterHtml val = constructObjectPropertyString "outer-html" val data DOMHTMLElementOuterHtmlPropertyInfo instance AttrInfo DOMHTMLElementOuterHtmlPropertyInfo where type AttrAllowedOps DOMHTMLElementOuterHtmlPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLElementOuterHtmlPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLElementOuterHtmlPropertyInfo = DOMHTMLElementK type AttrGetType DOMHTMLElementOuterHtmlPropertyInfo = T.Text type AttrLabel DOMHTMLElementOuterHtmlPropertyInfo = "DOMHTMLElement::outer-html" attrGet _ = getDOMHTMLElementOuterHtml attrSet _ = setDOMHTMLElementOuterHtml attrConstruct _ = constructDOMHTMLElementOuterHtml -- VVV Prop "outer-text" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLElementOuterText :: (MonadIO m, DOMHTMLElementK o) => o -> m T.Text getDOMHTMLElementOuterText obj = liftIO $ getObjectPropertyString obj "outer-text" setDOMHTMLElementOuterText :: (MonadIO m, DOMHTMLElementK o) => o -> T.Text -> m () setDOMHTMLElementOuterText obj val = liftIO $ setObjectPropertyString obj "outer-text" val constructDOMHTMLElementOuterText :: T.Text -> IO ([Char], GValue) constructDOMHTMLElementOuterText val = constructObjectPropertyString "outer-text" val data DOMHTMLElementOuterTextPropertyInfo instance AttrInfo DOMHTMLElementOuterTextPropertyInfo where type AttrAllowedOps DOMHTMLElementOuterTextPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLElementOuterTextPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLElementOuterTextPropertyInfo = DOMHTMLElementK type AttrGetType DOMHTMLElementOuterTextPropertyInfo = T.Text type AttrLabel DOMHTMLElementOuterTextPropertyInfo = "DOMHTMLElement::outer-text" attrGet _ = getDOMHTMLElementOuterText attrSet _ = setDOMHTMLElementOuterText attrConstruct _ = constructDOMHTMLElementOuterText -- VVV Prop "spellcheck" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLElementSpellcheck :: (MonadIO m, DOMHTMLElementK o) => o -> m Bool getDOMHTMLElementSpellcheck obj = liftIO $ getObjectPropertyBool obj "spellcheck" setDOMHTMLElementSpellcheck :: (MonadIO m, DOMHTMLElementK o) => o -> Bool -> m () setDOMHTMLElementSpellcheck obj val = liftIO $ setObjectPropertyBool obj "spellcheck" val constructDOMHTMLElementSpellcheck :: Bool -> IO ([Char], GValue) constructDOMHTMLElementSpellcheck val = constructObjectPropertyBool "spellcheck" val data DOMHTMLElementSpellcheckPropertyInfo instance AttrInfo DOMHTMLElementSpellcheckPropertyInfo where type AttrAllowedOps DOMHTMLElementSpellcheckPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLElementSpellcheckPropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLElementSpellcheckPropertyInfo = DOMHTMLElementK type AttrGetType DOMHTMLElementSpellcheckPropertyInfo = Bool type AttrLabel DOMHTMLElementSpellcheckPropertyInfo = "DOMHTMLElement::spellcheck" attrGet _ = getDOMHTMLElementSpellcheck attrSet _ = setDOMHTMLElementSpellcheck attrConstruct _ = constructDOMHTMLElementSpellcheck -- VVV Prop "tab-index" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLElementTabIndex :: (MonadIO m, DOMHTMLElementK o) => o -> m Int64 getDOMHTMLElementTabIndex obj = liftIO $ getObjectPropertyInt64 obj "tab-index" setDOMHTMLElementTabIndex :: (MonadIO m, DOMHTMLElementK o) => o -> Int64 -> m () setDOMHTMLElementTabIndex obj val = liftIO $ setObjectPropertyInt64 obj "tab-index" val constructDOMHTMLElementTabIndex :: Int64 -> IO ([Char], GValue) constructDOMHTMLElementTabIndex val = constructObjectPropertyInt64 "tab-index" val data DOMHTMLElementTabIndexPropertyInfo instance AttrInfo DOMHTMLElementTabIndexPropertyInfo where type AttrAllowedOps DOMHTMLElementTabIndexPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLElementTabIndexPropertyInfo = (~) Int64 type AttrBaseTypeConstraint DOMHTMLElementTabIndexPropertyInfo = DOMHTMLElementK type AttrGetType DOMHTMLElementTabIndexPropertyInfo = Int64 type AttrLabel DOMHTMLElementTabIndexPropertyInfo = "DOMHTMLElement::tab-index" attrGet _ = getDOMHTMLElementTabIndex attrSet _ = setDOMHTMLElementTabIndex attrConstruct _ = constructDOMHTMLElementTabIndex -- VVV Prop "title" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLElementTitle :: (MonadIO m, DOMHTMLElementK o) => o -> m T.Text getDOMHTMLElementTitle obj = liftIO $ getObjectPropertyString obj "title" setDOMHTMLElementTitle :: (MonadIO m, DOMHTMLElementK o) => o -> T.Text -> m () setDOMHTMLElementTitle obj val = liftIO $ setObjectPropertyString obj "title" val constructDOMHTMLElementTitle :: T.Text -> IO ([Char], GValue) constructDOMHTMLElementTitle val = constructObjectPropertyString "title" val data DOMHTMLElementTitlePropertyInfo instance AttrInfo DOMHTMLElementTitlePropertyInfo where type AttrAllowedOps DOMHTMLElementTitlePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLElementTitlePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLElementTitlePropertyInfo = DOMHTMLElementK type AttrGetType DOMHTMLElementTitlePropertyInfo = T.Text type AttrLabel DOMHTMLElementTitlePropertyInfo = "DOMHTMLElement::title" attrGet _ = getDOMHTMLElementTitle attrSet _ = setDOMHTMLElementTitle attrConstruct _ = constructDOMHTMLElementTitle -- VVV Prop "translate" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLElementTranslate :: (MonadIO m, DOMHTMLElementK o) => o -> m Bool getDOMHTMLElementTranslate obj = liftIO $ getObjectPropertyBool obj "translate" setDOMHTMLElementTranslate :: (MonadIO m, DOMHTMLElementK o) => o -> Bool -> m () setDOMHTMLElementTranslate obj val = liftIO $ setObjectPropertyBool obj "translate" val constructDOMHTMLElementTranslate :: Bool -> IO ([Char], GValue) constructDOMHTMLElementTranslate val = constructObjectPropertyBool "translate" val data DOMHTMLElementTranslatePropertyInfo instance AttrInfo DOMHTMLElementTranslatePropertyInfo where type AttrAllowedOps DOMHTMLElementTranslatePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLElementTranslatePropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLElementTranslatePropertyInfo = DOMHTMLElementK type AttrGetType DOMHTMLElementTranslatePropertyInfo = Bool type AttrLabel DOMHTMLElementTranslatePropertyInfo = "DOMHTMLElement::translate" attrGet _ = getDOMHTMLElementTranslate attrSet _ = setDOMHTMLElementTranslate attrConstruct _ = constructDOMHTMLElementTranslate -- VVV Prop "webkitdropzone" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLElementWebkitdropzone :: (MonadIO m, DOMHTMLElementK o) => o -> m T.Text getDOMHTMLElementWebkitdropzone obj = liftIO $ getObjectPropertyString obj "webkitdropzone" setDOMHTMLElementWebkitdropzone :: (MonadIO m, DOMHTMLElementK o) => o -> T.Text -> m () setDOMHTMLElementWebkitdropzone obj val = liftIO $ setObjectPropertyString obj "webkitdropzone" val constructDOMHTMLElementWebkitdropzone :: T.Text -> IO ([Char], GValue) constructDOMHTMLElementWebkitdropzone val = constructObjectPropertyString "webkitdropzone" val data DOMHTMLElementWebkitdropzonePropertyInfo instance AttrInfo DOMHTMLElementWebkitdropzonePropertyInfo where type AttrAllowedOps DOMHTMLElementWebkitdropzonePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLElementWebkitdropzonePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLElementWebkitdropzonePropertyInfo = DOMHTMLElementK type AttrGetType DOMHTMLElementWebkitdropzonePropertyInfo = T.Text type AttrLabel DOMHTMLElementWebkitdropzonePropertyInfo = "DOMHTMLElement::webkitdropzone" attrGet _ = getDOMHTMLElementWebkitdropzone attrSet _ = setDOMHTMLElementWebkitdropzone attrConstruct _ = constructDOMHTMLElementWebkitdropzone type instance AttributeList DOMHTMLElement = '[ '("access-key", DOMHTMLElementAccessKeyPropertyInfo), '("attributes", DOMElementAttributesPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("child-element-count", DOMElementChildElementCountPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("children", DOMHTMLElementChildrenPropertyInfo), '("class-list", DOMElementClassListPropertyInfo), '("class-name", DOMElementClassNamePropertyInfo), '("client-height", DOMElementClientHeightPropertyInfo), '("client-left", DOMElementClientLeftPropertyInfo), '("client-top", DOMElementClientTopPropertyInfo), '("client-width", DOMElementClientWidthPropertyInfo), '("content-editable", DOMHTMLElementContentEditablePropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("dir", DOMHTMLElementDirPropertyInfo), '("draggable", DOMHTMLElementDraggablePropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("first-element-child", DOMElementFirstElementChildPropertyInfo), '("hidden", DOMHTMLElementHiddenPropertyInfo), '("id", DOMElementIdPropertyInfo), '("inner-html", DOMHTMLElementInnerHtmlPropertyInfo), '("inner-text", DOMHTMLElementInnerTextPropertyInfo), '("is-content-editable", DOMHTMLElementIsContentEditablePropertyInfo), '("lang", DOMHTMLElementLangPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-element-child", DOMElementLastElementChildPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-element-sibling", DOMElementNextElementSiblingPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("offset-height", DOMElementOffsetHeightPropertyInfo), '("offset-left", DOMElementOffsetLeftPropertyInfo), '("offset-parent", DOMElementOffsetParentPropertyInfo), '("offset-top", DOMElementOffsetTopPropertyInfo), '("offset-width", DOMElementOffsetWidthPropertyInfo), '("outer-html", DOMHTMLElementOuterHtmlPropertyInfo), '("outer-text", DOMHTMLElementOuterTextPropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-element-sibling", DOMElementPreviousElementSiblingPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("scroll-height", DOMElementScrollHeightPropertyInfo), '("scroll-left", DOMElementScrollLeftPropertyInfo), '("scroll-top", DOMElementScrollTopPropertyInfo), '("scroll-width", DOMElementScrollWidthPropertyInfo), '("spellcheck", DOMHTMLElementSpellcheckPropertyInfo), '("style", DOMElementStylePropertyInfo), '("tab-index", DOMHTMLElementTabIndexPropertyInfo), '("tag-name", DOMElementTagNamePropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("title", DOMHTMLElementTitlePropertyInfo), '("translate", DOMHTMLElementTranslatePropertyInfo), '("webkit-region-overset", DOMElementWebkitRegionOversetPropertyInfo), '("webkitdropzone", DOMHTMLElementWebkitdropzonePropertyInfo)] -- VVV Prop "align" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLEmbedElementAlign :: (MonadIO m, DOMHTMLEmbedElementK o) => o -> m T.Text getDOMHTMLEmbedElementAlign obj = liftIO $ getObjectPropertyString obj "align" setDOMHTMLEmbedElementAlign :: (MonadIO m, DOMHTMLEmbedElementK o) => o -> T.Text -> m () setDOMHTMLEmbedElementAlign obj val = liftIO $ setObjectPropertyString obj "align" val constructDOMHTMLEmbedElementAlign :: T.Text -> IO ([Char], GValue) constructDOMHTMLEmbedElementAlign val = constructObjectPropertyString "align" val data DOMHTMLEmbedElementAlignPropertyInfo instance AttrInfo DOMHTMLEmbedElementAlignPropertyInfo where type AttrAllowedOps DOMHTMLEmbedElementAlignPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLEmbedElementAlignPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLEmbedElementAlignPropertyInfo = DOMHTMLEmbedElementK type AttrGetType DOMHTMLEmbedElementAlignPropertyInfo = T.Text type AttrLabel DOMHTMLEmbedElementAlignPropertyInfo = "DOMHTMLEmbedElement::align" attrGet _ = getDOMHTMLEmbedElementAlign attrSet _ = setDOMHTMLEmbedElementAlign attrConstruct _ = constructDOMHTMLEmbedElementAlign -- VVV Prop "height" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLEmbedElementHeight :: (MonadIO m, DOMHTMLEmbedElementK o) => o -> m Int64 getDOMHTMLEmbedElementHeight obj = liftIO $ getObjectPropertyInt64 obj "height" setDOMHTMLEmbedElementHeight :: (MonadIO m, DOMHTMLEmbedElementK o) => o -> Int64 -> m () setDOMHTMLEmbedElementHeight obj val = liftIO $ setObjectPropertyInt64 obj "height" val constructDOMHTMLEmbedElementHeight :: Int64 -> IO ([Char], GValue) constructDOMHTMLEmbedElementHeight val = constructObjectPropertyInt64 "height" val data DOMHTMLEmbedElementHeightPropertyInfo instance AttrInfo DOMHTMLEmbedElementHeightPropertyInfo where type AttrAllowedOps DOMHTMLEmbedElementHeightPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLEmbedElementHeightPropertyInfo = (~) Int64 type AttrBaseTypeConstraint DOMHTMLEmbedElementHeightPropertyInfo = DOMHTMLEmbedElementK type AttrGetType DOMHTMLEmbedElementHeightPropertyInfo = Int64 type AttrLabel DOMHTMLEmbedElementHeightPropertyInfo = "DOMHTMLEmbedElement::height" attrGet _ = getDOMHTMLEmbedElementHeight attrSet _ = setDOMHTMLEmbedElementHeight attrConstruct _ = constructDOMHTMLEmbedElementHeight -- VVV Prop "name" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLEmbedElementName :: (MonadIO m, DOMHTMLEmbedElementK o) => o -> m T.Text getDOMHTMLEmbedElementName obj = liftIO $ getObjectPropertyString obj "name" setDOMHTMLEmbedElementName :: (MonadIO m, DOMHTMLEmbedElementK o) => o -> T.Text -> m () setDOMHTMLEmbedElementName obj val = liftIO $ setObjectPropertyString obj "name" val constructDOMHTMLEmbedElementName :: T.Text -> IO ([Char], GValue) constructDOMHTMLEmbedElementName val = constructObjectPropertyString "name" val data DOMHTMLEmbedElementNamePropertyInfo instance AttrInfo DOMHTMLEmbedElementNamePropertyInfo where type AttrAllowedOps DOMHTMLEmbedElementNamePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLEmbedElementNamePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLEmbedElementNamePropertyInfo = DOMHTMLEmbedElementK type AttrGetType DOMHTMLEmbedElementNamePropertyInfo = T.Text type AttrLabel DOMHTMLEmbedElementNamePropertyInfo = "DOMHTMLEmbedElement::name" attrGet _ = getDOMHTMLEmbedElementName attrSet _ = setDOMHTMLEmbedElementName attrConstruct _ = constructDOMHTMLEmbedElementName -- VVV Prop "src" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLEmbedElementSrc :: (MonadIO m, DOMHTMLEmbedElementK o) => o -> m T.Text getDOMHTMLEmbedElementSrc obj = liftIO $ getObjectPropertyString obj "src" setDOMHTMLEmbedElementSrc :: (MonadIO m, DOMHTMLEmbedElementK o) => o -> T.Text -> m () setDOMHTMLEmbedElementSrc obj val = liftIO $ setObjectPropertyString obj "src" val constructDOMHTMLEmbedElementSrc :: T.Text -> IO ([Char], GValue) constructDOMHTMLEmbedElementSrc val = constructObjectPropertyString "src" val data DOMHTMLEmbedElementSrcPropertyInfo instance AttrInfo DOMHTMLEmbedElementSrcPropertyInfo where type AttrAllowedOps DOMHTMLEmbedElementSrcPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLEmbedElementSrcPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLEmbedElementSrcPropertyInfo = DOMHTMLEmbedElementK type AttrGetType DOMHTMLEmbedElementSrcPropertyInfo = T.Text type AttrLabel DOMHTMLEmbedElementSrcPropertyInfo = "DOMHTMLEmbedElement::src" attrGet _ = getDOMHTMLEmbedElementSrc attrSet _ = setDOMHTMLEmbedElementSrc attrConstruct _ = constructDOMHTMLEmbedElementSrc -- VVV Prop "type" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLEmbedElementType :: (MonadIO m, DOMHTMLEmbedElementK o) => o -> m T.Text getDOMHTMLEmbedElementType obj = liftIO $ getObjectPropertyString obj "type" setDOMHTMLEmbedElementType :: (MonadIO m, DOMHTMLEmbedElementK o) => o -> T.Text -> m () setDOMHTMLEmbedElementType obj val = liftIO $ setObjectPropertyString obj "type" val constructDOMHTMLEmbedElementType :: T.Text -> IO ([Char], GValue) constructDOMHTMLEmbedElementType val = constructObjectPropertyString "type" val data DOMHTMLEmbedElementTypePropertyInfo instance AttrInfo DOMHTMLEmbedElementTypePropertyInfo where type AttrAllowedOps DOMHTMLEmbedElementTypePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLEmbedElementTypePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLEmbedElementTypePropertyInfo = DOMHTMLEmbedElementK type AttrGetType DOMHTMLEmbedElementTypePropertyInfo = T.Text type AttrLabel DOMHTMLEmbedElementTypePropertyInfo = "DOMHTMLEmbedElement::type" attrGet _ = getDOMHTMLEmbedElementType attrSet _ = setDOMHTMLEmbedElementType attrConstruct _ = constructDOMHTMLEmbedElementType -- VVV Prop "width" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLEmbedElementWidth :: (MonadIO m, DOMHTMLEmbedElementK o) => o -> m Int64 getDOMHTMLEmbedElementWidth obj = liftIO $ getObjectPropertyInt64 obj "width" setDOMHTMLEmbedElementWidth :: (MonadIO m, DOMHTMLEmbedElementK o) => o -> Int64 -> m () setDOMHTMLEmbedElementWidth obj val = liftIO $ setObjectPropertyInt64 obj "width" val constructDOMHTMLEmbedElementWidth :: Int64 -> IO ([Char], GValue) constructDOMHTMLEmbedElementWidth val = constructObjectPropertyInt64 "width" val data DOMHTMLEmbedElementWidthPropertyInfo instance AttrInfo DOMHTMLEmbedElementWidthPropertyInfo where type AttrAllowedOps DOMHTMLEmbedElementWidthPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLEmbedElementWidthPropertyInfo = (~) Int64 type AttrBaseTypeConstraint DOMHTMLEmbedElementWidthPropertyInfo = DOMHTMLEmbedElementK type AttrGetType DOMHTMLEmbedElementWidthPropertyInfo = Int64 type AttrLabel DOMHTMLEmbedElementWidthPropertyInfo = "DOMHTMLEmbedElement::width" attrGet _ = getDOMHTMLEmbedElementWidth attrSet _ = setDOMHTMLEmbedElementWidth attrConstruct _ = constructDOMHTMLEmbedElementWidth type instance AttributeList DOMHTMLEmbedElement = '[ '("access-key", DOMHTMLElementAccessKeyPropertyInfo), '("align", DOMHTMLEmbedElementAlignPropertyInfo), '("attributes", DOMElementAttributesPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("child-element-count", DOMElementChildElementCountPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("children", DOMHTMLElementChildrenPropertyInfo), '("class-list", DOMElementClassListPropertyInfo), '("class-name", DOMElementClassNamePropertyInfo), '("client-height", DOMElementClientHeightPropertyInfo), '("client-left", DOMElementClientLeftPropertyInfo), '("client-top", DOMElementClientTopPropertyInfo), '("client-width", DOMElementClientWidthPropertyInfo), '("content-editable", DOMHTMLElementContentEditablePropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("dir", DOMHTMLElementDirPropertyInfo), '("draggable", DOMHTMLElementDraggablePropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("first-element-child", DOMElementFirstElementChildPropertyInfo), '("height", DOMHTMLEmbedElementHeightPropertyInfo), '("hidden", DOMHTMLElementHiddenPropertyInfo), '("id", DOMElementIdPropertyInfo), '("inner-html", DOMHTMLElementInnerHtmlPropertyInfo), '("inner-text", DOMHTMLElementInnerTextPropertyInfo), '("is-content-editable", DOMHTMLElementIsContentEditablePropertyInfo), '("lang", DOMHTMLElementLangPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-element-child", DOMElementLastElementChildPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("name", DOMHTMLEmbedElementNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-element-sibling", DOMElementNextElementSiblingPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("offset-height", DOMElementOffsetHeightPropertyInfo), '("offset-left", DOMElementOffsetLeftPropertyInfo), '("offset-parent", DOMElementOffsetParentPropertyInfo), '("offset-top", DOMElementOffsetTopPropertyInfo), '("offset-width", DOMElementOffsetWidthPropertyInfo), '("outer-html", DOMHTMLElementOuterHtmlPropertyInfo), '("outer-text", DOMHTMLElementOuterTextPropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-element-sibling", DOMElementPreviousElementSiblingPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("scroll-height", DOMElementScrollHeightPropertyInfo), '("scroll-left", DOMElementScrollLeftPropertyInfo), '("scroll-top", DOMElementScrollTopPropertyInfo), '("scroll-width", DOMElementScrollWidthPropertyInfo), '("spellcheck", DOMHTMLElementSpellcheckPropertyInfo), '("src", DOMHTMLEmbedElementSrcPropertyInfo), '("style", DOMElementStylePropertyInfo), '("tab-index", DOMHTMLElementTabIndexPropertyInfo), '("tag-name", DOMElementTagNamePropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("title", DOMHTMLElementTitlePropertyInfo), '("translate", DOMHTMLElementTranslatePropertyInfo), '("type", DOMHTMLEmbedElementTypePropertyInfo), '("webkit-region-overset", DOMElementWebkitRegionOversetPropertyInfo), '("webkitdropzone", DOMHTMLElementWebkitdropzonePropertyInfo), '("width", DOMHTMLEmbedElementWidthPropertyInfo)] -- VVV Prop "disabled" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLFieldSetElementDisabled :: (MonadIO m, DOMHTMLFieldSetElementK o) => o -> m Bool getDOMHTMLFieldSetElementDisabled obj = liftIO $ getObjectPropertyBool obj "disabled" setDOMHTMLFieldSetElementDisabled :: (MonadIO m, DOMHTMLFieldSetElementK o) => o -> Bool -> m () setDOMHTMLFieldSetElementDisabled obj val = liftIO $ setObjectPropertyBool obj "disabled" val constructDOMHTMLFieldSetElementDisabled :: Bool -> IO ([Char], GValue) constructDOMHTMLFieldSetElementDisabled val = constructObjectPropertyBool "disabled" val data DOMHTMLFieldSetElementDisabledPropertyInfo instance AttrInfo DOMHTMLFieldSetElementDisabledPropertyInfo where type AttrAllowedOps DOMHTMLFieldSetElementDisabledPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLFieldSetElementDisabledPropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLFieldSetElementDisabledPropertyInfo = DOMHTMLFieldSetElementK type AttrGetType DOMHTMLFieldSetElementDisabledPropertyInfo = Bool type AttrLabel DOMHTMLFieldSetElementDisabledPropertyInfo = "DOMHTMLFieldSetElement::disabled" attrGet _ = getDOMHTMLFieldSetElementDisabled attrSet _ = setDOMHTMLFieldSetElementDisabled attrConstruct _ = constructDOMHTMLFieldSetElementDisabled -- VVV Prop "elements" -- Type: TInterface "WebKit" "DOMHTMLCollection" -- Flags: [PropertyReadable] getDOMHTMLFieldSetElementElements :: (MonadIO m, DOMHTMLFieldSetElementK o) => o -> m DOMHTMLCollection getDOMHTMLFieldSetElementElements obj = liftIO $ getObjectPropertyObject obj "elements" DOMHTMLCollection data DOMHTMLFieldSetElementElementsPropertyInfo instance AttrInfo DOMHTMLFieldSetElementElementsPropertyInfo where type AttrAllowedOps DOMHTMLFieldSetElementElementsPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLFieldSetElementElementsPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLFieldSetElementElementsPropertyInfo = DOMHTMLFieldSetElementK type AttrGetType DOMHTMLFieldSetElementElementsPropertyInfo = DOMHTMLCollection type AttrLabel DOMHTMLFieldSetElementElementsPropertyInfo = "DOMHTMLFieldSetElement::elements" attrGet _ = getDOMHTMLFieldSetElementElements attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "form" -- Type: TInterface "WebKit" "DOMHTMLFormElement" -- Flags: [PropertyReadable] getDOMHTMLFieldSetElementForm :: (MonadIO m, DOMHTMLFieldSetElementK o) => o -> m DOMHTMLFormElement getDOMHTMLFieldSetElementForm obj = liftIO $ getObjectPropertyObject obj "form" DOMHTMLFormElement data DOMHTMLFieldSetElementFormPropertyInfo instance AttrInfo DOMHTMLFieldSetElementFormPropertyInfo where type AttrAllowedOps DOMHTMLFieldSetElementFormPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLFieldSetElementFormPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLFieldSetElementFormPropertyInfo = DOMHTMLFieldSetElementK type AttrGetType DOMHTMLFieldSetElementFormPropertyInfo = DOMHTMLFormElement type AttrLabel DOMHTMLFieldSetElementFormPropertyInfo = "DOMHTMLFieldSetElement::form" attrGet _ = getDOMHTMLFieldSetElementForm attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "name" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLFieldSetElementName :: (MonadIO m, DOMHTMLFieldSetElementK o) => o -> m T.Text getDOMHTMLFieldSetElementName obj = liftIO $ getObjectPropertyString obj "name" setDOMHTMLFieldSetElementName :: (MonadIO m, DOMHTMLFieldSetElementK o) => o -> T.Text -> m () setDOMHTMLFieldSetElementName obj val = liftIO $ setObjectPropertyString obj "name" val constructDOMHTMLFieldSetElementName :: T.Text -> IO ([Char], GValue) constructDOMHTMLFieldSetElementName val = constructObjectPropertyString "name" val data DOMHTMLFieldSetElementNamePropertyInfo instance AttrInfo DOMHTMLFieldSetElementNamePropertyInfo where type AttrAllowedOps DOMHTMLFieldSetElementNamePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLFieldSetElementNamePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLFieldSetElementNamePropertyInfo = DOMHTMLFieldSetElementK type AttrGetType DOMHTMLFieldSetElementNamePropertyInfo = T.Text type AttrLabel DOMHTMLFieldSetElementNamePropertyInfo = "DOMHTMLFieldSetElement::name" attrGet _ = getDOMHTMLFieldSetElementName attrSet _ = setDOMHTMLFieldSetElementName attrConstruct _ = constructDOMHTMLFieldSetElementName -- VVV Prop "type" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMHTMLFieldSetElementType :: (MonadIO m, DOMHTMLFieldSetElementK o) => o -> m T.Text getDOMHTMLFieldSetElementType obj = liftIO $ getObjectPropertyString obj "type" data DOMHTMLFieldSetElementTypePropertyInfo instance AttrInfo DOMHTMLFieldSetElementTypePropertyInfo where type AttrAllowedOps DOMHTMLFieldSetElementTypePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLFieldSetElementTypePropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLFieldSetElementTypePropertyInfo = DOMHTMLFieldSetElementK type AttrGetType DOMHTMLFieldSetElementTypePropertyInfo = T.Text type AttrLabel DOMHTMLFieldSetElementTypePropertyInfo = "DOMHTMLFieldSetElement::type" attrGet _ = getDOMHTMLFieldSetElementType attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "validation-message" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMHTMLFieldSetElementValidationMessage :: (MonadIO m, DOMHTMLFieldSetElementK o) => o -> m T.Text getDOMHTMLFieldSetElementValidationMessage obj = liftIO $ getObjectPropertyString obj "validation-message" data DOMHTMLFieldSetElementValidationMessagePropertyInfo instance AttrInfo DOMHTMLFieldSetElementValidationMessagePropertyInfo where type AttrAllowedOps DOMHTMLFieldSetElementValidationMessagePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLFieldSetElementValidationMessagePropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLFieldSetElementValidationMessagePropertyInfo = DOMHTMLFieldSetElementK type AttrGetType DOMHTMLFieldSetElementValidationMessagePropertyInfo = T.Text type AttrLabel DOMHTMLFieldSetElementValidationMessagePropertyInfo = "DOMHTMLFieldSetElement::validation-message" attrGet _ = getDOMHTMLFieldSetElementValidationMessage attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "validity" -- Type: TInterface "WebKit" "DOMValidityState" -- Flags: [PropertyReadable] getDOMHTMLFieldSetElementValidity :: (MonadIO m, DOMHTMLFieldSetElementK o) => o -> m DOMValidityState getDOMHTMLFieldSetElementValidity obj = liftIO $ getObjectPropertyObject obj "validity" DOMValidityState data DOMHTMLFieldSetElementValidityPropertyInfo instance AttrInfo DOMHTMLFieldSetElementValidityPropertyInfo where type AttrAllowedOps DOMHTMLFieldSetElementValidityPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLFieldSetElementValidityPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLFieldSetElementValidityPropertyInfo = DOMHTMLFieldSetElementK type AttrGetType DOMHTMLFieldSetElementValidityPropertyInfo = DOMValidityState type AttrLabel DOMHTMLFieldSetElementValidityPropertyInfo = "DOMHTMLFieldSetElement::validity" attrGet _ = getDOMHTMLFieldSetElementValidity attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "will-validate" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMHTMLFieldSetElementWillValidate :: (MonadIO m, DOMHTMLFieldSetElementK o) => o -> m Bool getDOMHTMLFieldSetElementWillValidate obj = liftIO $ getObjectPropertyBool obj "will-validate" data DOMHTMLFieldSetElementWillValidatePropertyInfo instance AttrInfo DOMHTMLFieldSetElementWillValidatePropertyInfo where type AttrAllowedOps DOMHTMLFieldSetElementWillValidatePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLFieldSetElementWillValidatePropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLFieldSetElementWillValidatePropertyInfo = DOMHTMLFieldSetElementK type AttrGetType DOMHTMLFieldSetElementWillValidatePropertyInfo = Bool type AttrLabel DOMHTMLFieldSetElementWillValidatePropertyInfo = "DOMHTMLFieldSetElement::will-validate" attrGet _ = getDOMHTMLFieldSetElementWillValidate attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMHTMLFieldSetElement = '[ '("access-key", DOMHTMLElementAccessKeyPropertyInfo), '("attributes", DOMElementAttributesPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("child-element-count", DOMElementChildElementCountPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("children", DOMHTMLElementChildrenPropertyInfo), '("class-list", DOMElementClassListPropertyInfo), '("class-name", DOMElementClassNamePropertyInfo), '("client-height", DOMElementClientHeightPropertyInfo), '("client-left", DOMElementClientLeftPropertyInfo), '("client-top", DOMElementClientTopPropertyInfo), '("client-width", DOMElementClientWidthPropertyInfo), '("content-editable", DOMHTMLElementContentEditablePropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("dir", DOMHTMLElementDirPropertyInfo), '("disabled", DOMHTMLFieldSetElementDisabledPropertyInfo), '("draggable", DOMHTMLElementDraggablePropertyInfo), '("elements", DOMHTMLFieldSetElementElementsPropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("first-element-child", DOMElementFirstElementChildPropertyInfo), '("form", DOMHTMLFieldSetElementFormPropertyInfo), '("hidden", DOMHTMLElementHiddenPropertyInfo), '("id", DOMElementIdPropertyInfo), '("inner-html", DOMHTMLElementInnerHtmlPropertyInfo), '("inner-text", DOMHTMLElementInnerTextPropertyInfo), '("is-content-editable", DOMHTMLElementIsContentEditablePropertyInfo), '("lang", DOMHTMLElementLangPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-element-child", DOMElementLastElementChildPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("name", DOMHTMLFieldSetElementNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-element-sibling", DOMElementNextElementSiblingPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("offset-height", DOMElementOffsetHeightPropertyInfo), '("offset-left", DOMElementOffsetLeftPropertyInfo), '("offset-parent", DOMElementOffsetParentPropertyInfo), '("offset-top", DOMElementOffsetTopPropertyInfo), '("offset-width", DOMElementOffsetWidthPropertyInfo), '("outer-html", DOMHTMLElementOuterHtmlPropertyInfo), '("outer-text", DOMHTMLElementOuterTextPropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-element-sibling", DOMElementPreviousElementSiblingPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("scroll-height", DOMElementScrollHeightPropertyInfo), '("scroll-left", DOMElementScrollLeftPropertyInfo), '("scroll-top", DOMElementScrollTopPropertyInfo), '("scroll-width", DOMElementScrollWidthPropertyInfo), '("spellcheck", DOMHTMLElementSpellcheckPropertyInfo), '("style", DOMElementStylePropertyInfo), '("tab-index", DOMHTMLElementTabIndexPropertyInfo), '("tag-name", DOMElementTagNamePropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("title", DOMHTMLElementTitlePropertyInfo), '("translate", DOMHTMLElementTranslatePropertyInfo), '("type", DOMHTMLFieldSetElementTypePropertyInfo), '("validation-message", DOMHTMLFieldSetElementValidationMessagePropertyInfo), '("validity", DOMHTMLFieldSetElementValidityPropertyInfo), '("webkit-region-overset", DOMElementWebkitRegionOversetPropertyInfo), '("webkitdropzone", DOMHTMLElementWebkitdropzonePropertyInfo), '("will-validate", DOMHTMLFieldSetElementWillValidatePropertyInfo)] -- VVV Prop "color" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLFontElementColor :: (MonadIO m, DOMHTMLFontElementK o) => o -> m T.Text getDOMHTMLFontElementColor obj = liftIO $ getObjectPropertyString obj "color" setDOMHTMLFontElementColor :: (MonadIO m, DOMHTMLFontElementK o) => o -> T.Text -> m () setDOMHTMLFontElementColor obj val = liftIO $ setObjectPropertyString obj "color" val constructDOMHTMLFontElementColor :: T.Text -> IO ([Char], GValue) constructDOMHTMLFontElementColor val = constructObjectPropertyString "color" val data DOMHTMLFontElementColorPropertyInfo instance AttrInfo DOMHTMLFontElementColorPropertyInfo where type AttrAllowedOps DOMHTMLFontElementColorPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLFontElementColorPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLFontElementColorPropertyInfo = DOMHTMLFontElementK type AttrGetType DOMHTMLFontElementColorPropertyInfo = T.Text type AttrLabel DOMHTMLFontElementColorPropertyInfo = "DOMHTMLFontElement::color" attrGet _ = getDOMHTMLFontElementColor attrSet _ = setDOMHTMLFontElementColor attrConstruct _ = constructDOMHTMLFontElementColor -- VVV Prop "face" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLFontElementFace :: (MonadIO m, DOMHTMLFontElementK o) => o -> m T.Text getDOMHTMLFontElementFace obj = liftIO $ getObjectPropertyString obj "face" setDOMHTMLFontElementFace :: (MonadIO m, DOMHTMLFontElementK o) => o -> T.Text -> m () setDOMHTMLFontElementFace obj val = liftIO $ setObjectPropertyString obj "face" val constructDOMHTMLFontElementFace :: T.Text -> IO ([Char], GValue) constructDOMHTMLFontElementFace val = constructObjectPropertyString "face" val data DOMHTMLFontElementFacePropertyInfo instance AttrInfo DOMHTMLFontElementFacePropertyInfo where type AttrAllowedOps DOMHTMLFontElementFacePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLFontElementFacePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLFontElementFacePropertyInfo = DOMHTMLFontElementK type AttrGetType DOMHTMLFontElementFacePropertyInfo = T.Text type AttrLabel DOMHTMLFontElementFacePropertyInfo = "DOMHTMLFontElement::face" attrGet _ = getDOMHTMLFontElementFace attrSet _ = setDOMHTMLFontElementFace attrConstruct _ = constructDOMHTMLFontElementFace -- VVV Prop "size" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLFontElementSize :: (MonadIO m, DOMHTMLFontElementK o) => o -> m T.Text getDOMHTMLFontElementSize obj = liftIO $ getObjectPropertyString obj "size" setDOMHTMLFontElementSize :: (MonadIO m, DOMHTMLFontElementK o) => o -> T.Text -> m () setDOMHTMLFontElementSize obj val = liftIO $ setObjectPropertyString obj "size" val constructDOMHTMLFontElementSize :: T.Text -> IO ([Char], GValue) constructDOMHTMLFontElementSize val = constructObjectPropertyString "size" val data DOMHTMLFontElementSizePropertyInfo instance AttrInfo DOMHTMLFontElementSizePropertyInfo where type AttrAllowedOps DOMHTMLFontElementSizePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLFontElementSizePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLFontElementSizePropertyInfo = DOMHTMLFontElementK type AttrGetType DOMHTMLFontElementSizePropertyInfo = T.Text type AttrLabel DOMHTMLFontElementSizePropertyInfo = "DOMHTMLFontElement::size" attrGet _ = getDOMHTMLFontElementSize attrSet _ = setDOMHTMLFontElementSize attrConstruct _ = constructDOMHTMLFontElementSize type instance AttributeList DOMHTMLFontElement = '[ '("access-key", DOMHTMLElementAccessKeyPropertyInfo), '("attributes", DOMElementAttributesPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("child-element-count", DOMElementChildElementCountPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("children", DOMHTMLElementChildrenPropertyInfo), '("class-list", DOMElementClassListPropertyInfo), '("class-name", DOMElementClassNamePropertyInfo), '("client-height", DOMElementClientHeightPropertyInfo), '("client-left", DOMElementClientLeftPropertyInfo), '("client-top", DOMElementClientTopPropertyInfo), '("client-width", DOMElementClientWidthPropertyInfo), '("color", DOMHTMLFontElementColorPropertyInfo), '("content-editable", DOMHTMLElementContentEditablePropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("dir", DOMHTMLElementDirPropertyInfo), '("draggable", DOMHTMLElementDraggablePropertyInfo), '("face", DOMHTMLFontElementFacePropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("first-element-child", DOMElementFirstElementChildPropertyInfo), '("hidden", DOMHTMLElementHiddenPropertyInfo), '("id", DOMElementIdPropertyInfo), '("inner-html", DOMHTMLElementInnerHtmlPropertyInfo), '("inner-text", DOMHTMLElementInnerTextPropertyInfo), '("is-content-editable", DOMHTMLElementIsContentEditablePropertyInfo), '("lang", DOMHTMLElementLangPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-element-child", DOMElementLastElementChildPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-element-sibling", DOMElementNextElementSiblingPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("offset-height", DOMElementOffsetHeightPropertyInfo), '("offset-left", DOMElementOffsetLeftPropertyInfo), '("offset-parent", DOMElementOffsetParentPropertyInfo), '("offset-top", DOMElementOffsetTopPropertyInfo), '("offset-width", DOMElementOffsetWidthPropertyInfo), '("outer-html", DOMHTMLElementOuterHtmlPropertyInfo), '("outer-text", DOMHTMLElementOuterTextPropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-element-sibling", DOMElementPreviousElementSiblingPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("scroll-height", DOMElementScrollHeightPropertyInfo), '("scroll-left", DOMElementScrollLeftPropertyInfo), '("scroll-top", DOMElementScrollTopPropertyInfo), '("scroll-width", DOMElementScrollWidthPropertyInfo), '("size", DOMHTMLFontElementSizePropertyInfo), '("spellcheck", DOMHTMLElementSpellcheckPropertyInfo), '("style", DOMElementStylePropertyInfo), '("tab-index", DOMHTMLElementTabIndexPropertyInfo), '("tag-name", DOMElementTagNamePropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("title", DOMHTMLElementTitlePropertyInfo), '("translate", DOMHTMLElementTranslatePropertyInfo), '("webkit-region-overset", DOMElementWebkitRegionOversetPropertyInfo), '("webkitdropzone", DOMHTMLElementWebkitdropzonePropertyInfo)] -- VVV Prop "accept-charset" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLFormElementAcceptCharset :: (MonadIO m, DOMHTMLFormElementK o) => o -> m T.Text getDOMHTMLFormElementAcceptCharset obj = liftIO $ getObjectPropertyString obj "accept-charset" setDOMHTMLFormElementAcceptCharset :: (MonadIO m, DOMHTMLFormElementK o) => o -> T.Text -> m () setDOMHTMLFormElementAcceptCharset obj val = liftIO $ setObjectPropertyString obj "accept-charset" val constructDOMHTMLFormElementAcceptCharset :: T.Text -> IO ([Char], GValue) constructDOMHTMLFormElementAcceptCharset val = constructObjectPropertyString "accept-charset" val data DOMHTMLFormElementAcceptCharsetPropertyInfo instance AttrInfo DOMHTMLFormElementAcceptCharsetPropertyInfo where type AttrAllowedOps DOMHTMLFormElementAcceptCharsetPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLFormElementAcceptCharsetPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLFormElementAcceptCharsetPropertyInfo = DOMHTMLFormElementK type AttrGetType DOMHTMLFormElementAcceptCharsetPropertyInfo = T.Text type AttrLabel DOMHTMLFormElementAcceptCharsetPropertyInfo = "DOMHTMLFormElement::accept-charset" attrGet _ = getDOMHTMLFormElementAcceptCharset attrSet _ = setDOMHTMLFormElementAcceptCharset attrConstruct _ = constructDOMHTMLFormElementAcceptCharset -- VVV Prop "action" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLFormElementAction :: (MonadIO m, DOMHTMLFormElementK o) => o -> m T.Text getDOMHTMLFormElementAction obj = liftIO $ getObjectPropertyString obj "action" setDOMHTMLFormElementAction :: (MonadIO m, DOMHTMLFormElementK o) => o -> T.Text -> m () setDOMHTMLFormElementAction obj val = liftIO $ setObjectPropertyString obj "action" val constructDOMHTMLFormElementAction :: T.Text -> IO ([Char], GValue) constructDOMHTMLFormElementAction val = constructObjectPropertyString "action" val data DOMHTMLFormElementActionPropertyInfo instance AttrInfo DOMHTMLFormElementActionPropertyInfo where type AttrAllowedOps DOMHTMLFormElementActionPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLFormElementActionPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLFormElementActionPropertyInfo = DOMHTMLFormElementK type AttrGetType DOMHTMLFormElementActionPropertyInfo = T.Text type AttrLabel DOMHTMLFormElementActionPropertyInfo = "DOMHTMLFormElement::action" attrGet _ = getDOMHTMLFormElementAction attrSet _ = setDOMHTMLFormElementAction attrConstruct _ = constructDOMHTMLFormElementAction -- VVV Prop "autocapitalize" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLFormElementAutocapitalize :: (MonadIO m, DOMHTMLFormElementK o) => o -> m T.Text getDOMHTMLFormElementAutocapitalize obj = liftIO $ getObjectPropertyString obj "autocapitalize" setDOMHTMLFormElementAutocapitalize :: (MonadIO m, DOMHTMLFormElementK o) => o -> T.Text -> m () setDOMHTMLFormElementAutocapitalize obj val = liftIO $ setObjectPropertyString obj "autocapitalize" val constructDOMHTMLFormElementAutocapitalize :: T.Text -> IO ([Char], GValue) constructDOMHTMLFormElementAutocapitalize val = constructObjectPropertyString "autocapitalize" val data DOMHTMLFormElementAutocapitalizePropertyInfo instance AttrInfo DOMHTMLFormElementAutocapitalizePropertyInfo where type AttrAllowedOps DOMHTMLFormElementAutocapitalizePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLFormElementAutocapitalizePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLFormElementAutocapitalizePropertyInfo = DOMHTMLFormElementK type AttrGetType DOMHTMLFormElementAutocapitalizePropertyInfo = T.Text type AttrLabel DOMHTMLFormElementAutocapitalizePropertyInfo = "DOMHTMLFormElement::autocapitalize" attrGet _ = getDOMHTMLFormElementAutocapitalize attrSet _ = setDOMHTMLFormElementAutocapitalize attrConstruct _ = constructDOMHTMLFormElementAutocapitalize -- VVV Prop "autocomplete" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLFormElementAutocomplete :: (MonadIO m, DOMHTMLFormElementK o) => o -> m T.Text getDOMHTMLFormElementAutocomplete obj = liftIO $ getObjectPropertyString obj "autocomplete" setDOMHTMLFormElementAutocomplete :: (MonadIO m, DOMHTMLFormElementK o) => o -> T.Text -> m () setDOMHTMLFormElementAutocomplete obj val = liftIO $ setObjectPropertyString obj "autocomplete" val constructDOMHTMLFormElementAutocomplete :: T.Text -> IO ([Char], GValue) constructDOMHTMLFormElementAutocomplete val = constructObjectPropertyString "autocomplete" val data DOMHTMLFormElementAutocompletePropertyInfo instance AttrInfo DOMHTMLFormElementAutocompletePropertyInfo where type AttrAllowedOps DOMHTMLFormElementAutocompletePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLFormElementAutocompletePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLFormElementAutocompletePropertyInfo = DOMHTMLFormElementK type AttrGetType DOMHTMLFormElementAutocompletePropertyInfo = T.Text type AttrLabel DOMHTMLFormElementAutocompletePropertyInfo = "DOMHTMLFormElement::autocomplete" attrGet _ = getDOMHTMLFormElementAutocomplete attrSet _ = setDOMHTMLFormElementAutocomplete attrConstruct _ = constructDOMHTMLFormElementAutocomplete -- VVV Prop "autocorrect" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLFormElementAutocorrect :: (MonadIO m, DOMHTMLFormElementK o) => o -> m Bool getDOMHTMLFormElementAutocorrect obj = liftIO $ getObjectPropertyBool obj "autocorrect" setDOMHTMLFormElementAutocorrect :: (MonadIO m, DOMHTMLFormElementK o) => o -> Bool -> m () setDOMHTMLFormElementAutocorrect obj val = liftIO $ setObjectPropertyBool obj "autocorrect" val constructDOMHTMLFormElementAutocorrect :: Bool -> IO ([Char], GValue) constructDOMHTMLFormElementAutocorrect val = constructObjectPropertyBool "autocorrect" val data DOMHTMLFormElementAutocorrectPropertyInfo instance AttrInfo DOMHTMLFormElementAutocorrectPropertyInfo where type AttrAllowedOps DOMHTMLFormElementAutocorrectPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLFormElementAutocorrectPropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLFormElementAutocorrectPropertyInfo = DOMHTMLFormElementK type AttrGetType DOMHTMLFormElementAutocorrectPropertyInfo = Bool type AttrLabel DOMHTMLFormElementAutocorrectPropertyInfo = "DOMHTMLFormElement::autocorrect" attrGet _ = getDOMHTMLFormElementAutocorrect attrSet _ = setDOMHTMLFormElementAutocorrect attrConstruct _ = constructDOMHTMLFormElementAutocorrect -- VVV Prop "elements" -- Type: TInterface "WebKit" "DOMHTMLCollection" -- Flags: [PropertyReadable] getDOMHTMLFormElementElements :: (MonadIO m, DOMHTMLFormElementK o) => o -> m DOMHTMLCollection getDOMHTMLFormElementElements obj = liftIO $ getObjectPropertyObject obj "elements" DOMHTMLCollection data DOMHTMLFormElementElementsPropertyInfo instance AttrInfo DOMHTMLFormElementElementsPropertyInfo where type AttrAllowedOps DOMHTMLFormElementElementsPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLFormElementElementsPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLFormElementElementsPropertyInfo = DOMHTMLFormElementK type AttrGetType DOMHTMLFormElementElementsPropertyInfo = DOMHTMLCollection type AttrLabel DOMHTMLFormElementElementsPropertyInfo = "DOMHTMLFormElement::elements" attrGet _ = getDOMHTMLFormElementElements attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "encoding" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLFormElementEncoding :: (MonadIO m, DOMHTMLFormElementK o) => o -> m T.Text getDOMHTMLFormElementEncoding obj = liftIO $ getObjectPropertyString obj "encoding" setDOMHTMLFormElementEncoding :: (MonadIO m, DOMHTMLFormElementK o) => o -> T.Text -> m () setDOMHTMLFormElementEncoding obj val = liftIO $ setObjectPropertyString obj "encoding" val constructDOMHTMLFormElementEncoding :: T.Text -> IO ([Char], GValue) constructDOMHTMLFormElementEncoding val = constructObjectPropertyString "encoding" val data DOMHTMLFormElementEncodingPropertyInfo instance AttrInfo DOMHTMLFormElementEncodingPropertyInfo where type AttrAllowedOps DOMHTMLFormElementEncodingPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLFormElementEncodingPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLFormElementEncodingPropertyInfo = DOMHTMLFormElementK type AttrGetType DOMHTMLFormElementEncodingPropertyInfo = T.Text type AttrLabel DOMHTMLFormElementEncodingPropertyInfo = "DOMHTMLFormElement::encoding" attrGet _ = getDOMHTMLFormElementEncoding attrSet _ = setDOMHTMLFormElementEncoding attrConstruct _ = constructDOMHTMLFormElementEncoding -- VVV Prop "enctype" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLFormElementEnctype :: (MonadIO m, DOMHTMLFormElementK o) => o -> m T.Text getDOMHTMLFormElementEnctype obj = liftIO $ getObjectPropertyString obj "enctype" setDOMHTMLFormElementEnctype :: (MonadIO m, DOMHTMLFormElementK o) => o -> T.Text -> m () setDOMHTMLFormElementEnctype obj val = liftIO $ setObjectPropertyString obj "enctype" val constructDOMHTMLFormElementEnctype :: T.Text -> IO ([Char], GValue) constructDOMHTMLFormElementEnctype val = constructObjectPropertyString "enctype" val data DOMHTMLFormElementEnctypePropertyInfo instance AttrInfo DOMHTMLFormElementEnctypePropertyInfo where type AttrAllowedOps DOMHTMLFormElementEnctypePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLFormElementEnctypePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLFormElementEnctypePropertyInfo = DOMHTMLFormElementK type AttrGetType DOMHTMLFormElementEnctypePropertyInfo = T.Text type AttrLabel DOMHTMLFormElementEnctypePropertyInfo = "DOMHTMLFormElement::enctype" attrGet _ = getDOMHTMLFormElementEnctype attrSet _ = setDOMHTMLFormElementEnctype attrConstruct _ = constructDOMHTMLFormElementEnctype -- VVV Prop "length" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMHTMLFormElementLength :: (MonadIO m, DOMHTMLFormElementK o) => o -> m Int64 getDOMHTMLFormElementLength obj = liftIO $ getObjectPropertyInt64 obj "length" data DOMHTMLFormElementLengthPropertyInfo instance AttrInfo DOMHTMLFormElementLengthPropertyInfo where type AttrAllowedOps DOMHTMLFormElementLengthPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLFormElementLengthPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLFormElementLengthPropertyInfo = DOMHTMLFormElementK type AttrGetType DOMHTMLFormElementLengthPropertyInfo = Int64 type AttrLabel DOMHTMLFormElementLengthPropertyInfo = "DOMHTMLFormElement::length" attrGet _ = getDOMHTMLFormElementLength attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "method" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLFormElementMethod :: (MonadIO m, DOMHTMLFormElementK o) => o -> m T.Text getDOMHTMLFormElementMethod obj = liftIO $ getObjectPropertyString obj "method" setDOMHTMLFormElementMethod :: (MonadIO m, DOMHTMLFormElementK o) => o -> T.Text -> m () setDOMHTMLFormElementMethod obj val = liftIO $ setObjectPropertyString obj "method" val constructDOMHTMLFormElementMethod :: T.Text -> IO ([Char], GValue) constructDOMHTMLFormElementMethod val = constructObjectPropertyString "method" val data DOMHTMLFormElementMethodPropertyInfo instance AttrInfo DOMHTMLFormElementMethodPropertyInfo where type AttrAllowedOps DOMHTMLFormElementMethodPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLFormElementMethodPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLFormElementMethodPropertyInfo = DOMHTMLFormElementK type AttrGetType DOMHTMLFormElementMethodPropertyInfo = T.Text type AttrLabel DOMHTMLFormElementMethodPropertyInfo = "DOMHTMLFormElement::method" attrGet _ = getDOMHTMLFormElementMethod attrSet _ = setDOMHTMLFormElementMethod attrConstruct _ = constructDOMHTMLFormElementMethod -- VVV Prop "name" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLFormElementName :: (MonadIO m, DOMHTMLFormElementK o) => o -> m T.Text getDOMHTMLFormElementName obj = liftIO $ getObjectPropertyString obj "name" setDOMHTMLFormElementName :: (MonadIO m, DOMHTMLFormElementK o) => o -> T.Text -> m () setDOMHTMLFormElementName obj val = liftIO $ setObjectPropertyString obj "name" val constructDOMHTMLFormElementName :: T.Text -> IO ([Char], GValue) constructDOMHTMLFormElementName val = constructObjectPropertyString "name" val data DOMHTMLFormElementNamePropertyInfo instance AttrInfo DOMHTMLFormElementNamePropertyInfo where type AttrAllowedOps DOMHTMLFormElementNamePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLFormElementNamePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLFormElementNamePropertyInfo = DOMHTMLFormElementK type AttrGetType DOMHTMLFormElementNamePropertyInfo = T.Text type AttrLabel DOMHTMLFormElementNamePropertyInfo = "DOMHTMLFormElement::name" attrGet _ = getDOMHTMLFormElementName attrSet _ = setDOMHTMLFormElementName attrConstruct _ = constructDOMHTMLFormElementName -- VVV Prop "no-validate" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLFormElementNoValidate :: (MonadIO m, DOMHTMLFormElementK o) => o -> m Bool getDOMHTMLFormElementNoValidate obj = liftIO $ getObjectPropertyBool obj "no-validate" setDOMHTMLFormElementNoValidate :: (MonadIO m, DOMHTMLFormElementK o) => o -> Bool -> m () setDOMHTMLFormElementNoValidate obj val = liftIO $ setObjectPropertyBool obj "no-validate" val constructDOMHTMLFormElementNoValidate :: Bool -> IO ([Char], GValue) constructDOMHTMLFormElementNoValidate val = constructObjectPropertyBool "no-validate" val data DOMHTMLFormElementNoValidatePropertyInfo instance AttrInfo DOMHTMLFormElementNoValidatePropertyInfo where type AttrAllowedOps DOMHTMLFormElementNoValidatePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLFormElementNoValidatePropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLFormElementNoValidatePropertyInfo = DOMHTMLFormElementK type AttrGetType DOMHTMLFormElementNoValidatePropertyInfo = Bool type AttrLabel DOMHTMLFormElementNoValidatePropertyInfo = "DOMHTMLFormElement::no-validate" attrGet _ = getDOMHTMLFormElementNoValidate attrSet _ = setDOMHTMLFormElementNoValidate attrConstruct _ = constructDOMHTMLFormElementNoValidate -- VVV Prop "target" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLFormElementTarget :: (MonadIO m, DOMHTMLFormElementK o) => o -> m T.Text getDOMHTMLFormElementTarget obj = liftIO $ getObjectPropertyString obj "target" setDOMHTMLFormElementTarget :: (MonadIO m, DOMHTMLFormElementK o) => o -> T.Text -> m () setDOMHTMLFormElementTarget obj val = liftIO $ setObjectPropertyString obj "target" val constructDOMHTMLFormElementTarget :: T.Text -> IO ([Char], GValue) constructDOMHTMLFormElementTarget val = constructObjectPropertyString "target" val data DOMHTMLFormElementTargetPropertyInfo instance AttrInfo DOMHTMLFormElementTargetPropertyInfo where type AttrAllowedOps DOMHTMLFormElementTargetPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLFormElementTargetPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLFormElementTargetPropertyInfo = DOMHTMLFormElementK type AttrGetType DOMHTMLFormElementTargetPropertyInfo = T.Text type AttrLabel DOMHTMLFormElementTargetPropertyInfo = "DOMHTMLFormElement::target" attrGet _ = getDOMHTMLFormElementTarget attrSet _ = setDOMHTMLFormElementTarget attrConstruct _ = constructDOMHTMLFormElementTarget type instance AttributeList DOMHTMLFormElement = '[ '("accept-charset", DOMHTMLFormElementAcceptCharsetPropertyInfo), '("access-key", DOMHTMLElementAccessKeyPropertyInfo), '("action", DOMHTMLFormElementActionPropertyInfo), '("attributes", DOMElementAttributesPropertyInfo), '("autocapitalize", DOMHTMLFormElementAutocapitalizePropertyInfo), '("autocomplete", DOMHTMLFormElementAutocompletePropertyInfo), '("autocorrect", DOMHTMLFormElementAutocorrectPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("child-element-count", DOMElementChildElementCountPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("children", DOMHTMLElementChildrenPropertyInfo), '("class-list", DOMElementClassListPropertyInfo), '("class-name", DOMElementClassNamePropertyInfo), '("client-height", DOMElementClientHeightPropertyInfo), '("client-left", DOMElementClientLeftPropertyInfo), '("client-top", DOMElementClientTopPropertyInfo), '("client-width", DOMElementClientWidthPropertyInfo), '("content-editable", DOMHTMLElementContentEditablePropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("dir", DOMHTMLElementDirPropertyInfo), '("draggable", DOMHTMLElementDraggablePropertyInfo), '("elements", DOMHTMLFormElementElementsPropertyInfo), '("encoding", DOMHTMLFormElementEncodingPropertyInfo), '("enctype", DOMHTMLFormElementEnctypePropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("first-element-child", DOMElementFirstElementChildPropertyInfo), '("hidden", DOMHTMLElementHiddenPropertyInfo), '("id", DOMElementIdPropertyInfo), '("inner-html", DOMHTMLElementInnerHtmlPropertyInfo), '("inner-text", DOMHTMLElementInnerTextPropertyInfo), '("is-content-editable", DOMHTMLElementIsContentEditablePropertyInfo), '("lang", DOMHTMLElementLangPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-element-child", DOMElementLastElementChildPropertyInfo), '("length", DOMHTMLFormElementLengthPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("method", DOMHTMLFormElementMethodPropertyInfo), '("name", DOMHTMLFormElementNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-element-sibling", DOMElementNextElementSiblingPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("no-validate", DOMHTMLFormElementNoValidatePropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("offset-height", DOMElementOffsetHeightPropertyInfo), '("offset-left", DOMElementOffsetLeftPropertyInfo), '("offset-parent", DOMElementOffsetParentPropertyInfo), '("offset-top", DOMElementOffsetTopPropertyInfo), '("offset-width", DOMElementOffsetWidthPropertyInfo), '("outer-html", DOMHTMLElementOuterHtmlPropertyInfo), '("outer-text", DOMHTMLElementOuterTextPropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-element-sibling", DOMElementPreviousElementSiblingPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("scroll-height", DOMElementScrollHeightPropertyInfo), '("scroll-left", DOMElementScrollLeftPropertyInfo), '("scroll-top", DOMElementScrollTopPropertyInfo), '("scroll-width", DOMElementScrollWidthPropertyInfo), '("spellcheck", DOMHTMLElementSpellcheckPropertyInfo), '("style", DOMElementStylePropertyInfo), '("tab-index", DOMHTMLElementTabIndexPropertyInfo), '("tag-name", DOMElementTagNamePropertyInfo), '("target", DOMHTMLFormElementTargetPropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("title", DOMHTMLElementTitlePropertyInfo), '("translate", DOMHTMLElementTranslatePropertyInfo), '("webkit-region-overset", DOMElementWebkitRegionOversetPropertyInfo), '("webkitdropzone", DOMHTMLElementWebkitdropzonePropertyInfo)] -- VVV Prop "content-document" -- Type: TInterface "WebKit" "DOMDocument" -- Flags: [PropertyReadable] getDOMHTMLFrameElementContentDocument :: (MonadIO m, DOMHTMLFrameElementK o) => o -> m DOMDocument getDOMHTMLFrameElementContentDocument obj = liftIO $ getObjectPropertyObject obj "content-document" DOMDocument data DOMHTMLFrameElementContentDocumentPropertyInfo instance AttrInfo DOMHTMLFrameElementContentDocumentPropertyInfo where type AttrAllowedOps DOMHTMLFrameElementContentDocumentPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLFrameElementContentDocumentPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLFrameElementContentDocumentPropertyInfo = DOMHTMLFrameElementK type AttrGetType DOMHTMLFrameElementContentDocumentPropertyInfo = DOMDocument type AttrLabel DOMHTMLFrameElementContentDocumentPropertyInfo = "DOMHTMLFrameElement::content-document" attrGet _ = getDOMHTMLFrameElementContentDocument attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "content-window" -- Type: TInterface "WebKit" "DOMDOMWindow" -- Flags: [PropertyReadable] getDOMHTMLFrameElementContentWindow :: (MonadIO m, DOMHTMLFrameElementK o) => o -> m DOMDOMWindow getDOMHTMLFrameElementContentWindow obj = liftIO $ getObjectPropertyObject obj "content-window" DOMDOMWindow data DOMHTMLFrameElementContentWindowPropertyInfo instance AttrInfo DOMHTMLFrameElementContentWindowPropertyInfo where type AttrAllowedOps DOMHTMLFrameElementContentWindowPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLFrameElementContentWindowPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLFrameElementContentWindowPropertyInfo = DOMHTMLFrameElementK type AttrGetType DOMHTMLFrameElementContentWindowPropertyInfo = DOMDOMWindow type AttrLabel DOMHTMLFrameElementContentWindowPropertyInfo = "DOMHTMLFrameElement::content-window" attrGet _ = getDOMHTMLFrameElementContentWindow attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "frame-border" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLFrameElementFrameBorder :: (MonadIO m, DOMHTMLFrameElementK o) => o -> m T.Text getDOMHTMLFrameElementFrameBorder obj = liftIO $ getObjectPropertyString obj "frame-border" setDOMHTMLFrameElementFrameBorder :: (MonadIO m, DOMHTMLFrameElementK o) => o -> T.Text -> m () setDOMHTMLFrameElementFrameBorder obj val = liftIO $ setObjectPropertyString obj "frame-border" val constructDOMHTMLFrameElementFrameBorder :: T.Text -> IO ([Char], GValue) constructDOMHTMLFrameElementFrameBorder val = constructObjectPropertyString "frame-border" val data DOMHTMLFrameElementFrameBorderPropertyInfo instance AttrInfo DOMHTMLFrameElementFrameBorderPropertyInfo where type AttrAllowedOps DOMHTMLFrameElementFrameBorderPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLFrameElementFrameBorderPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLFrameElementFrameBorderPropertyInfo = DOMHTMLFrameElementK type AttrGetType DOMHTMLFrameElementFrameBorderPropertyInfo = T.Text type AttrLabel DOMHTMLFrameElementFrameBorderPropertyInfo = "DOMHTMLFrameElement::frame-border" attrGet _ = getDOMHTMLFrameElementFrameBorder attrSet _ = setDOMHTMLFrameElementFrameBorder attrConstruct _ = constructDOMHTMLFrameElementFrameBorder -- VVV Prop "height" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMHTMLFrameElementHeight :: (MonadIO m, DOMHTMLFrameElementK o) => o -> m Int64 getDOMHTMLFrameElementHeight obj = liftIO $ getObjectPropertyInt64 obj "height" data DOMHTMLFrameElementHeightPropertyInfo instance AttrInfo DOMHTMLFrameElementHeightPropertyInfo where type AttrAllowedOps DOMHTMLFrameElementHeightPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLFrameElementHeightPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLFrameElementHeightPropertyInfo = DOMHTMLFrameElementK type AttrGetType DOMHTMLFrameElementHeightPropertyInfo = Int64 type AttrLabel DOMHTMLFrameElementHeightPropertyInfo = "DOMHTMLFrameElement::height" attrGet _ = getDOMHTMLFrameElementHeight attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "long-desc" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLFrameElementLongDesc :: (MonadIO m, DOMHTMLFrameElementK o) => o -> m T.Text getDOMHTMLFrameElementLongDesc obj = liftIO $ getObjectPropertyString obj "long-desc" setDOMHTMLFrameElementLongDesc :: (MonadIO m, DOMHTMLFrameElementK o) => o -> T.Text -> m () setDOMHTMLFrameElementLongDesc obj val = liftIO $ setObjectPropertyString obj "long-desc" val constructDOMHTMLFrameElementLongDesc :: T.Text -> IO ([Char], GValue) constructDOMHTMLFrameElementLongDesc val = constructObjectPropertyString "long-desc" val data DOMHTMLFrameElementLongDescPropertyInfo instance AttrInfo DOMHTMLFrameElementLongDescPropertyInfo where type AttrAllowedOps DOMHTMLFrameElementLongDescPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLFrameElementLongDescPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLFrameElementLongDescPropertyInfo = DOMHTMLFrameElementK type AttrGetType DOMHTMLFrameElementLongDescPropertyInfo = T.Text type AttrLabel DOMHTMLFrameElementLongDescPropertyInfo = "DOMHTMLFrameElement::long-desc" attrGet _ = getDOMHTMLFrameElementLongDesc attrSet _ = setDOMHTMLFrameElementLongDesc attrConstruct _ = constructDOMHTMLFrameElementLongDesc -- VVV Prop "margin-height" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLFrameElementMarginHeight :: (MonadIO m, DOMHTMLFrameElementK o) => o -> m T.Text getDOMHTMLFrameElementMarginHeight obj = liftIO $ getObjectPropertyString obj "margin-height" setDOMHTMLFrameElementMarginHeight :: (MonadIO m, DOMHTMLFrameElementK o) => o -> T.Text -> m () setDOMHTMLFrameElementMarginHeight obj val = liftIO $ setObjectPropertyString obj "margin-height" val constructDOMHTMLFrameElementMarginHeight :: T.Text -> IO ([Char], GValue) constructDOMHTMLFrameElementMarginHeight val = constructObjectPropertyString "margin-height" val data DOMHTMLFrameElementMarginHeightPropertyInfo instance AttrInfo DOMHTMLFrameElementMarginHeightPropertyInfo where type AttrAllowedOps DOMHTMLFrameElementMarginHeightPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLFrameElementMarginHeightPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLFrameElementMarginHeightPropertyInfo = DOMHTMLFrameElementK type AttrGetType DOMHTMLFrameElementMarginHeightPropertyInfo = T.Text type AttrLabel DOMHTMLFrameElementMarginHeightPropertyInfo = "DOMHTMLFrameElement::margin-height" attrGet _ = getDOMHTMLFrameElementMarginHeight attrSet _ = setDOMHTMLFrameElementMarginHeight attrConstruct _ = constructDOMHTMLFrameElementMarginHeight -- VVV Prop "margin-width" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLFrameElementMarginWidth :: (MonadIO m, DOMHTMLFrameElementK o) => o -> m T.Text getDOMHTMLFrameElementMarginWidth obj = liftIO $ getObjectPropertyString obj "margin-width" setDOMHTMLFrameElementMarginWidth :: (MonadIO m, DOMHTMLFrameElementK o) => o -> T.Text -> m () setDOMHTMLFrameElementMarginWidth obj val = liftIO $ setObjectPropertyString obj "margin-width" val constructDOMHTMLFrameElementMarginWidth :: T.Text -> IO ([Char], GValue) constructDOMHTMLFrameElementMarginWidth val = constructObjectPropertyString "margin-width" val data DOMHTMLFrameElementMarginWidthPropertyInfo instance AttrInfo DOMHTMLFrameElementMarginWidthPropertyInfo where type AttrAllowedOps DOMHTMLFrameElementMarginWidthPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLFrameElementMarginWidthPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLFrameElementMarginWidthPropertyInfo = DOMHTMLFrameElementK type AttrGetType DOMHTMLFrameElementMarginWidthPropertyInfo = T.Text type AttrLabel DOMHTMLFrameElementMarginWidthPropertyInfo = "DOMHTMLFrameElement::margin-width" attrGet _ = getDOMHTMLFrameElementMarginWidth attrSet _ = setDOMHTMLFrameElementMarginWidth attrConstruct _ = constructDOMHTMLFrameElementMarginWidth -- VVV Prop "name" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLFrameElementName :: (MonadIO m, DOMHTMLFrameElementK o) => o -> m T.Text getDOMHTMLFrameElementName obj = liftIO $ getObjectPropertyString obj "name" setDOMHTMLFrameElementName :: (MonadIO m, DOMHTMLFrameElementK o) => o -> T.Text -> m () setDOMHTMLFrameElementName obj val = liftIO $ setObjectPropertyString obj "name" val constructDOMHTMLFrameElementName :: T.Text -> IO ([Char], GValue) constructDOMHTMLFrameElementName val = constructObjectPropertyString "name" val data DOMHTMLFrameElementNamePropertyInfo instance AttrInfo DOMHTMLFrameElementNamePropertyInfo where type AttrAllowedOps DOMHTMLFrameElementNamePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLFrameElementNamePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLFrameElementNamePropertyInfo = DOMHTMLFrameElementK type AttrGetType DOMHTMLFrameElementNamePropertyInfo = T.Text type AttrLabel DOMHTMLFrameElementNamePropertyInfo = "DOMHTMLFrameElement::name" attrGet _ = getDOMHTMLFrameElementName attrSet _ = setDOMHTMLFrameElementName attrConstruct _ = constructDOMHTMLFrameElementName -- VVV Prop "no-resize" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLFrameElementNoResize :: (MonadIO m, DOMHTMLFrameElementK o) => o -> m Bool getDOMHTMLFrameElementNoResize obj = liftIO $ getObjectPropertyBool obj "no-resize" setDOMHTMLFrameElementNoResize :: (MonadIO m, DOMHTMLFrameElementK o) => o -> Bool -> m () setDOMHTMLFrameElementNoResize obj val = liftIO $ setObjectPropertyBool obj "no-resize" val constructDOMHTMLFrameElementNoResize :: Bool -> IO ([Char], GValue) constructDOMHTMLFrameElementNoResize val = constructObjectPropertyBool "no-resize" val data DOMHTMLFrameElementNoResizePropertyInfo instance AttrInfo DOMHTMLFrameElementNoResizePropertyInfo where type AttrAllowedOps DOMHTMLFrameElementNoResizePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLFrameElementNoResizePropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLFrameElementNoResizePropertyInfo = DOMHTMLFrameElementK type AttrGetType DOMHTMLFrameElementNoResizePropertyInfo = Bool type AttrLabel DOMHTMLFrameElementNoResizePropertyInfo = "DOMHTMLFrameElement::no-resize" attrGet _ = getDOMHTMLFrameElementNoResize attrSet _ = setDOMHTMLFrameElementNoResize attrConstruct _ = constructDOMHTMLFrameElementNoResize -- VVV Prop "scrolling" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLFrameElementScrolling :: (MonadIO m, DOMHTMLFrameElementK o) => o -> m T.Text getDOMHTMLFrameElementScrolling obj = liftIO $ getObjectPropertyString obj "scrolling" setDOMHTMLFrameElementScrolling :: (MonadIO m, DOMHTMLFrameElementK o) => o -> T.Text -> m () setDOMHTMLFrameElementScrolling obj val = liftIO $ setObjectPropertyString obj "scrolling" val constructDOMHTMLFrameElementScrolling :: T.Text -> IO ([Char], GValue) constructDOMHTMLFrameElementScrolling val = constructObjectPropertyString "scrolling" val data DOMHTMLFrameElementScrollingPropertyInfo instance AttrInfo DOMHTMLFrameElementScrollingPropertyInfo where type AttrAllowedOps DOMHTMLFrameElementScrollingPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLFrameElementScrollingPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLFrameElementScrollingPropertyInfo = DOMHTMLFrameElementK type AttrGetType DOMHTMLFrameElementScrollingPropertyInfo = T.Text type AttrLabel DOMHTMLFrameElementScrollingPropertyInfo = "DOMHTMLFrameElement::scrolling" attrGet _ = getDOMHTMLFrameElementScrolling attrSet _ = setDOMHTMLFrameElementScrolling attrConstruct _ = constructDOMHTMLFrameElementScrolling -- VVV Prop "src" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLFrameElementSrc :: (MonadIO m, DOMHTMLFrameElementK o) => o -> m T.Text getDOMHTMLFrameElementSrc obj = liftIO $ getObjectPropertyString obj "src" setDOMHTMLFrameElementSrc :: (MonadIO m, DOMHTMLFrameElementK o) => o -> T.Text -> m () setDOMHTMLFrameElementSrc obj val = liftIO $ setObjectPropertyString obj "src" val constructDOMHTMLFrameElementSrc :: T.Text -> IO ([Char], GValue) constructDOMHTMLFrameElementSrc val = constructObjectPropertyString "src" val data DOMHTMLFrameElementSrcPropertyInfo instance AttrInfo DOMHTMLFrameElementSrcPropertyInfo where type AttrAllowedOps DOMHTMLFrameElementSrcPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLFrameElementSrcPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLFrameElementSrcPropertyInfo = DOMHTMLFrameElementK type AttrGetType DOMHTMLFrameElementSrcPropertyInfo = T.Text type AttrLabel DOMHTMLFrameElementSrcPropertyInfo = "DOMHTMLFrameElement::src" attrGet _ = getDOMHTMLFrameElementSrc attrSet _ = setDOMHTMLFrameElementSrc attrConstruct _ = constructDOMHTMLFrameElementSrc -- VVV Prop "width" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMHTMLFrameElementWidth :: (MonadIO m, DOMHTMLFrameElementK o) => o -> m Int64 getDOMHTMLFrameElementWidth obj = liftIO $ getObjectPropertyInt64 obj "width" data DOMHTMLFrameElementWidthPropertyInfo instance AttrInfo DOMHTMLFrameElementWidthPropertyInfo where type AttrAllowedOps DOMHTMLFrameElementWidthPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLFrameElementWidthPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLFrameElementWidthPropertyInfo = DOMHTMLFrameElementK type AttrGetType DOMHTMLFrameElementWidthPropertyInfo = Int64 type AttrLabel DOMHTMLFrameElementWidthPropertyInfo = "DOMHTMLFrameElement::width" attrGet _ = getDOMHTMLFrameElementWidth attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMHTMLFrameElement = '[ '("access-key", DOMHTMLElementAccessKeyPropertyInfo), '("attributes", DOMElementAttributesPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("child-element-count", DOMElementChildElementCountPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("children", DOMHTMLElementChildrenPropertyInfo), '("class-list", DOMElementClassListPropertyInfo), '("class-name", DOMElementClassNamePropertyInfo), '("client-height", DOMElementClientHeightPropertyInfo), '("client-left", DOMElementClientLeftPropertyInfo), '("client-top", DOMElementClientTopPropertyInfo), '("client-width", DOMElementClientWidthPropertyInfo), '("content-document", DOMHTMLFrameElementContentDocumentPropertyInfo), '("content-editable", DOMHTMLElementContentEditablePropertyInfo), '("content-window", DOMHTMLFrameElementContentWindowPropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("dir", DOMHTMLElementDirPropertyInfo), '("draggable", DOMHTMLElementDraggablePropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("first-element-child", DOMElementFirstElementChildPropertyInfo), '("frame-border", DOMHTMLFrameElementFrameBorderPropertyInfo), '("height", DOMHTMLFrameElementHeightPropertyInfo), '("hidden", DOMHTMLElementHiddenPropertyInfo), '("id", DOMElementIdPropertyInfo), '("inner-html", DOMHTMLElementInnerHtmlPropertyInfo), '("inner-text", DOMHTMLElementInnerTextPropertyInfo), '("is-content-editable", DOMHTMLElementIsContentEditablePropertyInfo), '("lang", DOMHTMLElementLangPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-element-child", DOMElementLastElementChildPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("long-desc", DOMHTMLFrameElementLongDescPropertyInfo), '("margin-height", DOMHTMLFrameElementMarginHeightPropertyInfo), '("margin-width", DOMHTMLFrameElementMarginWidthPropertyInfo), '("name", DOMHTMLFrameElementNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-element-sibling", DOMElementNextElementSiblingPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("no-resize", DOMHTMLFrameElementNoResizePropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("offset-height", DOMElementOffsetHeightPropertyInfo), '("offset-left", DOMElementOffsetLeftPropertyInfo), '("offset-parent", DOMElementOffsetParentPropertyInfo), '("offset-top", DOMElementOffsetTopPropertyInfo), '("offset-width", DOMElementOffsetWidthPropertyInfo), '("outer-html", DOMHTMLElementOuterHtmlPropertyInfo), '("outer-text", DOMHTMLElementOuterTextPropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-element-sibling", DOMElementPreviousElementSiblingPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("scroll-height", DOMElementScrollHeightPropertyInfo), '("scroll-left", DOMElementScrollLeftPropertyInfo), '("scroll-top", DOMElementScrollTopPropertyInfo), '("scroll-width", DOMElementScrollWidthPropertyInfo), '("scrolling", DOMHTMLFrameElementScrollingPropertyInfo), '("spellcheck", DOMHTMLElementSpellcheckPropertyInfo), '("src", DOMHTMLFrameElementSrcPropertyInfo), '("style", DOMElementStylePropertyInfo), '("tab-index", DOMHTMLElementTabIndexPropertyInfo), '("tag-name", DOMElementTagNamePropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("title", DOMHTMLElementTitlePropertyInfo), '("translate", DOMHTMLElementTranslatePropertyInfo), '("webkit-region-overset", DOMElementWebkitRegionOversetPropertyInfo), '("webkitdropzone", DOMHTMLElementWebkitdropzonePropertyInfo), '("width", DOMHTMLFrameElementWidthPropertyInfo)] -- VVV Prop "cols" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLFrameSetElementCols :: (MonadIO m, DOMHTMLFrameSetElementK o) => o -> m T.Text getDOMHTMLFrameSetElementCols obj = liftIO $ getObjectPropertyString obj "cols" setDOMHTMLFrameSetElementCols :: (MonadIO m, DOMHTMLFrameSetElementK o) => o -> T.Text -> m () setDOMHTMLFrameSetElementCols obj val = liftIO $ setObjectPropertyString obj "cols" val constructDOMHTMLFrameSetElementCols :: T.Text -> IO ([Char], GValue) constructDOMHTMLFrameSetElementCols val = constructObjectPropertyString "cols" val data DOMHTMLFrameSetElementColsPropertyInfo instance AttrInfo DOMHTMLFrameSetElementColsPropertyInfo where type AttrAllowedOps DOMHTMLFrameSetElementColsPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLFrameSetElementColsPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLFrameSetElementColsPropertyInfo = DOMHTMLFrameSetElementK type AttrGetType DOMHTMLFrameSetElementColsPropertyInfo = T.Text type AttrLabel DOMHTMLFrameSetElementColsPropertyInfo = "DOMHTMLFrameSetElement::cols" attrGet _ = getDOMHTMLFrameSetElementCols attrSet _ = setDOMHTMLFrameSetElementCols attrConstruct _ = constructDOMHTMLFrameSetElementCols -- VVV Prop "rows" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLFrameSetElementRows :: (MonadIO m, DOMHTMLFrameSetElementK o) => o -> m T.Text getDOMHTMLFrameSetElementRows obj = liftIO $ getObjectPropertyString obj "rows" setDOMHTMLFrameSetElementRows :: (MonadIO m, DOMHTMLFrameSetElementK o) => o -> T.Text -> m () setDOMHTMLFrameSetElementRows obj val = liftIO $ setObjectPropertyString obj "rows" val constructDOMHTMLFrameSetElementRows :: T.Text -> IO ([Char], GValue) constructDOMHTMLFrameSetElementRows val = constructObjectPropertyString "rows" val data DOMHTMLFrameSetElementRowsPropertyInfo instance AttrInfo DOMHTMLFrameSetElementRowsPropertyInfo where type AttrAllowedOps DOMHTMLFrameSetElementRowsPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLFrameSetElementRowsPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLFrameSetElementRowsPropertyInfo = DOMHTMLFrameSetElementK type AttrGetType DOMHTMLFrameSetElementRowsPropertyInfo = T.Text type AttrLabel DOMHTMLFrameSetElementRowsPropertyInfo = "DOMHTMLFrameSetElement::rows" attrGet _ = getDOMHTMLFrameSetElementRows attrSet _ = setDOMHTMLFrameSetElementRows attrConstruct _ = constructDOMHTMLFrameSetElementRows type instance AttributeList DOMHTMLFrameSetElement = '[ '("access-key", DOMHTMLElementAccessKeyPropertyInfo), '("attributes", DOMElementAttributesPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("child-element-count", DOMElementChildElementCountPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("children", DOMHTMLElementChildrenPropertyInfo), '("class-list", DOMElementClassListPropertyInfo), '("class-name", DOMElementClassNamePropertyInfo), '("client-height", DOMElementClientHeightPropertyInfo), '("client-left", DOMElementClientLeftPropertyInfo), '("client-top", DOMElementClientTopPropertyInfo), '("client-width", DOMElementClientWidthPropertyInfo), '("cols", DOMHTMLFrameSetElementColsPropertyInfo), '("content-editable", DOMHTMLElementContentEditablePropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("dir", DOMHTMLElementDirPropertyInfo), '("draggable", DOMHTMLElementDraggablePropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("first-element-child", DOMElementFirstElementChildPropertyInfo), '("hidden", DOMHTMLElementHiddenPropertyInfo), '("id", DOMElementIdPropertyInfo), '("inner-html", DOMHTMLElementInnerHtmlPropertyInfo), '("inner-text", DOMHTMLElementInnerTextPropertyInfo), '("is-content-editable", DOMHTMLElementIsContentEditablePropertyInfo), '("lang", DOMHTMLElementLangPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-element-child", DOMElementLastElementChildPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-element-sibling", DOMElementNextElementSiblingPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("offset-height", DOMElementOffsetHeightPropertyInfo), '("offset-left", DOMElementOffsetLeftPropertyInfo), '("offset-parent", DOMElementOffsetParentPropertyInfo), '("offset-top", DOMElementOffsetTopPropertyInfo), '("offset-width", DOMElementOffsetWidthPropertyInfo), '("outer-html", DOMHTMLElementOuterHtmlPropertyInfo), '("outer-text", DOMHTMLElementOuterTextPropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-element-sibling", DOMElementPreviousElementSiblingPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("rows", DOMHTMLFrameSetElementRowsPropertyInfo), '("scroll-height", DOMElementScrollHeightPropertyInfo), '("scroll-left", DOMElementScrollLeftPropertyInfo), '("scroll-top", DOMElementScrollTopPropertyInfo), '("scroll-width", DOMElementScrollWidthPropertyInfo), '("spellcheck", DOMHTMLElementSpellcheckPropertyInfo), '("style", DOMElementStylePropertyInfo), '("tab-index", DOMHTMLElementTabIndexPropertyInfo), '("tag-name", DOMElementTagNamePropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("title", DOMHTMLElementTitlePropertyInfo), '("translate", DOMHTMLElementTranslatePropertyInfo), '("webkit-region-overset", DOMElementWebkitRegionOversetPropertyInfo), '("webkitdropzone", DOMHTMLElementWebkitdropzonePropertyInfo)] -- VVV Prop "align" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLHRElementAlign :: (MonadIO m, DOMHTMLHRElementK o) => o -> m T.Text getDOMHTMLHRElementAlign obj = liftIO $ getObjectPropertyString obj "align" setDOMHTMLHRElementAlign :: (MonadIO m, DOMHTMLHRElementK o) => o -> T.Text -> m () setDOMHTMLHRElementAlign obj val = liftIO $ setObjectPropertyString obj "align" val constructDOMHTMLHRElementAlign :: T.Text -> IO ([Char], GValue) constructDOMHTMLHRElementAlign val = constructObjectPropertyString "align" val data DOMHTMLHRElementAlignPropertyInfo instance AttrInfo DOMHTMLHRElementAlignPropertyInfo where type AttrAllowedOps DOMHTMLHRElementAlignPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLHRElementAlignPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLHRElementAlignPropertyInfo = DOMHTMLHRElementK type AttrGetType DOMHTMLHRElementAlignPropertyInfo = T.Text type AttrLabel DOMHTMLHRElementAlignPropertyInfo = "DOMHTMLHRElement::align" attrGet _ = getDOMHTMLHRElementAlign attrSet _ = setDOMHTMLHRElementAlign attrConstruct _ = constructDOMHTMLHRElementAlign -- VVV Prop "no-shade" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLHRElementNoShade :: (MonadIO m, DOMHTMLHRElementK o) => o -> m Bool getDOMHTMLHRElementNoShade obj = liftIO $ getObjectPropertyBool obj "no-shade" setDOMHTMLHRElementNoShade :: (MonadIO m, DOMHTMLHRElementK o) => o -> Bool -> m () setDOMHTMLHRElementNoShade obj val = liftIO $ setObjectPropertyBool obj "no-shade" val constructDOMHTMLHRElementNoShade :: Bool -> IO ([Char], GValue) constructDOMHTMLHRElementNoShade val = constructObjectPropertyBool "no-shade" val data DOMHTMLHRElementNoShadePropertyInfo instance AttrInfo DOMHTMLHRElementNoShadePropertyInfo where type AttrAllowedOps DOMHTMLHRElementNoShadePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLHRElementNoShadePropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLHRElementNoShadePropertyInfo = DOMHTMLHRElementK type AttrGetType DOMHTMLHRElementNoShadePropertyInfo = Bool type AttrLabel DOMHTMLHRElementNoShadePropertyInfo = "DOMHTMLHRElement::no-shade" attrGet _ = getDOMHTMLHRElementNoShade attrSet _ = setDOMHTMLHRElementNoShade attrConstruct _ = constructDOMHTMLHRElementNoShade -- VVV Prop "size" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLHRElementSize :: (MonadIO m, DOMHTMLHRElementK o) => o -> m T.Text getDOMHTMLHRElementSize obj = liftIO $ getObjectPropertyString obj "size" setDOMHTMLHRElementSize :: (MonadIO m, DOMHTMLHRElementK o) => o -> T.Text -> m () setDOMHTMLHRElementSize obj val = liftIO $ setObjectPropertyString obj "size" val constructDOMHTMLHRElementSize :: T.Text -> IO ([Char], GValue) constructDOMHTMLHRElementSize val = constructObjectPropertyString "size" val data DOMHTMLHRElementSizePropertyInfo instance AttrInfo DOMHTMLHRElementSizePropertyInfo where type AttrAllowedOps DOMHTMLHRElementSizePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLHRElementSizePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLHRElementSizePropertyInfo = DOMHTMLHRElementK type AttrGetType DOMHTMLHRElementSizePropertyInfo = T.Text type AttrLabel DOMHTMLHRElementSizePropertyInfo = "DOMHTMLHRElement::size" attrGet _ = getDOMHTMLHRElementSize attrSet _ = setDOMHTMLHRElementSize attrConstruct _ = constructDOMHTMLHRElementSize -- VVV Prop "width" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLHRElementWidth :: (MonadIO m, DOMHTMLHRElementK o) => o -> m T.Text getDOMHTMLHRElementWidth obj = liftIO $ getObjectPropertyString obj "width" setDOMHTMLHRElementWidth :: (MonadIO m, DOMHTMLHRElementK o) => o -> T.Text -> m () setDOMHTMLHRElementWidth obj val = liftIO $ setObjectPropertyString obj "width" val constructDOMHTMLHRElementWidth :: T.Text -> IO ([Char], GValue) constructDOMHTMLHRElementWidth val = constructObjectPropertyString "width" val data DOMHTMLHRElementWidthPropertyInfo instance AttrInfo DOMHTMLHRElementWidthPropertyInfo where type AttrAllowedOps DOMHTMLHRElementWidthPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLHRElementWidthPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLHRElementWidthPropertyInfo = DOMHTMLHRElementK type AttrGetType DOMHTMLHRElementWidthPropertyInfo = T.Text type AttrLabel DOMHTMLHRElementWidthPropertyInfo = "DOMHTMLHRElement::width" attrGet _ = getDOMHTMLHRElementWidth attrSet _ = setDOMHTMLHRElementWidth attrConstruct _ = constructDOMHTMLHRElementWidth type instance AttributeList DOMHTMLHRElement = '[ '("access-key", DOMHTMLElementAccessKeyPropertyInfo), '("align", DOMHTMLHRElementAlignPropertyInfo), '("attributes", DOMElementAttributesPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("child-element-count", DOMElementChildElementCountPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("children", DOMHTMLElementChildrenPropertyInfo), '("class-list", DOMElementClassListPropertyInfo), '("class-name", DOMElementClassNamePropertyInfo), '("client-height", DOMElementClientHeightPropertyInfo), '("client-left", DOMElementClientLeftPropertyInfo), '("client-top", DOMElementClientTopPropertyInfo), '("client-width", DOMElementClientWidthPropertyInfo), '("content-editable", DOMHTMLElementContentEditablePropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("dir", DOMHTMLElementDirPropertyInfo), '("draggable", DOMHTMLElementDraggablePropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("first-element-child", DOMElementFirstElementChildPropertyInfo), '("hidden", DOMHTMLElementHiddenPropertyInfo), '("id", DOMElementIdPropertyInfo), '("inner-html", DOMHTMLElementInnerHtmlPropertyInfo), '("inner-text", DOMHTMLElementInnerTextPropertyInfo), '("is-content-editable", DOMHTMLElementIsContentEditablePropertyInfo), '("lang", DOMHTMLElementLangPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-element-child", DOMElementLastElementChildPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-element-sibling", DOMElementNextElementSiblingPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("no-shade", DOMHTMLHRElementNoShadePropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("offset-height", DOMElementOffsetHeightPropertyInfo), '("offset-left", DOMElementOffsetLeftPropertyInfo), '("offset-parent", DOMElementOffsetParentPropertyInfo), '("offset-top", DOMElementOffsetTopPropertyInfo), '("offset-width", DOMElementOffsetWidthPropertyInfo), '("outer-html", DOMHTMLElementOuterHtmlPropertyInfo), '("outer-text", DOMHTMLElementOuterTextPropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-element-sibling", DOMElementPreviousElementSiblingPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("scroll-height", DOMElementScrollHeightPropertyInfo), '("scroll-left", DOMElementScrollLeftPropertyInfo), '("scroll-top", DOMElementScrollTopPropertyInfo), '("scroll-width", DOMElementScrollWidthPropertyInfo), '("size", DOMHTMLHRElementSizePropertyInfo), '("spellcheck", DOMHTMLElementSpellcheckPropertyInfo), '("style", DOMElementStylePropertyInfo), '("tab-index", DOMHTMLElementTabIndexPropertyInfo), '("tag-name", DOMElementTagNamePropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("title", DOMHTMLElementTitlePropertyInfo), '("translate", DOMHTMLElementTranslatePropertyInfo), '("webkit-region-overset", DOMElementWebkitRegionOversetPropertyInfo), '("webkitdropzone", DOMHTMLElementWebkitdropzonePropertyInfo), '("width", DOMHTMLHRElementWidthPropertyInfo)] -- VVV Prop "profile" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLHeadElementProfile :: (MonadIO m, DOMHTMLHeadElementK o) => o -> m T.Text getDOMHTMLHeadElementProfile obj = liftIO $ getObjectPropertyString obj "profile" setDOMHTMLHeadElementProfile :: (MonadIO m, DOMHTMLHeadElementK o) => o -> T.Text -> m () setDOMHTMLHeadElementProfile obj val = liftIO $ setObjectPropertyString obj "profile" val constructDOMHTMLHeadElementProfile :: T.Text -> IO ([Char], GValue) constructDOMHTMLHeadElementProfile val = constructObjectPropertyString "profile" val data DOMHTMLHeadElementProfilePropertyInfo instance AttrInfo DOMHTMLHeadElementProfilePropertyInfo where type AttrAllowedOps DOMHTMLHeadElementProfilePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLHeadElementProfilePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLHeadElementProfilePropertyInfo = DOMHTMLHeadElementK type AttrGetType DOMHTMLHeadElementProfilePropertyInfo = T.Text type AttrLabel DOMHTMLHeadElementProfilePropertyInfo = "DOMHTMLHeadElement::profile" attrGet _ = getDOMHTMLHeadElementProfile attrSet _ = setDOMHTMLHeadElementProfile attrConstruct _ = constructDOMHTMLHeadElementProfile type instance AttributeList DOMHTMLHeadElement = '[ '("access-key", DOMHTMLElementAccessKeyPropertyInfo), '("attributes", DOMElementAttributesPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("child-element-count", DOMElementChildElementCountPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("children", DOMHTMLElementChildrenPropertyInfo), '("class-list", DOMElementClassListPropertyInfo), '("class-name", DOMElementClassNamePropertyInfo), '("client-height", DOMElementClientHeightPropertyInfo), '("client-left", DOMElementClientLeftPropertyInfo), '("client-top", DOMElementClientTopPropertyInfo), '("client-width", DOMElementClientWidthPropertyInfo), '("content-editable", DOMHTMLElementContentEditablePropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("dir", DOMHTMLElementDirPropertyInfo), '("draggable", DOMHTMLElementDraggablePropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("first-element-child", DOMElementFirstElementChildPropertyInfo), '("hidden", DOMHTMLElementHiddenPropertyInfo), '("id", DOMElementIdPropertyInfo), '("inner-html", DOMHTMLElementInnerHtmlPropertyInfo), '("inner-text", DOMHTMLElementInnerTextPropertyInfo), '("is-content-editable", DOMHTMLElementIsContentEditablePropertyInfo), '("lang", DOMHTMLElementLangPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-element-child", DOMElementLastElementChildPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-element-sibling", DOMElementNextElementSiblingPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("offset-height", DOMElementOffsetHeightPropertyInfo), '("offset-left", DOMElementOffsetLeftPropertyInfo), '("offset-parent", DOMElementOffsetParentPropertyInfo), '("offset-top", DOMElementOffsetTopPropertyInfo), '("offset-width", DOMElementOffsetWidthPropertyInfo), '("outer-html", DOMHTMLElementOuterHtmlPropertyInfo), '("outer-text", DOMHTMLElementOuterTextPropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-element-sibling", DOMElementPreviousElementSiblingPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("profile", DOMHTMLHeadElementProfilePropertyInfo), '("scroll-height", DOMElementScrollHeightPropertyInfo), '("scroll-left", DOMElementScrollLeftPropertyInfo), '("scroll-top", DOMElementScrollTopPropertyInfo), '("scroll-width", DOMElementScrollWidthPropertyInfo), '("spellcheck", DOMHTMLElementSpellcheckPropertyInfo), '("style", DOMElementStylePropertyInfo), '("tab-index", DOMHTMLElementTabIndexPropertyInfo), '("tag-name", DOMElementTagNamePropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("title", DOMHTMLElementTitlePropertyInfo), '("translate", DOMHTMLElementTranslatePropertyInfo), '("webkit-region-overset", DOMElementWebkitRegionOversetPropertyInfo), '("webkitdropzone", DOMHTMLElementWebkitdropzonePropertyInfo)] -- VVV Prop "align" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLHeadingElementAlign :: (MonadIO m, DOMHTMLHeadingElementK o) => o -> m T.Text getDOMHTMLHeadingElementAlign obj = liftIO $ getObjectPropertyString obj "align" setDOMHTMLHeadingElementAlign :: (MonadIO m, DOMHTMLHeadingElementK o) => o -> T.Text -> m () setDOMHTMLHeadingElementAlign obj val = liftIO $ setObjectPropertyString obj "align" val constructDOMHTMLHeadingElementAlign :: T.Text -> IO ([Char], GValue) constructDOMHTMLHeadingElementAlign val = constructObjectPropertyString "align" val data DOMHTMLHeadingElementAlignPropertyInfo instance AttrInfo DOMHTMLHeadingElementAlignPropertyInfo where type AttrAllowedOps DOMHTMLHeadingElementAlignPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLHeadingElementAlignPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLHeadingElementAlignPropertyInfo = DOMHTMLHeadingElementK type AttrGetType DOMHTMLHeadingElementAlignPropertyInfo = T.Text type AttrLabel DOMHTMLHeadingElementAlignPropertyInfo = "DOMHTMLHeadingElement::align" attrGet _ = getDOMHTMLHeadingElementAlign attrSet _ = setDOMHTMLHeadingElementAlign attrConstruct _ = constructDOMHTMLHeadingElementAlign type instance AttributeList DOMHTMLHeadingElement = '[ '("access-key", DOMHTMLElementAccessKeyPropertyInfo), '("align", DOMHTMLHeadingElementAlignPropertyInfo), '("attributes", DOMElementAttributesPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("child-element-count", DOMElementChildElementCountPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("children", DOMHTMLElementChildrenPropertyInfo), '("class-list", DOMElementClassListPropertyInfo), '("class-name", DOMElementClassNamePropertyInfo), '("client-height", DOMElementClientHeightPropertyInfo), '("client-left", DOMElementClientLeftPropertyInfo), '("client-top", DOMElementClientTopPropertyInfo), '("client-width", DOMElementClientWidthPropertyInfo), '("content-editable", DOMHTMLElementContentEditablePropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("dir", DOMHTMLElementDirPropertyInfo), '("draggable", DOMHTMLElementDraggablePropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("first-element-child", DOMElementFirstElementChildPropertyInfo), '("hidden", DOMHTMLElementHiddenPropertyInfo), '("id", DOMElementIdPropertyInfo), '("inner-html", DOMHTMLElementInnerHtmlPropertyInfo), '("inner-text", DOMHTMLElementInnerTextPropertyInfo), '("is-content-editable", DOMHTMLElementIsContentEditablePropertyInfo), '("lang", DOMHTMLElementLangPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-element-child", DOMElementLastElementChildPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-element-sibling", DOMElementNextElementSiblingPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("offset-height", DOMElementOffsetHeightPropertyInfo), '("offset-left", DOMElementOffsetLeftPropertyInfo), '("offset-parent", DOMElementOffsetParentPropertyInfo), '("offset-top", DOMElementOffsetTopPropertyInfo), '("offset-width", DOMElementOffsetWidthPropertyInfo), '("outer-html", DOMHTMLElementOuterHtmlPropertyInfo), '("outer-text", DOMHTMLElementOuterTextPropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-element-sibling", DOMElementPreviousElementSiblingPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("scroll-height", DOMElementScrollHeightPropertyInfo), '("scroll-left", DOMElementScrollLeftPropertyInfo), '("scroll-top", DOMElementScrollTopPropertyInfo), '("scroll-width", DOMElementScrollWidthPropertyInfo), '("spellcheck", DOMHTMLElementSpellcheckPropertyInfo), '("style", DOMElementStylePropertyInfo), '("tab-index", DOMHTMLElementTabIndexPropertyInfo), '("tag-name", DOMElementTagNamePropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("title", DOMHTMLElementTitlePropertyInfo), '("translate", DOMHTMLElementTranslatePropertyInfo), '("webkit-region-overset", DOMElementWebkitRegionOversetPropertyInfo), '("webkitdropzone", DOMHTMLElementWebkitdropzonePropertyInfo)] -- VVV Prop "manifest" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLHtmlElementManifest :: (MonadIO m, DOMHTMLHtmlElementK o) => o -> m T.Text getDOMHTMLHtmlElementManifest obj = liftIO $ getObjectPropertyString obj "manifest" setDOMHTMLHtmlElementManifest :: (MonadIO m, DOMHTMLHtmlElementK o) => o -> T.Text -> m () setDOMHTMLHtmlElementManifest obj val = liftIO $ setObjectPropertyString obj "manifest" val constructDOMHTMLHtmlElementManifest :: T.Text -> IO ([Char], GValue) constructDOMHTMLHtmlElementManifest val = constructObjectPropertyString "manifest" val data DOMHTMLHtmlElementManifestPropertyInfo instance AttrInfo DOMHTMLHtmlElementManifestPropertyInfo where type AttrAllowedOps DOMHTMLHtmlElementManifestPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLHtmlElementManifestPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLHtmlElementManifestPropertyInfo = DOMHTMLHtmlElementK type AttrGetType DOMHTMLHtmlElementManifestPropertyInfo = T.Text type AttrLabel DOMHTMLHtmlElementManifestPropertyInfo = "DOMHTMLHtmlElement::manifest" attrGet _ = getDOMHTMLHtmlElementManifest attrSet _ = setDOMHTMLHtmlElementManifest attrConstruct _ = constructDOMHTMLHtmlElementManifest -- VVV Prop "version" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLHtmlElementVersion :: (MonadIO m, DOMHTMLHtmlElementK o) => o -> m T.Text getDOMHTMLHtmlElementVersion obj = liftIO $ getObjectPropertyString obj "version" setDOMHTMLHtmlElementVersion :: (MonadIO m, DOMHTMLHtmlElementK o) => o -> T.Text -> m () setDOMHTMLHtmlElementVersion obj val = liftIO $ setObjectPropertyString obj "version" val constructDOMHTMLHtmlElementVersion :: T.Text -> IO ([Char], GValue) constructDOMHTMLHtmlElementVersion val = constructObjectPropertyString "version" val data DOMHTMLHtmlElementVersionPropertyInfo instance AttrInfo DOMHTMLHtmlElementVersionPropertyInfo where type AttrAllowedOps DOMHTMLHtmlElementVersionPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLHtmlElementVersionPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLHtmlElementVersionPropertyInfo = DOMHTMLHtmlElementK type AttrGetType DOMHTMLHtmlElementVersionPropertyInfo = T.Text type AttrLabel DOMHTMLHtmlElementVersionPropertyInfo = "DOMHTMLHtmlElement::version" attrGet _ = getDOMHTMLHtmlElementVersion attrSet _ = setDOMHTMLHtmlElementVersion attrConstruct _ = constructDOMHTMLHtmlElementVersion type instance AttributeList DOMHTMLHtmlElement = '[ '("access-key", DOMHTMLElementAccessKeyPropertyInfo), '("attributes", DOMElementAttributesPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("child-element-count", DOMElementChildElementCountPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("children", DOMHTMLElementChildrenPropertyInfo), '("class-list", DOMElementClassListPropertyInfo), '("class-name", DOMElementClassNamePropertyInfo), '("client-height", DOMElementClientHeightPropertyInfo), '("client-left", DOMElementClientLeftPropertyInfo), '("client-top", DOMElementClientTopPropertyInfo), '("client-width", DOMElementClientWidthPropertyInfo), '("content-editable", DOMHTMLElementContentEditablePropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("dir", DOMHTMLElementDirPropertyInfo), '("draggable", DOMHTMLElementDraggablePropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("first-element-child", DOMElementFirstElementChildPropertyInfo), '("hidden", DOMHTMLElementHiddenPropertyInfo), '("id", DOMElementIdPropertyInfo), '("inner-html", DOMHTMLElementInnerHtmlPropertyInfo), '("inner-text", DOMHTMLElementInnerTextPropertyInfo), '("is-content-editable", DOMHTMLElementIsContentEditablePropertyInfo), '("lang", DOMHTMLElementLangPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-element-child", DOMElementLastElementChildPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("manifest", DOMHTMLHtmlElementManifestPropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-element-sibling", DOMElementNextElementSiblingPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("offset-height", DOMElementOffsetHeightPropertyInfo), '("offset-left", DOMElementOffsetLeftPropertyInfo), '("offset-parent", DOMElementOffsetParentPropertyInfo), '("offset-top", DOMElementOffsetTopPropertyInfo), '("offset-width", DOMElementOffsetWidthPropertyInfo), '("outer-html", DOMHTMLElementOuterHtmlPropertyInfo), '("outer-text", DOMHTMLElementOuterTextPropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-element-sibling", DOMElementPreviousElementSiblingPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("scroll-height", DOMElementScrollHeightPropertyInfo), '("scroll-left", DOMElementScrollLeftPropertyInfo), '("scroll-top", DOMElementScrollTopPropertyInfo), '("scroll-width", DOMElementScrollWidthPropertyInfo), '("spellcheck", DOMHTMLElementSpellcheckPropertyInfo), '("style", DOMElementStylePropertyInfo), '("tab-index", DOMHTMLElementTabIndexPropertyInfo), '("tag-name", DOMElementTagNamePropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("title", DOMHTMLElementTitlePropertyInfo), '("translate", DOMHTMLElementTranslatePropertyInfo), '("version", DOMHTMLHtmlElementVersionPropertyInfo), '("webkit-region-overset", DOMElementWebkitRegionOversetPropertyInfo), '("webkitdropzone", DOMHTMLElementWebkitdropzonePropertyInfo)] -- VVV Prop "align" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLIFrameElementAlign :: (MonadIO m, DOMHTMLIFrameElementK o) => o -> m T.Text getDOMHTMLIFrameElementAlign obj = liftIO $ getObjectPropertyString obj "align" setDOMHTMLIFrameElementAlign :: (MonadIO m, DOMHTMLIFrameElementK o) => o -> T.Text -> m () setDOMHTMLIFrameElementAlign obj val = liftIO $ setObjectPropertyString obj "align" val constructDOMHTMLIFrameElementAlign :: T.Text -> IO ([Char], GValue) constructDOMHTMLIFrameElementAlign val = constructObjectPropertyString "align" val data DOMHTMLIFrameElementAlignPropertyInfo instance AttrInfo DOMHTMLIFrameElementAlignPropertyInfo where type AttrAllowedOps DOMHTMLIFrameElementAlignPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLIFrameElementAlignPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLIFrameElementAlignPropertyInfo = DOMHTMLIFrameElementK type AttrGetType DOMHTMLIFrameElementAlignPropertyInfo = T.Text type AttrLabel DOMHTMLIFrameElementAlignPropertyInfo = "DOMHTMLIFrameElement::align" attrGet _ = getDOMHTMLIFrameElementAlign attrSet _ = setDOMHTMLIFrameElementAlign attrConstruct _ = constructDOMHTMLIFrameElementAlign -- VVV Prop "content-document" -- Type: TInterface "WebKit" "DOMDocument" -- Flags: [PropertyReadable] getDOMHTMLIFrameElementContentDocument :: (MonadIO m, DOMHTMLIFrameElementK o) => o -> m DOMDocument getDOMHTMLIFrameElementContentDocument obj = liftIO $ getObjectPropertyObject obj "content-document" DOMDocument data DOMHTMLIFrameElementContentDocumentPropertyInfo instance AttrInfo DOMHTMLIFrameElementContentDocumentPropertyInfo where type AttrAllowedOps DOMHTMLIFrameElementContentDocumentPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLIFrameElementContentDocumentPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLIFrameElementContentDocumentPropertyInfo = DOMHTMLIFrameElementK type AttrGetType DOMHTMLIFrameElementContentDocumentPropertyInfo = DOMDocument type AttrLabel DOMHTMLIFrameElementContentDocumentPropertyInfo = "DOMHTMLIFrameElement::content-document" attrGet _ = getDOMHTMLIFrameElementContentDocument attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "content-window" -- Type: TInterface "WebKit" "DOMDOMWindow" -- Flags: [PropertyReadable] getDOMHTMLIFrameElementContentWindow :: (MonadIO m, DOMHTMLIFrameElementK o) => o -> m DOMDOMWindow getDOMHTMLIFrameElementContentWindow obj = liftIO $ getObjectPropertyObject obj "content-window" DOMDOMWindow data DOMHTMLIFrameElementContentWindowPropertyInfo instance AttrInfo DOMHTMLIFrameElementContentWindowPropertyInfo where type AttrAllowedOps DOMHTMLIFrameElementContentWindowPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLIFrameElementContentWindowPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLIFrameElementContentWindowPropertyInfo = DOMHTMLIFrameElementK type AttrGetType DOMHTMLIFrameElementContentWindowPropertyInfo = DOMDOMWindow type AttrLabel DOMHTMLIFrameElementContentWindowPropertyInfo = "DOMHTMLIFrameElement::content-window" attrGet _ = getDOMHTMLIFrameElementContentWindow attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "frame-border" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLIFrameElementFrameBorder :: (MonadIO m, DOMHTMLIFrameElementK o) => o -> m T.Text getDOMHTMLIFrameElementFrameBorder obj = liftIO $ getObjectPropertyString obj "frame-border" setDOMHTMLIFrameElementFrameBorder :: (MonadIO m, DOMHTMLIFrameElementK o) => o -> T.Text -> m () setDOMHTMLIFrameElementFrameBorder obj val = liftIO $ setObjectPropertyString obj "frame-border" val constructDOMHTMLIFrameElementFrameBorder :: T.Text -> IO ([Char], GValue) constructDOMHTMLIFrameElementFrameBorder val = constructObjectPropertyString "frame-border" val data DOMHTMLIFrameElementFrameBorderPropertyInfo instance AttrInfo DOMHTMLIFrameElementFrameBorderPropertyInfo where type AttrAllowedOps DOMHTMLIFrameElementFrameBorderPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLIFrameElementFrameBorderPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLIFrameElementFrameBorderPropertyInfo = DOMHTMLIFrameElementK type AttrGetType DOMHTMLIFrameElementFrameBorderPropertyInfo = T.Text type AttrLabel DOMHTMLIFrameElementFrameBorderPropertyInfo = "DOMHTMLIFrameElement::frame-border" attrGet _ = getDOMHTMLIFrameElementFrameBorder attrSet _ = setDOMHTMLIFrameElementFrameBorder attrConstruct _ = constructDOMHTMLIFrameElementFrameBorder -- VVV Prop "height" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLIFrameElementHeight :: (MonadIO m, DOMHTMLIFrameElementK o) => o -> m T.Text getDOMHTMLIFrameElementHeight obj = liftIO $ getObjectPropertyString obj "height" setDOMHTMLIFrameElementHeight :: (MonadIO m, DOMHTMLIFrameElementK o) => o -> T.Text -> m () setDOMHTMLIFrameElementHeight obj val = liftIO $ setObjectPropertyString obj "height" val constructDOMHTMLIFrameElementHeight :: T.Text -> IO ([Char], GValue) constructDOMHTMLIFrameElementHeight val = constructObjectPropertyString "height" val data DOMHTMLIFrameElementHeightPropertyInfo instance AttrInfo DOMHTMLIFrameElementHeightPropertyInfo where type AttrAllowedOps DOMHTMLIFrameElementHeightPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLIFrameElementHeightPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLIFrameElementHeightPropertyInfo = DOMHTMLIFrameElementK type AttrGetType DOMHTMLIFrameElementHeightPropertyInfo = T.Text type AttrLabel DOMHTMLIFrameElementHeightPropertyInfo = "DOMHTMLIFrameElement::height" attrGet _ = getDOMHTMLIFrameElementHeight attrSet _ = setDOMHTMLIFrameElementHeight attrConstruct _ = constructDOMHTMLIFrameElementHeight -- VVV Prop "long-desc" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLIFrameElementLongDesc :: (MonadIO m, DOMHTMLIFrameElementK o) => o -> m T.Text getDOMHTMLIFrameElementLongDesc obj = liftIO $ getObjectPropertyString obj "long-desc" setDOMHTMLIFrameElementLongDesc :: (MonadIO m, DOMHTMLIFrameElementK o) => o -> T.Text -> m () setDOMHTMLIFrameElementLongDesc obj val = liftIO $ setObjectPropertyString obj "long-desc" val constructDOMHTMLIFrameElementLongDesc :: T.Text -> IO ([Char], GValue) constructDOMHTMLIFrameElementLongDesc val = constructObjectPropertyString "long-desc" val data DOMHTMLIFrameElementLongDescPropertyInfo instance AttrInfo DOMHTMLIFrameElementLongDescPropertyInfo where type AttrAllowedOps DOMHTMLIFrameElementLongDescPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLIFrameElementLongDescPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLIFrameElementLongDescPropertyInfo = DOMHTMLIFrameElementK type AttrGetType DOMHTMLIFrameElementLongDescPropertyInfo = T.Text type AttrLabel DOMHTMLIFrameElementLongDescPropertyInfo = "DOMHTMLIFrameElement::long-desc" attrGet _ = getDOMHTMLIFrameElementLongDesc attrSet _ = setDOMHTMLIFrameElementLongDesc attrConstruct _ = constructDOMHTMLIFrameElementLongDesc -- VVV Prop "margin-height" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLIFrameElementMarginHeight :: (MonadIO m, DOMHTMLIFrameElementK o) => o -> m T.Text getDOMHTMLIFrameElementMarginHeight obj = liftIO $ getObjectPropertyString obj "margin-height" setDOMHTMLIFrameElementMarginHeight :: (MonadIO m, DOMHTMLIFrameElementK o) => o -> T.Text -> m () setDOMHTMLIFrameElementMarginHeight obj val = liftIO $ setObjectPropertyString obj "margin-height" val constructDOMHTMLIFrameElementMarginHeight :: T.Text -> IO ([Char], GValue) constructDOMHTMLIFrameElementMarginHeight val = constructObjectPropertyString "margin-height" val data DOMHTMLIFrameElementMarginHeightPropertyInfo instance AttrInfo DOMHTMLIFrameElementMarginHeightPropertyInfo where type AttrAllowedOps DOMHTMLIFrameElementMarginHeightPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLIFrameElementMarginHeightPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLIFrameElementMarginHeightPropertyInfo = DOMHTMLIFrameElementK type AttrGetType DOMHTMLIFrameElementMarginHeightPropertyInfo = T.Text type AttrLabel DOMHTMLIFrameElementMarginHeightPropertyInfo = "DOMHTMLIFrameElement::margin-height" attrGet _ = getDOMHTMLIFrameElementMarginHeight attrSet _ = setDOMHTMLIFrameElementMarginHeight attrConstruct _ = constructDOMHTMLIFrameElementMarginHeight -- VVV Prop "margin-width" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLIFrameElementMarginWidth :: (MonadIO m, DOMHTMLIFrameElementK o) => o -> m T.Text getDOMHTMLIFrameElementMarginWidth obj = liftIO $ getObjectPropertyString obj "margin-width" setDOMHTMLIFrameElementMarginWidth :: (MonadIO m, DOMHTMLIFrameElementK o) => o -> T.Text -> m () setDOMHTMLIFrameElementMarginWidth obj val = liftIO $ setObjectPropertyString obj "margin-width" val constructDOMHTMLIFrameElementMarginWidth :: T.Text -> IO ([Char], GValue) constructDOMHTMLIFrameElementMarginWidth val = constructObjectPropertyString "margin-width" val data DOMHTMLIFrameElementMarginWidthPropertyInfo instance AttrInfo DOMHTMLIFrameElementMarginWidthPropertyInfo where type AttrAllowedOps DOMHTMLIFrameElementMarginWidthPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLIFrameElementMarginWidthPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLIFrameElementMarginWidthPropertyInfo = DOMHTMLIFrameElementK type AttrGetType DOMHTMLIFrameElementMarginWidthPropertyInfo = T.Text type AttrLabel DOMHTMLIFrameElementMarginWidthPropertyInfo = "DOMHTMLIFrameElement::margin-width" attrGet _ = getDOMHTMLIFrameElementMarginWidth attrSet _ = setDOMHTMLIFrameElementMarginWidth attrConstruct _ = constructDOMHTMLIFrameElementMarginWidth -- VVV Prop "name" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLIFrameElementName :: (MonadIO m, DOMHTMLIFrameElementK o) => o -> m T.Text getDOMHTMLIFrameElementName obj = liftIO $ getObjectPropertyString obj "name" setDOMHTMLIFrameElementName :: (MonadIO m, DOMHTMLIFrameElementK o) => o -> T.Text -> m () setDOMHTMLIFrameElementName obj val = liftIO $ setObjectPropertyString obj "name" val constructDOMHTMLIFrameElementName :: T.Text -> IO ([Char], GValue) constructDOMHTMLIFrameElementName val = constructObjectPropertyString "name" val data DOMHTMLIFrameElementNamePropertyInfo instance AttrInfo DOMHTMLIFrameElementNamePropertyInfo where type AttrAllowedOps DOMHTMLIFrameElementNamePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLIFrameElementNamePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLIFrameElementNamePropertyInfo = DOMHTMLIFrameElementK type AttrGetType DOMHTMLIFrameElementNamePropertyInfo = T.Text type AttrLabel DOMHTMLIFrameElementNamePropertyInfo = "DOMHTMLIFrameElement::name" attrGet _ = getDOMHTMLIFrameElementName attrSet _ = setDOMHTMLIFrameElementName attrConstruct _ = constructDOMHTMLIFrameElementName -- VVV Prop "sandbox" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLIFrameElementSandbox :: (MonadIO m, DOMHTMLIFrameElementK o) => o -> m T.Text getDOMHTMLIFrameElementSandbox obj = liftIO $ getObjectPropertyString obj "sandbox" setDOMHTMLIFrameElementSandbox :: (MonadIO m, DOMHTMLIFrameElementK o) => o -> T.Text -> m () setDOMHTMLIFrameElementSandbox obj val = liftIO $ setObjectPropertyString obj "sandbox" val constructDOMHTMLIFrameElementSandbox :: T.Text -> IO ([Char], GValue) constructDOMHTMLIFrameElementSandbox val = constructObjectPropertyString "sandbox" val data DOMHTMLIFrameElementSandboxPropertyInfo instance AttrInfo DOMHTMLIFrameElementSandboxPropertyInfo where type AttrAllowedOps DOMHTMLIFrameElementSandboxPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLIFrameElementSandboxPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLIFrameElementSandboxPropertyInfo = DOMHTMLIFrameElementK type AttrGetType DOMHTMLIFrameElementSandboxPropertyInfo = T.Text type AttrLabel DOMHTMLIFrameElementSandboxPropertyInfo = "DOMHTMLIFrameElement::sandbox" attrGet _ = getDOMHTMLIFrameElementSandbox attrSet _ = setDOMHTMLIFrameElementSandbox attrConstruct _ = constructDOMHTMLIFrameElementSandbox -- VVV Prop "scrolling" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLIFrameElementScrolling :: (MonadIO m, DOMHTMLIFrameElementK o) => o -> m T.Text getDOMHTMLIFrameElementScrolling obj = liftIO $ getObjectPropertyString obj "scrolling" setDOMHTMLIFrameElementScrolling :: (MonadIO m, DOMHTMLIFrameElementK o) => o -> T.Text -> m () setDOMHTMLIFrameElementScrolling obj val = liftIO $ setObjectPropertyString obj "scrolling" val constructDOMHTMLIFrameElementScrolling :: T.Text -> IO ([Char], GValue) constructDOMHTMLIFrameElementScrolling val = constructObjectPropertyString "scrolling" val data DOMHTMLIFrameElementScrollingPropertyInfo instance AttrInfo DOMHTMLIFrameElementScrollingPropertyInfo where type AttrAllowedOps DOMHTMLIFrameElementScrollingPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLIFrameElementScrollingPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLIFrameElementScrollingPropertyInfo = DOMHTMLIFrameElementK type AttrGetType DOMHTMLIFrameElementScrollingPropertyInfo = T.Text type AttrLabel DOMHTMLIFrameElementScrollingPropertyInfo = "DOMHTMLIFrameElement::scrolling" attrGet _ = getDOMHTMLIFrameElementScrolling attrSet _ = setDOMHTMLIFrameElementScrolling attrConstruct _ = constructDOMHTMLIFrameElementScrolling -- VVV Prop "seamless" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLIFrameElementSeamless :: (MonadIO m, DOMHTMLIFrameElementK o) => o -> m Bool getDOMHTMLIFrameElementSeamless obj = liftIO $ getObjectPropertyBool obj "seamless" setDOMHTMLIFrameElementSeamless :: (MonadIO m, DOMHTMLIFrameElementK o) => o -> Bool -> m () setDOMHTMLIFrameElementSeamless obj val = liftIO $ setObjectPropertyBool obj "seamless" val constructDOMHTMLIFrameElementSeamless :: Bool -> IO ([Char], GValue) constructDOMHTMLIFrameElementSeamless val = constructObjectPropertyBool "seamless" val data DOMHTMLIFrameElementSeamlessPropertyInfo instance AttrInfo DOMHTMLIFrameElementSeamlessPropertyInfo where type AttrAllowedOps DOMHTMLIFrameElementSeamlessPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLIFrameElementSeamlessPropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLIFrameElementSeamlessPropertyInfo = DOMHTMLIFrameElementK type AttrGetType DOMHTMLIFrameElementSeamlessPropertyInfo = Bool type AttrLabel DOMHTMLIFrameElementSeamlessPropertyInfo = "DOMHTMLIFrameElement::seamless" attrGet _ = getDOMHTMLIFrameElementSeamless attrSet _ = setDOMHTMLIFrameElementSeamless attrConstruct _ = constructDOMHTMLIFrameElementSeamless -- VVV Prop "src" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLIFrameElementSrc :: (MonadIO m, DOMHTMLIFrameElementK o) => o -> m T.Text getDOMHTMLIFrameElementSrc obj = liftIO $ getObjectPropertyString obj "src" setDOMHTMLIFrameElementSrc :: (MonadIO m, DOMHTMLIFrameElementK o) => o -> T.Text -> m () setDOMHTMLIFrameElementSrc obj val = liftIO $ setObjectPropertyString obj "src" val constructDOMHTMLIFrameElementSrc :: T.Text -> IO ([Char], GValue) constructDOMHTMLIFrameElementSrc val = constructObjectPropertyString "src" val data DOMHTMLIFrameElementSrcPropertyInfo instance AttrInfo DOMHTMLIFrameElementSrcPropertyInfo where type AttrAllowedOps DOMHTMLIFrameElementSrcPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLIFrameElementSrcPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLIFrameElementSrcPropertyInfo = DOMHTMLIFrameElementK type AttrGetType DOMHTMLIFrameElementSrcPropertyInfo = T.Text type AttrLabel DOMHTMLIFrameElementSrcPropertyInfo = "DOMHTMLIFrameElement::src" attrGet _ = getDOMHTMLIFrameElementSrc attrSet _ = setDOMHTMLIFrameElementSrc attrConstruct _ = constructDOMHTMLIFrameElementSrc -- VVV Prop "srcdoc" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLIFrameElementSrcdoc :: (MonadIO m, DOMHTMLIFrameElementK o) => o -> m T.Text getDOMHTMLIFrameElementSrcdoc obj = liftIO $ getObjectPropertyString obj "srcdoc" setDOMHTMLIFrameElementSrcdoc :: (MonadIO m, DOMHTMLIFrameElementK o) => o -> T.Text -> m () setDOMHTMLIFrameElementSrcdoc obj val = liftIO $ setObjectPropertyString obj "srcdoc" val constructDOMHTMLIFrameElementSrcdoc :: T.Text -> IO ([Char], GValue) constructDOMHTMLIFrameElementSrcdoc val = constructObjectPropertyString "srcdoc" val data DOMHTMLIFrameElementSrcdocPropertyInfo instance AttrInfo DOMHTMLIFrameElementSrcdocPropertyInfo where type AttrAllowedOps DOMHTMLIFrameElementSrcdocPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLIFrameElementSrcdocPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLIFrameElementSrcdocPropertyInfo = DOMHTMLIFrameElementK type AttrGetType DOMHTMLIFrameElementSrcdocPropertyInfo = T.Text type AttrLabel DOMHTMLIFrameElementSrcdocPropertyInfo = "DOMHTMLIFrameElement::srcdoc" attrGet _ = getDOMHTMLIFrameElementSrcdoc attrSet _ = setDOMHTMLIFrameElementSrcdoc attrConstruct _ = constructDOMHTMLIFrameElementSrcdoc -- VVV Prop "width" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLIFrameElementWidth :: (MonadIO m, DOMHTMLIFrameElementK o) => o -> m T.Text getDOMHTMLIFrameElementWidth obj = liftIO $ getObjectPropertyString obj "width" setDOMHTMLIFrameElementWidth :: (MonadIO m, DOMHTMLIFrameElementK o) => o -> T.Text -> m () setDOMHTMLIFrameElementWidth obj val = liftIO $ setObjectPropertyString obj "width" val constructDOMHTMLIFrameElementWidth :: T.Text -> IO ([Char], GValue) constructDOMHTMLIFrameElementWidth val = constructObjectPropertyString "width" val data DOMHTMLIFrameElementWidthPropertyInfo instance AttrInfo DOMHTMLIFrameElementWidthPropertyInfo where type AttrAllowedOps DOMHTMLIFrameElementWidthPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLIFrameElementWidthPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLIFrameElementWidthPropertyInfo = DOMHTMLIFrameElementK type AttrGetType DOMHTMLIFrameElementWidthPropertyInfo = T.Text type AttrLabel DOMHTMLIFrameElementWidthPropertyInfo = "DOMHTMLIFrameElement::width" attrGet _ = getDOMHTMLIFrameElementWidth attrSet _ = setDOMHTMLIFrameElementWidth attrConstruct _ = constructDOMHTMLIFrameElementWidth type instance AttributeList DOMHTMLIFrameElement = '[ '("access-key", DOMHTMLElementAccessKeyPropertyInfo), '("align", DOMHTMLIFrameElementAlignPropertyInfo), '("attributes", DOMElementAttributesPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("child-element-count", DOMElementChildElementCountPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("children", DOMHTMLElementChildrenPropertyInfo), '("class-list", DOMElementClassListPropertyInfo), '("class-name", DOMElementClassNamePropertyInfo), '("client-height", DOMElementClientHeightPropertyInfo), '("client-left", DOMElementClientLeftPropertyInfo), '("client-top", DOMElementClientTopPropertyInfo), '("client-width", DOMElementClientWidthPropertyInfo), '("content-document", DOMHTMLIFrameElementContentDocumentPropertyInfo), '("content-editable", DOMHTMLElementContentEditablePropertyInfo), '("content-window", DOMHTMLIFrameElementContentWindowPropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("dir", DOMHTMLElementDirPropertyInfo), '("draggable", DOMHTMLElementDraggablePropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("first-element-child", DOMElementFirstElementChildPropertyInfo), '("frame-border", DOMHTMLIFrameElementFrameBorderPropertyInfo), '("height", DOMHTMLIFrameElementHeightPropertyInfo), '("hidden", DOMHTMLElementHiddenPropertyInfo), '("id", DOMElementIdPropertyInfo), '("inner-html", DOMHTMLElementInnerHtmlPropertyInfo), '("inner-text", DOMHTMLElementInnerTextPropertyInfo), '("is-content-editable", DOMHTMLElementIsContentEditablePropertyInfo), '("lang", DOMHTMLElementLangPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-element-child", DOMElementLastElementChildPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("long-desc", DOMHTMLIFrameElementLongDescPropertyInfo), '("margin-height", DOMHTMLIFrameElementMarginHeightPropertyInfo), '("margin-width", DOMHTMLIFrameElementMarginWidthPropertyInfo), '("name", DOMHTMLIFrameElementNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-element-sibling", DOMElementNextElementSiblingPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("offset-height", DOMElementOffsetHeightPropertyInfo), '("offset-left", DOMElementOffsetLeftPropertyInfo), '("offset-parent", DOMElementOffsetParentPropertyInfo), '("offset-top", DOMElementOffsetTopPropertyInfo), '("offset-width", DOMElementOffsetWidthPropertyInfo), '("outer-html", DOMHTMLElementOuterHtmlPropertyInfo), '("outer-text", DOMHTMLElementOuterTextPropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-element-sibling", DOMElementPreviousElementSiblingPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("sandbox", DOMHTMLIFrameElementSandboxPropertyInfo), '("scroll-height", DOMElementScrollHeightPropertyInfo), '("scroll-left", DOMElementScrollLeftPropertyInfo), '("scroll-top", DOMElementScrollTopPropertyInfo), '("scroll-width", DOMElementScrollWidthPropertyInfo), '("scrolling", DOMHTMLIFrameElementScrollingPropertyInfo), '("seamless", DOMHTMLIFrameElementSeamlessPropertyInfo), '("spellcheck", DOMHTMLElementSpellcheckPropertyInfo), '("src", DOMHTMLIFrameElementSrcPropertyInfo), '("srcdoc", DOMHTMLIFrameElementSrcdocPropertyInfo), '("style", DOMElementStylePropertyInfo), '("tab-index", DOMHTMLElementTabIndexPropertyInfo), '("tag-name", DOMElementTagNamePropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("title", DOMHTMLElementTitlePropertyInfo), '("translate", DOMHTMLElementTranslatePropertyInfo), '("webkit-region-overset", DOMElementWebkitRegionOversetPropertyInfo), '("webkitdropzone", DOMHTMLElementWebkitdropzonePropertyInfo), '("width", DOMHTMLIFrameElementWidthPropertyInfo)] -- VVV Prop "align" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLImageElementAlign :: (MonadIO m, DOMHTMLImageElementK o) => o -> m T.Text getDOMHTMLImageElementAlign obj = liftIO $ getObjectPropertyString obj "align" setDOMHTMLImageElementAlign :: (MonadIO m, DOMHTMLImageElementK o) => o -> T.Text -> m () setDOMHTMLImageElementAlign obj val = liftIO $ setObjectPropertyString obj "align" val constructDOMHTMLImageElementAlign :: T.Text -> IO ([Char], GValue) constructDOMHTMLImageElementAlign val = constructObjectPropertyString "align" val data DOMHTMLImageElementAlignPropertyInfo instance AttrInfo DOMHTMLImageElementAlignPropertyInfo where type AttrAllowedOps DOMHTMLImageElementAlignPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLImageElementAlignPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLImageElementAlignPropertyInfo = DOMHTMLImageElementK type AttrGetType DOMHTMLImageElementAlignPropertyInfo = T.Text type AttrLabel DOMHTMLImageElementAlignPropertyInfo = "DOMHTMLImageElement::align" attrGet _ = getDOMHTMLImageElementAlign attrSet _ = setDOMHTMLImageElementAlign attrConstruct _ = constructDOMHTMLImageElementAlign -- VVV Prop "alt" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLImageElementAlt :: (MonadIO m, DOMHTMLImageElementK o) => o -> m T.Text getDOMHTMLImageElementAlt obj = liftIO $ getObjectPropertyString obj "alt" setDOMHTMLImageElementAlt :: (MonadIO m, DOMHTMLImageElementK o) => o -> T.Text -> m () setDOMHTMLImageElementAlt obj val = liftIO $ setObjectPropertyString obj "alt" val constructDOMHTMLImageElementAlt :: T.Text -> IO ([Char], GValue) constructDOMHTMLImageElementAlt val = constructObjectPropertyString "alt" val data DOMHTMLImageElementAltPropertyInfo instance AttrInfo DOMHTMLImageElementAltPropertyInfo where type AttrAllowedOps DOMHTMLImageElementAltPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLImageElementAltPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLImageElementAltPropertyInfo = DOMHTMLImageElementK type AttrGetType DOMHTMLImageElementAltPropertyInfo = T.Text type AttrLabel DOMHTMLImageElementAltPropertyInfo = "DOMHTMLImageElement::alt" attrGet _ = getDOMHTMLImageElementAlt attrSet _ = setDOMHTMLImageElementAlt attrConstruct _ = constructDOMHTMLImageElementAlt -- VVV Prop "border" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLImageElementBorder :: (MonadIO m, DOMHTMLImageElementK o) => o -> m T.Text getDOMHTMLImageElementBorder obj = liftIO $ getObjectPropertyString obj "border" setDOMHTMLImageElementBorder :: (MonadIO m, DOMHTMLImageElementK o) => o -> T.Text -> m () setDOMHTMLImageElementBorder obj val = liftIO $ setObjectPropertyString obj "border" val constructDOMHTMLImageElementBorder :: T.Text -> IO ([Char], GValue) constructDOMHTMLImageElementBorder val = constructObjectPropertyString "border" val data DOMHTMLImageElementBorderPropertyInfo instance AttrInfo DOMHTMLImageElementBorderPropertyInfo where type AttrAllowedOps DOMHTMLImageElementBorderPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLImageElementBorderPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLImageElementBorderPropertyInfo = DOMHTMLImageElementK type AttrGetType DOMHTMLImageElementBorderPropertyInfo = T.Text type AttrLabel DOMHTMLImageElementBorderPropertyInfo = "DOMHTMLImageElement::border" attrGet _ = getDOMHTMLImageElementBorder attrSet _ = setDOMHTMLImageElementBorder attrConstruct _ = constructDOMHTMLImageElementBorder -- VVV Prop "complete" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMHTMLImageElementComplete :: (MonadIO m, DOMHTMLImageElementK o) => o -> m Bool getDOMHTMLImageElementComplete obj = liftIO $ getObjectPropertyBool obj "complete" data DOMHTMLImageElementCompletePropertyInfo instance AttrInfo DOMHTMLImageElementCompletePropertyInfo where type AttrAllowedOps DOMHTMLImageElementCompletePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLImageElementCompletePropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLImageElementCompletePropertyInfo = DOMHTMLImageElementK type AttrGetType DOMHTMLImageElementCompletePropertyInfo = Bool type AttrLabel DOMHTMLImageElementCompletePropertyInfo = "DOMHTMLImageElement::complete" attrGet _ = getDOMHTMLImageElementComplete attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "cross-origin" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLImageElementCrossOrigin :: (MonadIO m, DOMHTMLImageElementK o) => o -> m T.Text getDOMHTMLImageElementCrossOrigin obj = liftIO $ getObjectPropertyString obj "cross-origin" setDOMHTMLImageElementCrossOrigin :: (MonadIO m, DOMHTMLImageElementK o) => o -> T.Text -> m () setDOMHTMLImageElementCrossOrigin obj val = liftIO $ setObjectPropertyString obj "cross-origin" val constructDOMHTMLImageElementCrossOrigin :: T.Text -> IO ([Char], GValue) constructDOMHTMLImageElementCrossOrigin val = constructObjectPropertyString "cross-origin" val data DOMHTMLImageElementCrossOriginPropertyInfo instance AttrInfo DOMHTMLImageElementCrossOriginPropertyInfo where type AttrAllowedOps DOMHTMLImageElementCrossOriginPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLImageElementCrossOriginPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLImageElementCrossOriginPropertyInfo = DOMHTMLImageElementK type AttrGetType DOMHTMLImageElementCrossOriginPropertyInfo = T.Text type AttrLabel DOMHTMLImageElementCrossOriginPropertyInfo = "DOMHTMLImageElement::cross-origin" attrGet _ = getDOMHTMLImageElementCrossOrigin attrSet _ = setDOMHTMLImageElementCrossOrigin attrConstruct _ = constructDOMHTMLImageElementCrossOrigin -- VVV Prop "height" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLImageElementHeight :: (MonadIO m, DOMHTMLImageElementK o) => o -> m Int64 getDOMHTMLImageElementHeight obj = liftIO $ getObjectPropertyInt64 obj "height" setDOMHTMLImageElementHeight :: (MonadIO m, DOMHTMLImageElementK o) => o -> Int64 -> m () setDOMHTMLImageElementHeight obj val = liftIO $ setObjectPropertyInt64 obj "height" val constructDOMHTMLImageElementHeight :: Int64 -> IO ([Char], GValue) constructDOMHTMLImageElementHeight val = constructObjectPropertyInt64 "height" val data DOMHTMLImageElementHeightPropertyInfo instance AttrInfo DOMHTMLImageElementHeightPropertyInfo where type AttrAllowedOps DOMHTMLImageElementHeightPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLImageElementHeightPropertyInfo = (~) Int64 type AttrBaseTypeConstraint DOMHTMLImageElementHeightPropertyInfo = DOMHTMLImageElementK type AttrGetType DOMHTMLImageElementHeightPropertyInfo = Int64 type AttrLabel DOMHTMLImageElementHeightPropertyInfo = "DOMHTMLImageElement::height" attrGet _ = getDOMHTMLImageElementHeight attrSet _ = setDOMHTMLImageElementHeight attrConstruct _ = constructDOMHTMLImageElementHeight -- VVV Prop "hspace" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLImageElementHspace :: (MonadIO m, DOMHTMLImageElementK o) => o -> m Int64 getDOMHTMLImageElementHspace obj = liftIO $ getObjectPropertyInt64 obj "hspace" setDOMHTMLImageElementHspace :: (MonadIO m, DOMHTMLImageElementK o) => o -> Int64 -> m () setDOMHTMLImageElementHspace obj val = liftIO $ setObjectPropertyInt64 obj "hspace" val constructDOMHTMLImageElementHspace :: Int64 -> IO ([Char], GValue) constructDOMHTMLImageElementHspace val = constructObjectPropertyInt64 "hspace" val data DOMHTMLImageElementHspacePropertyInfo instance AttrInfo DOMHTMLImageElementHspacePropertyInfo where type AttrAllowedOps DOMHTMLImageElementHspacePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLImageElementHspacePropertyInfo = (~) Int64 type AttrBaseTypeConstraint DOMHTMLImageElementHspacePropertyInfo = DOMHTMLImageElementK type AttrGetType DOMHTMLImageElementHspacePropertyInfo = Int64 type AttrLabel DOMHTMLImageElementHspacePropertyInfo = "DOMHTMLImageElement::hspace" attrGet _ = getDOMHTMLImageElementHspace attrSet _ = setDOMHTMLImageElementHspace attrConstruct _ = constructDOMHTMLImageElementHspace -- VVV Prop "is-map" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLImageElementIsMap :: (MonadIO m, DOMHTMLImageElementK o) => o -> m Bool getDOMHTMLImageElementIsMap obj = liftIO $ getObjectPropertyBool obj "is-map" setDOMHTMLImageElementIsMap :: (MonadIO m, DOMHTMLImageElementK o) => o -> Bool -> m () setDOMHTMLImageElementIsMap obj val = liftIO $ setObjectPropertyBool obj "is-map" val constructDOMHTMLImageElementIsMap :: Bool -> IO ([Char], GValue) constructDOMHTMLImageElementIsMap val = constructObjectPropertyBool "is-map" val data DOMHTMLImageElementIsMapPropertyInfo instance AttrInfo DOMHTMLImageElementIsMapPropertyInfo where type AttrAllowedOps DOMHTMLImageElementIsMapPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLImageElementIsMapPropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLImageElementIsMapPropertyInfo = DOMHTMLImageElementK type AttrGetType DOMHTMLImageElementIsMapPropertyInfo = Bool type AttrLabel DOMHTMLImageElementIsMapPropertyInfo = "DOMHTMLImageElement::is-map" attrGet _ = getDOMHTMLImageElementIsMap attrSet _ = setDOMHTMLImageElementIsMap attrConstruct _ = constructDOMHTMLImageElementIsMap -- VVV Prop "long-desc" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLImageElementLongDesc :: (MonadIO m, DOMHTMLImageElementK o) => o -> m T.Text getDOMHTMLImageElementLongDesc obj = liftIO $ getObjectPropertyString obj "long-desc" setDOMHTMLImageElementLongDesc :: (MonadIO m, DOMHTMLImageElementK o) => o -> T.Text -> m () setDOMHTMLImageElementLongDesc obj val = liftIO $ setObjectPropertyString obj "long-desc" val constructDOMHTMLImageElementLongDesc :: T.Text -> IO ([Char], GValue) constructDOMHTMLImageElementLongDesc val = constructObjectPropertyString "long-desc" val data DOMHTMLImageElementLongDescPropertyInfo instance AttrInfo DOMHTMLImageElementLongDescPropertyInfo where type AttrAllowedOps DOMHTMLImageElementLongDescPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLImageElementLongDescPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLImageElementLongDescPropertyInfo = DOMHTMLImageElementK type AttrGetType DOMHTMLImageElementLongDescPropertyInfo = T.Text type AttrLabel DOMHTMLImageElementLongDescPropertyInfo = "DOMHTMLImageElement::long-desc" attrGet _ = getDOMHTMLImageElementLongDesc attrSet _ = setDOMHTMLImageElementLongDesc attrConstruct _ = constructDOMHTMLImageElementLongDesc -- VVV Prop "lowsrc" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLImageElementLowsrc :: (MonadIO m, DOMHTMLImageElementK o) => o -> m T.Text getDOMHTMLImageElementLowsrc obj = liftIO $ getObjectPropertyString obj "lowsrc" setDOMHTMLImageElementLowsrc :: (MonadIO m, DOMHTMLImageElementK o) => o -> T.Text -> m () setDOMHTMLImageElementLowsrc obj val = liftIO $ setObjectPropertyString obj "lowsrc" val constructDOMHTMLImageElementLowsrc :: T.Text -> IO ([Char], GValue) constructDOMHTMLImageElementLowsrc val = constructObjectPropertyString "lowsrc" val data DOMHTMLImageElementLowsrcPropertyInfo instance AttrInfo DOMHTMLImageElementLowsrcPropertyInfo where type AttrAllowedOps DOMHTMLImageElementLowsrcPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLImageElementLowsrcPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLImageElementLowsrcPropertyInfo = DOMHTMLImageElementK type AttrGetType DOMHTMLImageElementLowsrcPropertyInfo = T.Text type AttrLabel DOMHTMLImageElementLowsrcPropertyInfo = "DOMHTMLImageElement::lowsrc" attrGet _ = getDOMHTMLImageElementLowsrc attrSet _ = setDOMHTMLImageElementLowsrc attrConstruct _ = constructDOMHTMLImageElementLowsrc -- VVV Prop "name" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLImageElementName :: (MonadIO m, DOMHTMLImageElementK o) => o -> m T.Text getDOMHTMLImageElementName obj = liftIO $ getObjectPropertyString obj "name" setDOMHTMLImageElementName :: (MonadIO m, DOMHTMLImageElementK o) => o -> T.Text -> m () setDOMHTMLImageElementName obj val = liftIO $ setObjectPropertyString obj "name" val constructDOMHTMLImageElementName :: T.Text -> IO ([Char], GValue) constructDOMHTMLImageElementName val = constructObjectPropertyString "name" val data DOMHTMLImageElementNamePropertyInfo instance AttrInfo DOMHTMLImageElementNamePropertyInfo where type AttrAllowedOps DOMHTMLImageElementNamePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLImageElementNamePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLImageElementNamePropertyInfo = DOMHTMLImageElementK type AttrGetType DOMHTMLImageElementNamePropertyInfo = T.Text type AttrLabel DOMHTMLImageElementNamePropertyInfo = "DOMHTMLImageElement::name" attrGet _ = getDOMHTMLImageElementName attrSet _ = setDOMHTMLImageElementName attrConstruct _ = constructDOMHTMLImageElementName -- VVV Prop "natural-height" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMHTMLImageElementNaturalHeight :: (MonadIO m, DOMHTMLImageElementK o) => o -> m Int64 getDOMHTMLImageElementNaturalHeight obj = liftIO $ getObjectPropertyInt64 obj "natural-height" data DOMHTMLImageElementNaturalHeightPropertyInfo instance AttrInfo DOMHTMLImageElementNaturalHeightPropertyInfo where type AttrAllowedOps DOMHTMLImageElementNaturalHeightPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLImageElementNaturalHeightPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLImageElementNaturalHeightPropertyInfo = DOMHTMLImageElementK type AttrGetType DOMHTMLImageElementNaturalHeightPropertyInfo = Int64 type AttrLabel DOMHTMLImageElementNaturalHeightPropertyInfo = "DOMHTMLImageElement::natural-height" attrGet _ = getDOMHTMLImageElementNaturalHeight attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "natural-width" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMHTMLImageElementNaturalWidth :: (MonadIO m, DOMHTMLImageElementK o) => o -> m Int64 getDOMHTMLImageElementNaturalWidth obj = liftIO $ getObjectPropertyInt64 obj "natural-width" data DOMHTMLImageElementNaturalWidthPropertyInfo instance AttrInfo DOMHTMLImageElementNaturalWidthPropertyInfo where type AttrAllowedOps DOMHTMLImageElementNaturalWidthPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLImageElementNaturalWidthPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLImageElementNaturalWidthPropertyInfo = DOMHTMLImageElementK type AttrGetType DOMHTMLImageElementNaturalWidthPropertyInfo = Int64 type AttrLabel DOMHTMLImageElementNaturalWidthPropertyInfo = "DOMHTMLImageElement::natural-width" attrGet _ = getDOMHTMLImageElementNaturalWidth attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "src" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLImageElementSrc :: (MonadIO m, DOMHTMLImageElementK o) => o -> m T.Text getDOMHTMLImageElementSrc obj = liftIO $ getObjectPropertyString obj "src" setDOMHTMLImageElementSrc :: (MonadIO m, DOMHTMLImageElementK o) => o -> T.Text -> m () setDOMHTMLImageElementSrc obj val = liftIO $ setObjectPropertyString obj "src" val constructDOMHTMLImageElementSrc :: T.Text -> IO ([Char], GValue) constructDOMHTMLImageElementSrc val = constructObjectPropertyString "src" val data DOMHTMLImageElementSrcPropertyInfo instance AttrInfo DOMHTMLImageElementSrcPropertyInfo where type AttrAllowedOps DOMHTMLImageElementSrcPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLImageElementSrcPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLImageElementSrcPropertyInfo = DOMHTMLImageElementK type AttrGetType DOMHTMLImageElementSrcPropertyInfo = T.Text type AttrLabel DOMHTMLImageElementSrcPropertyInfo = "DOMHTMLImageElement::src" attrGet _ = getDOMHTMLImageElementSrc attrSet _ = setDOMHTMLImageElementSrc attrConstruct _ = constructDOMHTMLImageElementSrc -- VVV Prop "srcset" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLImageElementSrcset :: (MonadIO m, DOMHTMLImageElementK o) => o -> m T.Text getDOMHTMLImageElementSrcset obj = liftIO $ getObjectPropertyString obj "srcset" setDOMHTMLImageElementSrcset :: (MonadIO m, DOMHTMLImageElementK o) => o -> T.Text -> m () setDOMHTMLImageElementSrcset obj val = liftIO $ setObjectPropertyString obj "srcset" val constructDOMHTMLImageElementSrcset :: T.Text -> IO ([Char], GValue) constructDOMHTMLImageElementSrcset val = constructObjectPropertyString "srcset" val data DOMHTMLImageElementSrcsetPropertyInfo instance AttrInfo DOMHTMLImageElementSrcsetPropertyInfo where type AttrAllowedOps DOMHTMLImageElementSrcsetPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLImageElementSrcsetPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLImageElementSrcsetPropertyInfo = DOMHTMLImageElementK type AttrGetType DOMHTMLImageElementSrcsetPropertyInfo = T.Text type AttrLabel DOMHTMLImageElementSrcsetPropertyInfo = "DOMHTMLImageElement::srcset" attrGet _ = getDOMHTMLImageElementSrcset attrSet _ = setDOMHTMLImageElementSrcset attrConstruct _ = constructDOMHTMLImageElementSrcset -- VVV Prop "use-map" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLImageElementUseMap :: (MonadIO m, DOMHTMLImageElementK o) => o -> m T.Text getDOMHTMLImageElementUseMap obj = liftIO $ getObjectPropertyString obj "use-map" setDOMHTMLImageElementUseMap :: (MonadIO m, DOMHTMLImageElementK o) => o -> T.Text -> m () setDOMHTMLImageElementUseMap obj val = liftIO $ setObjectPropertyString obj "use-map" val constructDOMHTMLImageElementUseMap :: T.Text -> IO ([Char], GValue) constructDOMHTMLImageElementUseMap val = constructObjectPropertyString "use-map" val data DOMHTMLImageElementUseMapPropertyInfo instance AttrInfo DOMHTMLImageElementUseMapPropertyInfo where type AttrAllowedOps DOMHTMLImageElementUseMapPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLImageElementUseMapPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLImageElementUseMapPropertyInfo = DOMHTMLImageElementK type AttrGetType DOMHTMLImageElementUseMapPropertyInfo = T.Text type AttrLabel DOMHTMLImageElementUseMapPropertyInfo = "DOMHTMLImageElement::use-map" attrGet _ = getDOMHTMLImageElementUseMap attrSet _ = setDOMHTMLImageElementUseMap attrConstruct _ = constructDOMHTMLImageElementUseMap -- VVV Prop "vspace" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLImageElementVspace :: (MonadIO m, DOMHTMLImageElementK o) => o -> m Int64 getDOMHTMLImageElementVspace obj = liftIO $ getObjectPropertyInt64 obj "vspace" setDOMHTMLImageElementVspace :: (MonadIO m, DOMHTMLImageElementK o) => o -> Int64 -> m () setDOMHTMLImageElementVspace obj val = liftIO $ setObjectPropertyInt64 obj "vspace" val constructDOMHTMLImageElementVspace :: Int64 -> IO ([Char], GValue) constructDOMHTMLImageElementVspace val = constructObjectPropertyInt64 "vspace" val data DOMHTMLImageElementVspacePropertyInfo instance AttrInfo DOMHTMLImageElementVspacePropertyInfo where type AttrAllowedOps DOMHTMLImageElementVspacePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLImageElementVspacePropertyInfo = (~) Int64 type AttrBaseTypeConstraint DOMHTMLImageElementVspacePropertyInfo = DOMHTMLImageElementK type AttrGetType DOMHTMLImageElementVspacePropertyInfo = Int64 type AttrLabel DOMHTMLImageElementVspacePropertyInfo = "DOMHTMLImageElement::vspace" attrGet _ = getDOMHTMLImageElementVspace attrSet _ = setDOMHTMLImageElementVspace attrConstruct _ = constructDOMHTMLImageElementVspace -- VVV Prop "width" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLImageElementWidth :: (MonadIO m, DOMHTMLImageElementK o) => o -> m Int64 getDOMHTMLImageElementWidth obj = liftIO $ getObjectPropertyInt64 obj "width" setDOMHTMLImageElementWidth :: (MonadIO m, DOMHTMLImageElementK o) => o -> Int64 -> m () setDOMHTMLImageElementWidth obj val = liftIO $ setObjectPropertyInt64 obj "width" val constructDOMHTMLImageElementWidth :: Int64 -> IO ([Char], GValue) constructDOMHTMLImageElementWidth val = constructObjectPropertyInt64 "width" val data DOMHTMLImageElementWidthPropertyInfo instance AttrInfo DOMHTMLImageElementWidthPropertyInfo where type AttrAllowedOps DOMHTMLImageElementWidthPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLImageElementWidthPropertyInfo = (~) Int64 type AttrBaseTypeConstraint DOMHTMLImageElementWidthPropertyInfo = DOMHTMLImageElementK type AttrGetType DOMHTMLImageElementWidthPropertyInfo = Int64 type AttrLabel DOMHTMLImageElementWidthPropertyInfo = "DOMHTMLImageElement::width" attrGet _ = getDOMHTMLImageElementWidth attrSet _ = setDOMHTMLImageElementWidth attrConstruct _ = constructDOMHTMLImageElementWidth -- VVV Prop "x" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMHTMLImageElementX :: (MonadIO m, DOMHTMLImageElementK o) => o -> m Int64 getDOMHTMLImageElementX obj = liftIO $ getObjectPropertyInt64 obj "x" data DOMHTMLImageElementXPropertyInfo instance AttrInfo DOMHTMLImageElementXPropertyInfo where type AttrAllowedOps DOMHTMLImageElementXPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLImageElementXPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLImageElementXPropertyInfo = DOMHTMLImageElementK type AttrGetType DOMHTMLImageElementXPropertyInfo = Int64 type AttrLabel DOMHTMLImageElementXPropertyInfo = "DOMHTMLImageElement::x" attrGet _ = getDOMHTMLImageElementX attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "y" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMHTMLImageElementY :: (MonadIO m, DOMHTMLImageElementK o) => o -> m Int64 getDOMHTMLImageElementY obj = liftIO $ getObjectPropertyInt64 obj "y" data DOMHTMLImageElementYPropertyInfo instance AttrInfo DOMHTMLImageElementYPropertyInfo where type AttrAllowedOps DOMHTMLImageElementYPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLImageElementYPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLImageElementYPropertyInfo = DOMHTMLImageElementK type AttrGetType DOMHTMLImageElementYPropertyInfo = Int64 type AttrLabel DOMHTMLImageElementYPropertyInfo = "DOMHTMLImageElement::y" attrGet _ = getDOMHTMLImageElementY attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMHTMLImageElement = '[ '("access-key", DOMHTMLElementAccessKeyPropertyInfo), '("align", DOMHTMLImageElementAlignPropertyInfo), '("alt", DOMHTMLImageElementAltPropertyInfo), '("attributes", DOMElementAttributesPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("border", DOMHTMLImageElementBorderPropertyInfo), '("child-element-count", DOMElementChildElementCountPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("children", DOMHTMLElementChildrenPropertyInfo), '("class-list", DOMElementClassListPropertyInfo), '("class-name", DOMElementClassNamePropertyInfo), '("client-height", DOMElementClientHeightPropertyInfo), '("client-left", DOMElementClientLeftPropertyInfo), '("client-top", DOMElementClientTopPropertyInfo), '("client-width", DOMElementClientWidthPropertyInfo), '("complete", DOMHTMLImageElementCompletePropertyInfo), '("content-editable", DOMHTMLElementContentEditablePropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("cross-origin", DOMHTMLImageElementCrossOriginPropertyInfo), '("dir", DOMHTMLElementDirPropertyInfo), '("draggable", DOMHTMLElementDraggablePropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("first-element-child", DOMElementFirstElementChildPropertyInfo), '("height", DOMHTMLImageElementHeightPropertyInfo), '("hidden", DOMHTMLElementHiddenPropertyInfo), '("hspace", DOMHTMLImageElementHspacePropertyInfo), '("id", DOMElementIdPropertyInfo), '("inner-html", DOMHTMLElementInnerHtmlPropertyInfo), '("inner-text", DOMHTMLElementInnerTextPropertyInfo), '("is-content-editable", DOMHTMLElementIsContentEditablePropertyInfo), '("is-map", DOMHTMLImageElementIsMapPropertyInfo), '("lang", DOMHTMLElementLangPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-element-child", DOMElementLastElementChildPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("long-desc", DOMHTMLImageElementLongDescPropertyInfo), '("lowsrc", DOMHTMLImageElementLowsrcPropertyInfo), '("name", DOMHTMLImageElementNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("natural-height", DOMHTMLImageElementNaturalHeightPropertyInfo), '("natural-width", DOMHTMLImageElementNaturalWidthPropertyInfo), '("next-element-sibling", DOMElementNextElementSiblingPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("offset-height", DOMElementOffsetHeightPropertyInfo), '("offset-left", DOMElementOffsetLeftPropertyInfo), '("offset-parent", DOMElementOffsetParentPropertyInfo), '("offset-top", DOMElementOffsetTopPropertyInfo), '("offset-width", DOMElementOffsetWidthPropertyInfo), '("outer-html", DOMHTMLElementOuterHtmlPropertyInfo), '("outer-text", DOMHTMLElementOuterTextPropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-element-sibling", DOMElementPreviousElementSiblingPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("scroll-height", DOMElementScrollHeightPropertyInfo), '("scroll-left", DOMElementScrollLeftPropertyInfo), '("scroll-top", DOMElementScrollTopPropertyInfo), '("scroll-width", DOMElementScrollWidthPropertyInfo), '("spellcheck", DOMHTMLElementSpellcheckPropertyInfo), '("src", DOMHTMLImageElementSrcPropertyInfo), '("srcset", DOMHTMLImageElementSrcsetPropertyInfo), '("style", DOMElementStylePropertyInfo), '("tab-index", DOMHTMLElementTabIndexPropertyInfo), '("tag-name", DOMElementTagNamePropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("title", DOMHTMLElementTitlePropertyInfo), '("translate", DOMHTMLElementTranslatePropertyInfo), '("use-map", DOMHTMLImageElementUseMapPropertyInfo), '("vspace", DOMHTMLImageElementVspacePropertyInfo), '("webkit-region-overset", DOMElementWebkitRegionOversetPropertyInfo), '("webkitdropzone", DOMHTMLElementWebkitdropzonePropertyInfo), '("width", DOMHTMLImageElementWidthPropertyInfo), '("x", DOMHTMLImageElementXPropertyInfo), '("y", DOMHTMLImageElementYPropertyInfo)] -- VVV Prop "accept" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLInputElementAccept :: (MonadIO m, DOMHTMLInputElementK o) => o -> m T.Text getDOMHTMLInputElementAccept obj = liftIO $ getObjectPropertyString obj "accept" setDOMHTMLInputElementAccept :: (MonadIO m, DOMHTMLInputElementK o) => o -> T.Text -> m () setDOMHTMLInputElementAccept obj val = liftIO $ setObjectPropertyString obj "accept" val constructDOMHTMLInputElementAccept :: T.Text -> IO ([Char], GValue) constructDOMHTMLInputElementAccept val = constructObjectPropertyString "accept" val data DOMHTMLInputElementAcceptPropertyInfo instance AttrInfo DOMHTMLInputElementAcceptPropertyInfo where type AttrAllowedOps DOMHTMLInputElementAcceptPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLInputElementAcceptPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLInputElementAcceptPropertyInfo = DOMHTMLInputElementK type AttrGetType DOMHTMLInputElementAcceptPropertyInfo = T.Text type AttrLabel DOMHTMLInputElementAcceptPropertyInfo = "DOMHTMLInputElement::accept" attrGet _ = getDOMHTMLInputElementAccept attrSet _ = setDOMHTMLInputElementAccept attrConstruct _ = constructDOMHTMLInputElementAccept -- VVV Prop "align" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLInputElementAlign :: (MonadIO m, DOMHTMLInputElementK o) => o -> m T.Text getDOMHTMLInputElementAlign obj = liftIO $ getObjectPropertyString obj "align" setDOMHTMLInputElementAlign :: (MonadIO m, DOMHTMLInputElementK o) => o -> T.Text -> m () setDOMHTMLInputElementAlign obj val = liftIO $ setObjectPropertyString obj "align" val constructDOMHTMLInputElementAlign :: T.Text -> IO ([Char], GValue) constructDOMHTMLInputElementAlign val = constructObjectPropertyString "align" val data DOMHTMLInputElementAlignPropertyInfo instance AttrInfo DOMHTMLInputElementAlignPropertyInfo where type AttrAllowedOps DOMHTMLInputElementAlignPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLInputElementAlignPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLInputElementAlignPropertyInfo = DOMHTMLInputElementK type AttrGetType DOMHTMLInputElementAlignPropertyInfo = T.Text type AttrLabel DOMHTMLInputElementAlignPropertyInfo = "DOMHTMLInputElement::align" attrGet _ = getDOMHTMLInputElementAlign attrSet _ = setDOMHTMLInputElementAlign attrConstruct _ = constructDOMHTMLInputElementAlign -- VVV Prop "alt" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLInputElementAlt :: (MonadIO m, DOMHTMLInputElementK o) => o -> m T.Text getDOMHTMLInputElementAlt obj = liftIO $ getObjectPropertyString obj "alt" setDOMHTMLInputElementAlt :: (MonadIO m, DOMHTMLInputElementK o) => o -> T.Text -> m () setDOMHTMLInputElementAlt obj val = liftIO $ setObjectPropertyString obj "alt" val constructDOMHTMLInputElementAlt :: T.Text -> IO ([Char], GValue) constructDOMHTMLInputElementAlt val = constructObjectPropertyString "alt" val data DOMHTMLInputElementAltPropertyInfo instance AttrInfo DOMHTMLInputElementAltPropertyInfo where type AttrAllowedOps DOMHTMLInputElementAltPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLInputElementAltPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLInputElementAltPropertyInfo = DOMHTMLInputElementK type AttrGetType DOMHTMLInputElementAltPropertyInfo = T.Text type AttrLabel DOMHTMLInputElementAltPropertyInfo = "DOMHTMLInputElement::alt" attrGet _ = getDOMHTMLInputElementAlt attrSet _ = setDOMHTMLInputElementAlt attrConstruct _ = constructDOMHTMLInputElementAlt -- VVV Prop "autocapitalize" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLInputElementAutocapitalize :: (MonadIO m, DOMHTMLInputElementK o) => o -> m T.Text getDOMHTMLInputElementAutocapitalize obj = liftIO $ getObjectPropertyString obj "autocapitalize" setDOMHTMLInputElementAutocapitalize :: (MonadIO m, DOMHTMLInputElementK o) => o -> T.Text -> m () setDOMHTMLInputElementAutocapitalize obj val = liftIO $ setObjectPropertyString obj "autocapitalize" val constructDOMHTMLInputElementAutocapitalize :: T.Text -> IO ([Char], GValue) constructDOMHTMLInputElementAutocapitalize val = constructObjectPropertyString "autocapitalize" val data DOMHTMLInputElementAutocapitalizePropertyInfo instance AttrInfo DOMHTMLInputElementAutocapitalizePropertyInfo where type AttrAllowedOps DOMHTMLInputElementAutocapitalizePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLInputElementAutocapitalizePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLInputElementAutocapitalizePropertyInfo = DOMHTMLInputElementK type AttrGetType DOMHTMLInputElementAutocapitalizePropertyInfo = T.Text type AttrLabel DOMHTMLInputElementAutocapitalizePropertyInfo = "DOMHTMLInputElement::autocapitalize" attrGet _ = getDOMHTMLInputElementAutocapitalize attrSet _ = setDOMHTMLInputElementAutocapitalize attrConstruct _ = constructDOMHTMLInputElementAutocapitalize -- VVV Prop "autocomplete" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLInputElementAutocomplete :: (MonadIO m, DOMHTMLInputElementK o) => o -> m T.Text getDOMHTMLInputElementAutocomplete obj = liftIO $ getObjectPropertyString obj "autocomplete" setDOMHTMLInputElementAutocomplete :: (MonadIO m, DOMHTMLInputElementK o) => o -> T.Text -> m () setDOMHTMLInputElementAutocomplete obj val = liftIO $ setObjectPropertyString obj "autocomplete" val constructDOMHTMLInputElementAutocomplete :: T.Text -> IO ([Char], GValue) constructDOMHTMLInputElementAutocomplete val = constructObjectPropertyString "autocomplete" val data DOMHTMLInputElementAutocompletePropertyInfo instance AttrInfo DOMHTMLInputElementAutocompletePropertyInfo where type AttrAllowedOps DOMHTMLInputElementAutocompletePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLInputElementAutocompletePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLInputElementAutocompletePropertyInfo = DOMHTMLInputElementK type AttrGetType DOMHTMLInputElementAutocompletePropertyInfo = T.Text type AttrLabel DOMHTMLInputElementAutocompletePropertyInfo = "DOMHTMLInputElement::autocomplete" attrGet _ = getDOMHTMLInputElementAutocomplete attrSet _ = setDOMHTMLInputElementAutocomplete attrConstruct _ = constructDOMHTMLInputElementAutocomplete -- VVV Prop "autocorrect" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLInputElementAutocorrect :: (MonadIO m, DOMHTMLInputElementK o) => o -> m Bool getDOMHTMLInputElementAutocorrect obj = liftIO $ getObjectPropertyBool obj "autocorrect" setDOMHTMLInputElementAutocorrect :: (MonadIO m, DOMHTMLInputElementK o) => o -> Bool -> m () setDOMHTMLInputElementAutocorrect obj val = liftIO $ setObjectPropertyBool obj "autocorrect" val constructDOMHTMLInputElementAutocorrect :: Bool -> IO ([Char], GValue) constructDOMHTMLInputElementAutocorrect val = constructObjectPropertyBool "autocorrect" val data DOMHTMLInputElementAutocorrectPropertyInfo instance AttrInfo DOMHTMLInputElementAutocorrectPropertyInfo where type AttrAllowedOps DOMHTMLInputElementAutocorrectPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLInputElementAutocorrectPropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLInputElementAutocorrectPropertyInfo = DOMHTMLInputElementK type AttrGetType DOMHTMLInputElementAutocorrectPropertyInfo = Bool type AttrLabel DOMHTMLInputElementAutocorrectPropertyInfo = "DOMHTMLInputElement::autocorrect" attrGet _ = getDOMHTMLInputElementAutocorrect attrSet _ = setDOMHTMLInputElementAutocorrect attrConstruct _ = constructDOMHTMLInputElementAutocorrect -- VVV Prop "autofocus" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLInputElementAutofocus :: (MonadIO m, DOMHTMLInputElementK o) => o -> m Bool getDOMHTMLInputElementAutofocus obj = liftIO $ getObjectPropertyBool obj "autofocus" setDOMHTMLInputElementAutofocus :: (MonadIO m, DOMHTMLInputElementK o) => o -> Bool -> m () setDOMHTMLInputElementAutofocus obj val = liftIO $ setObjectPropertyBool obj "autofocus" val constructDOMHTMLInputElementAutofocus :: Bool -> IO ([Char], GValue) constructDOMHTMLInputElementAutofocus val = constructObjectPropertyBool "autofocus" val data DOMHTMLInputElementAutofocusPropertyInfo instance AttrInfo DOMHTMLInputElementAutofocusPropertyInfo where type AttrAllowedOps DOMHTMLInputElementAutofocusPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLInputElementAutofocusPropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLInputElementAutofocusPropertyInfo = DOMHTMLInputElementK type AttrGetType DOMHTMLInputElementAutofocusPropertyInfo = Bool type AttrLabel DOMHTMLInputElementAutofocusPropertyInfo = "DOMHTMLInputElement::autofocus" attrGet _ = getDOMHTMLInputElementAutofocus attrSet _ = setDOMHTMLInputElementAutofocus attrConstruct _ = constructDOMHTMLInputElementAutofocus -- VVV Prop "capture" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLInputElementCapture :: (MonadIO m, DOMHTMLInputElementK o) => o -> m T.Text getDOMHTMLInputElementCapture obj = liftIO $ getObjectPropertyString obj "capture" setDOMHTMLInputElementCapture :: (MonadIO m, DOMHTMLInputElementK o) => o -> T.Text -> m () setDOMHTMLInputElementCapture obj val = liftIO $ setObjectPropertyString obj "capture" val constructDOMHTMLInputElementCapture :: T.Text -> IO ([Char], GValue) constructDOMHTMLInputElementCapture val = constructObjectPropertyString "capture" val data DOMHTMLInputElementCapturePropertyInfo instance AttrInfo DOMHTMLInputElementCapturePropertyInfo where type AttrAllowedOps DOMHTMLInputElementCapturePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLInputElementCapturePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLInputElementCapturePropertyInfo = DOMHTMLInputElementK type AttrGetType DOMHTMLInputElementCapturePropertyInfo = T.Text type AttrLabel DOMHTMLInputElementCapturePropertyInfo = "DOMHTMLInputElement::capture" attrGet _ = getDOMHTMLInputElementCapture attrSet _ = setDOMHTMLInputElementCapture attrConstruct _ = constructDOMHTMLInputElementCapture -- VVV Prop "checked" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLInputElementChecked :: (MonadIO m, DOMHTMLInputElementK o) => o -> m Bool getDOMHTMLInputElementChecked obj = liftIO $ getObjectPropertyBool obj "checked" setDOMHTMLInputElementChecked :: (MonadIO m, DOMHTMLInputElementK o) => o -> Bool -> m () setDOMHTMLInputElementChecked obj val = liftIO $ setObjectPropertyBool obj "checked" val constructDOMHTMLInputElementChecked :: Bool -> IO ([Char], GValue) constructDOMHTMLInputElementChecked val = constructObjectPropertyBool "checked" val data DOMHTMLInputElementCheckedPropertyInfo instance AttrInfo DOMHTMLInputElementCheckedPropertyInfo where type AttrAllowedOps DOMHTMLInputElementCheckedPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLInputElementCheckedPropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLInputElementCheckedPropertyInfo = DOMHTMLInputElementK type AttrGetType DOMHTMLInputElementCheckedPropertyInfo = Bool type AttrLabel DOMHTMLInputElementCheckedPropertyInfo = "DOMHTMLInputElement::checked" attrGet _ = getDOMHTMLInputElementChecked attrSet _ = setDOMHTMLInputElementChecked attrConstruct _ = constructDOMHTMLInputElementChecked -- VVV Prop "default-checked" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLInputElementDefaultChecked :: (MonadIO m, DOMHTMLInputElementK o) => o -> m Bool getDOMHTMLInputElementDefaultChecked obj = liftIO $ getObjectPropertyBool obj "default-checked" setDOMHTMLInputElementDefaultChecked :: (MonadIO m, DOMHTMLInputElementK o) => o -> Bool -> m () setDOMHTMLInputElementDefaultChecked obj val = liftIO $ setObjectPropertyBool obj "default-checked" val constructDOMHTMLInputElementDefaultChecked :: Bool -> IO ([Char], GValue) constructDOMHTMLInputElementDefaultChecked val = constructObjectPropertyBool "default-checked" val data DOMHTMLInputElementDefaultCheckedPropertyInfo instance AttrInfo DOMHTMLInputElementDefaultCheckedPropertyInfo where type AttrAllowedOps DOMHTMLInputElementDefaultCheckedPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLInputElementDefaultCheckedPropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLInputElementDefaultCheckedPropertyInfo = DOMHTMLInputElementK type AttrGetType DOMHTMLInputElementDefaultCheckedPropertyInfo = Bool type AttrLabel DOMHTMLInputElementDefaultCheckedPropertyInfo = "DOMHTMLInputElement::default-checked" attrGet _ = getDOMHTMLInputElementDefaultChecked attrSet _ = setDOMHTMLInputElementDefaultChecked attrConstruct _ = constructDOMHTMLInputElementDefaultChecked -- VVV Prop "default-value" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLInputElementDefaultValue :: (MonadIO m, DOMHTMLInputElementK o) => o -> m T.Text getDOMHTMLInputElementDefaultValue obj = liftIO $ getObjectPropertyString obj "default-value" setDOMHTMLInputElementDefaultValue :: (MonadIO m, DOMHTMLInputElementK o) => o -> T.Text -> m () setDOMHTMLInputElementDefaultValue obj val = liftIO $ setObjectPropertyString obj "default-value" val constructDOMHTMLInputElementDefaultValue :: T.Text -> IO ([Char], GValue) constructDOMHTMLInputElementDefaultValue val = constructObjectPropertyString "default-value" val data DOMHTMLInputElementDefaultValuePropertyInfo instance AttrInfo DOMHTMLInputElementDefaultValuePropertyInfo where type AttrAllowedOps DOMHTMLInputElementDefaultValuePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLInputElementDefaultValuePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLInputElementDefaultValuePropertyInfo = DOMHTMLInputElementK type AttrGetType DOMHTMLInputElementDefaultValuePropertyInfo = T.Text type AttrLabel DOMHTMLInputElementDefaultValuePropertyInfo = "DOMHTMLInputElement::default-value" attrGet _ = getDOMHTMLInputElementDefaultValue attrSet _ = setDOMHTMLInputElementDefaultValue attrConstruct _ = constructDOMHTMLInputElementDefaultValue -- VVV Prop "dir-name" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLInputElementDirName :: (MonadIO m, DOMHTMLInputElementK o) => o -> m T.Text getDOMHTMLInputElementDirName obj = liftIO $ getObjectPropertyString obj "dir-name" setDOMHTMLInputElementDirName :: (MonadIO m, DOMHTMLInputElementK o) => o -> T.Text -> m () setDOMHTMLInputElementDirName obj val = liftIO $ setObjectPropertyString obj "dir-name" val constructDOMHTMLInputElementDirName :: T.Text -> IO ([Char], GValue) constructDOMHTMLInputElementDirName val = constructObjectPropertyString "dir-name" val data DOMHTMLInputElementDirNamePropertyInfo instance AttrInfo DOMHTMLInputElementDirNamePropertyInfo where type AttrAllowedOps DOMHTMLInputElementDirNamePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLInputElementDirNamePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLInputElementDirNamePropertyInfo = DOMHTMLInputElementK type AttrGetType DOMHTMLInputElementDirNamePropertyInfo = T.Text type AttrLabel DOMHTMLInputElementDirNamePropertyInfo = "DOMHTMLInputElement::dir-name" attrGet _ = getDOMHTMLInputElementDirName attrSet _ = setDOMHTMLInputElementDirName attrConstruct _ = constructDOMHTMLInputElementDirName -- VVV Prop "disabled" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLInputElementDisabled :: (MonadIO m, DOMHTMLInputElementK o) => o -> m Bool getDOMHTMLInputElementDisabled obj = liftIO $ getObjectPropertyBool obj "disabled" setDOMHTMLInputElementDisabled :: (MonadIO m, DOMHTMLInputElementK o) => o -> Bool -> m () setDOMHTMLInputElementDisabled obj val = liftIO $ setObjectPropertyBool obj "disabled" val constructDOMHTMLInputElementDisabled :: Bool -> IO ([Char], GValue) constructDOMHTMLInputElementDisabled val = constructObjectPropertyBool "disabled" val data DOMHTMLInputElementDisabledPropertyInfo instance AttrInfo DOMHTMLInputElementDisabledPropertyInfo where type AttrAllowedOps DOMHTMLInputElementDisabledPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLInputElementDisabledPropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLInputElementDisabledPropertyInfo = DOMHTMLInputElementK type AttrGetType DOMHTMLInputElementDisabledPropertyInfo = Bool type AttrLabel DOMHTMLInputElementDisabledPropertyInfo = "DOMHTMLInputElement::disabled" attrGet _ = getDOMHTMLInputElementDisabled attrSet _ = setDOMHTMLInputElementDisabled attrConstruct _ = constructDOMHTMLInputElementDisabled -- VVV Prop "files" -- Type: TInterface "WebKit" "DOMFileList" -- Flags: [PropertyReadable] getDOMHTMLInputElementFiles :: (MonadIO m, DOMHTMLInputElementK o) => o -> m DOMFileList getDOMHTMLInputElementFiles obj = liftIO $ getObjectPropertyObject obj "files" DOMFileList data DOMHTMLInputElementFilesPropertyInfo instance AttrInfo DOMHTMLInputElementFilesPropertyInfo where type AttrAllowedOps DOMHTMLInputElementFilesPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLInputElementFilesPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLInputElementFilesPropertyInfo = DOMHTMLInputElementK type AttrGetType DOMHTMLInputElementFilesPropertyInfo = DOMFileList type AttrLabel DOMHTMLInputElementFilesPropertyInfo = "DOMHTMLInputElement::files" attrGet _ = getDOMHTMLInputElementFiles attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "form" -- Type: TInterface "WebKit" "DOMHTMLFormElement" -- Flags: [PropertyReadable] getDOMHTMLInputElementForm :: (MonadIO m, DOMHTMLInputElementK o) => o -> m DOMHTMLFormElement getDOMHTMLInputElementForm obj = liftIO $ getObjectPropertyObject obj "form" DOMHTMLFormElement data DOMHTMLInputElementFormPropertyInfo instance AttrInfo DOMHTMLInputElementFormPropertyInfo where type AttrAllowedOps DOMHTMLInputElementFormPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLInputElementFormPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLInputElementFormPropertyInfo = DOMHTMLInputElementK type AttrGetType DOMHTMLInputElementFormPropertyInfo = DOMHTMLFormElement type AttrLabel DOMHTMLInputElementFormPropertyInfo = "DOMHTMLInputElement::form" attrGet _ = getDOMHTMLInputElementForm attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "form-action" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLInputElementFormAction :: (MonadIO m, DOMHTMLInputElementK o) => o -> m T.Text getDOMHTMLInputElementFormAction obj = liftIO $ getObjectPropertyString obj "form-action" setDOMHTMLInputElementFormAction :: (MonadIO m, DOMHTMLInputElementK o) => o -> T.Text -> m () setDOMHTMLInputElementFormAction obj val = liftIO $ setObjectPropertyString obj "form-action" val constructDOMHTMLInputElementFormAction :: T.Text -> IO ([Char], GValue) constructDOMHTMLInputElementFormAction val = constructObjectPropertyString "form-action" val data DOMHTMLInputElementFormActionPropertyInfo instance AttrInfo DOMHTMLInputElementFormActionPropertyInfo where type AttrAllowedOps DOMHTMLInputElementFormActionPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLInputElementFormActionPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLInputElementFormActionPropertyInfo = DOMHTMLInputElementK type AttrGetType DOMHTMLInputElementFormActionPropertyInfo = T.Text type AttrLabel DOMHTMLInputElementFormActionPropertyInfo = "DOMHTMLInputElement::form-action" attrGet _ = getDOMHTMLInputElementFormAction attrSet _ = setDOMHTMLInputElementFormAction attrConstruct _ = constructDOMHTMLInputElementFormAction -- VVV Prop "form-enctype" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLInputElementFormEnctype :: (MonadIO m, DOMHTMLInputElementK o) => o -> m T.Text getDOMHTMLInputElementFormEnctype obj = liftIO $ getObjectPropertyString obj "form-enctype" setDOMHTMLInputElementFormEnctype :: (MonadIO m, DOMHTMLInputElementK o) => o -> T.Text -> m () setDOMHTMLInputElementFormEnctype obj val = liftIO $ setObjectPropertyString obj "form-enctype" val constructDOMHTMLInputElementFormEnctype :: T.Text -> IO ([Char], GValue) constructDOMHTMLInputElementFormEnctype val = constructObjectPropertyString "form-enctype" val data DOMHTMLInputElementFormEnctypePropertyInfo instance AttrInfo DOMHTMLInputElementFormEnctypePropertyInfo where type AttrAllowedOps DOMHTMLInputElementFormEnctypePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLInputElementFormEnctypePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLInputElementFormEnctypePropertyInfo = DOMHTMLInputElementK type AttrGetType DOMHTMLInputElementFormEnctypePropertyInfo = T.Text type AttrLabel DOMHTMLInputElementFormEnctypePropertyInfo = "DOMHTMLInputElement::form-enctype" attrGet _ = getDOMHTMLInputElementFormEnctype attrSet _ = setDOMHTMLInputElementFormEnctype attrConstruct _ = constructDOMHTMLInputElementFormEnctype -- VVV Prop "form-method" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLInputElementFormMethod :: (MonadIO m, DOMHTMLInputElementK o) => o -> m T.Text getDOMHTMLInputElementFormMethod obj = liftIO $ getObjectPropertyString obj "form-method" setDOMHTMLInputElementFormMethod :: (MonadIO m, DOMHTMLInputElementK o) => o -> T.Text -> m () setDOMHTMLInputElementFormMethod obj val = liftIO $ setObjectPropertyString obj "form-method" val constructDOMHTMLInputElementFormMethod :: T.Text -> IO ([Char], GValue) constructDOMHTMLInputElementFormMethod val = constructObjectPropertyString "form-method" val data DOMHTMLInputElementFormMethodPropertyInfo instance AttrInfo DOMHTMLInputElementFormMethodPropertyInfo where type AttrAllowedOps DOMHTMLInputElementFormMethodPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLInputElementFormMethodPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLInputElementFormMethodPropertyInfo = DOMHTMLInputElementK type AttrGetType DOMHTMLInputElementFormMethodPropertyInfo = T.Text type AttrLabel DOMHTMLInputElementFormMethodPropertyInfo = "DOMHTMLInputElement::form-method" attrGet _ = getDOMHTMLInputElementFormMethod attrSet _ = setDOMHTMLInputElementFormMethod attrConstruct _ = constructDOMHTMLInputElementFormMethod -- VVV Prop "form-no-validate" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLInputElementFormNoValidate :: (MonadIO m, DOMHTMLInputElementK o) => o -> m Bool getDOMHTMLInputElementFormNoValidate obj = liftIO $ getObjectPropertyBool obj "form-no-validate" setDOMHTMLInputElementFormNoValidate :: (MonadIO m, DOMHTMLInputElementK o) => o -> Bool -> m () setDOMHTMLInputElementFormNoValidate obj val = liftIO $ setObjectPropertyBool obj "form-no-validate" val constructDOMHTMLInputElementFormNoValidate :: Bool -> IO ([Char], GValue) constructDOMHTMLInputElementFormNoValidate val = constructObjectPropertyBool "form-no-validate" val data DOMHTMLInputElementFormNoValidatePropertyInfo instance AttrInfo DOMHTMLInputElementFormNoValidatePropertyInfo where type AttrAllowedOps DOMHTMLInputElementFormNoValidatePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLInputElementFormNoValidatePropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLInputElementFormNoValidatePropertyInfo = DOMHTMLInputElementK type AttrGetType DOMHTMLInputElementFormNoValidatePropertyInfo = Bool type AttrLabel DOMHTMLInputElementFormNoValidatePropertyInfo = "DOMHTMLInputElement::form-no-validate" attrGet _ = getDOMHTMLInputElementFormNoValidate attrSet _ = setDOMHTMLInputElementFormNoValidate attrConstruct _ = constructDOMHTMLInputElementFormNoValidate -- VVV Prop "form-target" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLInputElementFormTarget :: (MonadIO m, DOMHTMLInputElementK o) => o -> m T.Text getDOMHTMLInputElementFormTarget obj = liftIO $ getObjectPropertyString obj "form-target" setDOMHTMLInputElementFormTarget :: (MonadIO m, DOMHTMLInputElementK o) => o -> T.Text -> m () setDOMHTMLInputElementFormTarget obj val = liftIO $ setObjectPropertyString obj "form-target" val constructDOMHTMLInputElementFormTarget :: T.Text -> IO ([Char], GValue) constructDOMHTMLInputElementFormTarget val = constructObjectPropertyString "form-target" val data DOMHTMLInputElementFormTargetPropertyInfo instance AttrInfo DOMHTMLInputElementFormTargetPropertyInfo where type AttrAllowedOps DOMHTMLInputElementFormTargetPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLInputElementFormTargetPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLInputElementFormTargetPropertyInfo = DOMHTMLInputElementK type AttrGetType DOMHTMLInputElementFormTargetPropertyInfo = T.Text type AttrLabel DOMHTMLInputElementFormTargetPropertyInfo = "DOMHTMLInputElement::form-target" attrGet _ = getDOMHTMLInputElementFormTarget attrSet _ = setDOMHTMLInputElementFormTarget attrConstruct _ = constructDOMHTMLInputElementFormTarget -- VVV Prop "height" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLInputElementHeight :: (MonadIO m, DOMHTMLInputElementK o) => o -> m Word64 getDOMHTMLInputElementHeight obj = liftIO $ getObjectPropertyUInt64 obj "height" setDOMHTMLInputElementHeight :: (MonadIO m, DOMHTMLInputElementK o) => o -> Word64 -> m () setDOMHTMLInputElementHeight obj val = liftIO $ setObjectPropertyUInt64 obj "height" val constructDOMHTMLInputElementHeight :: Word64 -> IO ([Char], GValue) constructDOMHTMLInputElementHeight val = constructObjectPropertyUInt64 "height" val data DOMHTMLInputElementHeightPropertyInfo instance AttrInfo DOMHTMLInputElementHeightPropertyInfo where type AttrAllowedOps DOMHTMLInputElementHeightPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLInputElementHeightPropertyInfo = (~) Word64 type AttrBaseTypeConstraint DOMHTMLInputElementHeightPropertyInfo = DOMHTMLInputElementK type AttrGetType DOMHTMLInputElementHeightPropertyInfo = Word64 type AttrLabel DOMHTMLInputElementHeightPropertyInfo = "DOMHTMLInputElement::height" attrGet _ = getDOMHTMLInputElementHeight attrSet _ = setDOMHTMLInputElementHeight attrConstruct _ = constructDOMHTMLInputElementHeight -- VVV Prop "incremental" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLInputElementIncremental :: (MonadIO m, DOMHTMLInputElementK o) => o -> m Bool getDOMHTMLInputElementIncremental obj = liftIO $ getObjectPropertyBool obj "incremental" setDOMHTMLInputElementIncremental :: (MonadIO m, DOMHTMLInputElementK o) => o -> Bool -> m () setDOMHTMLInputElementIncremental obj val = liftIO $ setObjectPropertyBool obj "incremental" val constructDOMHTMLInputElementIncremental :: Bool -> IO ([Char], GValue) constructDOMHTMLInputElementIncremental val = constructObjectPropertyBool "incremental" val data DOMHTMLInputElementIncrementalPropertyInfo instance AttrInfo DOMHTMLInputElementIncrementalPropertyInfo where type AttrAllowedOps DOMHTMLInputElementIncrementalPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLInputElementIncrementalPropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLInputElementIncrementalPropertyInfo = DOMHTMLInputElementK type AttrGetType DOMHTMLInputElementIncrementalPropertyInfo = Bool type AttrLabel DOMHTMLInputElementIncrementalPropertyInfo = "DOMHTMLInputElement::incremental" attrGet _ = getDOMHTMLInputElementIncremental attrSet _ = setDOMHTMLInputElementIncremental attrConstruct _ = constructDOMHTMLInputElementIncremental -- VVV Prop "indeterminate" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLInputElementIndeterminate :: (MonadIO m, DOMHTMLInputElementK o) => o -> m Bool getDOMHTMLInputElementIndeterminate obj = liftIO $ getObjectPropertyBool obj "indeterminate" setDOMHTMLInputElementIndeterminate :: (MonadIO m, DOMHTMLInputElementK o) => o -> Bool -> m () setDOMHTMLInputElementIndeterminate obj val = liftIO $ setObjectPropertyBool obj "indeterminate" val constructDOMHTMLInputElementIndeterminate :: Bool -> IO ([Char], GValue) constructDOMHTMLInputElementIndeterminate val = constructObjectPropertyBool "indeterminate" val data DOMHTMLInputElementIndeterminatePropertyInfo instance AttrInfo DOMHTMLInputElementIndeterminatePropertyInfo where type AttrAllowedOps DOMHTMLInputElementIndeterminatePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLInputElementIndeterminatePropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLInputElementIndeterminatePropertyInfo = DOMHTMLInputElementK type AttrGetType DOMHTMLInputElementIndeterminatePropertyInfo = Bool type AttrLabel DOMHTMLInputElementIndeterminatePropertyInfo = "DOMHTMLInputElement::indeterminate" attrGet _ = getDOMHTMLInputElementIndeterminate attrSet _ = setDOMHTMLInputElementIndeterminate attrConstruct _ = constructDOMHTMLInputElementIndeterminate -- VVV Prop "labels" -- Type: TInterface "WebKit" "DOMNodeList" -- Flags: [PropertyReadable] getDOMHTMLInputElementLabels :: (MonadIO m, DOMHTMLInputElementK o) => o -> m DOMNodeList getDOMHTMLInputElementLabels obj = liftIO $ getObjectPropertyObject obj "labels" DOMNodeList data DOMHTMLInputElementLabelsPropertyInfo instance AttrInfo DOMHTMLInputElementLabelsPropertyInfo where type AttrAllowedOps DOMHTMLInputElementLabelsPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLInputElementLabelsPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLInputElementLabelsPropertyInfo = DOMHTMLInputElementK type AttrGetType DOMHTMLInputElementLabelsPropertyInfo = DOMNodeList type AttrLabel DOMHTMLInputElementLabelsPropertyInfo = "DOMHTMLInputElement::labels" attrGet _ = getDOMHTMLInputElementLabels attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "list" -- Type: TInterface "WebKit" "DOMHTMLElement" -- Flags: [PropertyReadable] getDOMHTMLInputElementList :: (MonadIO m, DOMHTMLInputElementK o) => o -> m DOMHTMLElement getDOMHTMLInputElementList obj = liftIO $ getObjectPropertyObject obj "list" DOMHTMLElement data DOMHTMLInputElementListPropertyInfo instance AttrInfo DOMHTMLInputElementListPropertyInfo where type AttrAllowedOps DOMHTMLInputElementListPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLInputElementListPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLInputElementListPropertyInfo = DOMHTMLInputElementK type AttrGetType DOMHTMLInputElementListPropertyInfo = DOMHTMLElement type AttrLabel DOMHTMLInputElementListPropertyInfo = "DOMHTMLInputElement::list" attrGet _ = getDOMHTMLInputElementList attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "max" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLInputElementMax :: (MonadIO m, DOMHTMLInputElementK o) => o -> m T.Text getDOMHTMLInputElementMax obj = liftIO $ getObjectPropertyString obj "max" setDOMHTMLInputElementMax :: (MonadIO m, DOMHTMLInputElementK o) => o -> T.Text -> m () setDOMHTMLInputElementMax obj val = liftIO $ setObjectPropertyString obj "max" val constructDOMHTMLInputElementMax :: T.Text -> IO ([Char], GValue) constructDOMHTMLInputElementMax val = constructObjectPropertyString "max" val data DOMHTMLInputElementMaxPropertyInfo instance AttrInfo DOMHTMLInputElementMaxPropertyInfo where type AttrAllowedOps DOMHTMLInputElementMaxPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLInputElementMaxPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLInputElementMaxPropertyInfo = DOMHTMLInputElementK type AttrGetType DOMHTMLInputElementMaxPropertyInfo = T.Text type AttrLabel DOMHTMLInputElementMaxPropertyInfo = "DOMHTMLInputElement::max" attrGet _ = getDOMHTMLInputElementMax attrSet _ = setDOMHTMLInputElementMax attrConstruct _ = constructDOMHTMLInputElementMax -- VVV Prop "max-length" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLInputElementMaxLength :: (MonadIO m, DOMHTMLInputElementK o) => o -> m Int64 getDOMHTMLInputElementMaxLength obj = liftIO $ getObjectPropertyInt64 obj "max-length" setDOMHTMLInputElementMaxLength :: (MonadIO m, DOMHTMLInputElementK o) => o -> Int64 -> m () setDOMHTMLInputElementMaxLength obj val = liftIO $ setObjectPropertyInt64 obj "max-length" val constructDOMHTMLInputElementMaxLength :: Int64 -> IO ([Char], GValue) constructDOMHTMLInputElementMaxLength val = constructObjectPropertyInt64 "max-length" val data DOMHTMLInputElementMaxLengthPropertyInfo instance AttrInfo DOMHTMLInputElementMaxLengthPropertyInfo where type AttrAllowedOps DOMHTMLInputElementMaxLengthPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLInputElementMaxLengthPropertyInfo = (~) Int64 type AttrBaseTypeConstraint DOMHTMLInputElementMaxLengthPropertyInfo = DOMHTMLInputElementK type AttrGetType DOMHTMLInputElementMaxLengthPropertyInfo = Int64 type AttrLabel DOMHTMLInputElementMaxLengthPropertyInfo = "DOMHTMLInputElement::max-length" attrGet _ = getDOMHTMLInputElementMaxLength attrSet _ = setDOMHTMLInputElementMaxLength attrConstruct _ = constructDOMHTMLInputElementMaxLength -- VVV Prop "min" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLInputElementMin :: (MonadIO m, DOMHTMLInputElementK o) => o -> m T.Text getDOMHTMLInputElementMin obj = liftIO $ getObjectPropertyString obj "min" setDOMHTMLInputElementMin :: (MonadIO m, DOMHTMLInputElementK o) => o -> T.Text -> m () setDOMHTMLInputElementMin obj val = liftIO $ setObjectPropertyString obj "min" val constructDOMHTMLInputElementMin :: T.Text -> IO ([Char], GValue) constructDOMHTMLInputElementMin val = constructObjectPropertyString "min" val data DOMHTMLInputElementMinPropertyInfo instance AttrInfo DOMHTMLInputElementMinPropertyInfo where type AttrAllowedOps DOMHTMLInputElementMinPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLInputElementMinPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLInputElementMinPropertyInfo = DOMHTMLInputElementK type AttrGetType DOMHTMLInputElementMinPropertyInfo = T.Text type AttrLabel DOMHTMLInputElementMinPropertyInfo = "DOMHTMLInputElement::min" attrGet _ = getDOMHTMLInputElementMin attrSet _ = setDOMHTMLInputElementMin attrConstruct _ = constructDOMHTMLInputElementMin -- VVV Prop "multiple" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLInputElementMultiple :: (MonadIO m, DOMHTMLInputElementK o) => o -> m Bool getDOMHTMLInputElementMultiple obj = liftIO $ getObjectPropertyBool obj "multiple" setDOMHTMLInputElementMultiple :: (MonadIO m, DOMHTMLInputElementK o) => o -> Bool -> m () setDOMHTMLInputElementMultiple obj val = liftIO $ setObjectPropertyBool obj "multiple" val constructDOMHTMLInputElementMultiple :: Bool -> IO ([Char], GValue) constructDOMHTMLInputElementMultiple val = constructObjectPropertyBool "multiple" val data DOMHTMLInputElementMultiplePropertyInfo instance AttrInfo DOMHTMLInputElementMultiplePropertyInfo where type AttrAllowedOps DOMHTMLInputElementMultiplePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLInputElementMultiplePropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLInputElementMultiplePropertyInfo = DOMHTMLInputElementK type AttrGetType DOMHTMLInputElementMultiplePropertyInfo = Bool type AttrLabel DOMHTMLInputElementMultiplePropertyInfo = "DOMHTMLInputElement::multiple" attrGet _ = getDOMHTMLInputElementMultiple attrSet _ = setDOMHTMLInputElementMultiple attrConstruct _ = constructDOMHTMLInputElementMultiple -- VVV Prop "name" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLInputElementName :: (MonadIO m, DOMHTMLInputElementK o) => o -> m T.Text getDOMHTMLInputElementName obj = liftIO $ getObjectPropertyString obj "name" setDOMHTMLInputElementName :: (MonadIO m, DOMHTMLInputElementK o) => o -> T.Text -> m () setDOMHTMLInputElementName obj val = liftIO $ setObjectPropertyString obj "name" val constructDOMHTMLInputElementName :: T.Text -> IO ([Char], GValue) constructDOMHTMLInputElementName val = constructObjectPropertyString "name" val data DOMHTMLInputElementNamePropertyInfo instance AttrInfo DOMHTMLInputElementNamePropertyInfo where type AttrAllowedOps DOMHTMLInputElementNamePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLInputElementNamePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLInputElementNamePropertyInfo = DOMHTMLInputElementK type AttrGetType DOMHTMLInputElementNamePropertyInfo = T.Text type AttrLabel DOMHTMLInputElementNamePropertyInfo = "DOMHTMLInputElement::name" attrGet _ = getDOMHTMLInputElementName attrSet _ = setDOMHTMLInputElementName attrConstruct _ = constructDOMHTMLInputElementName -- VVV Prop "pattern" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLInputElementPattern :: (MonadIO m, DOMHTMLInputElementK o) => o -> m T.Text getDOMHTMLInputElementPattern obj = liftIO $ getObjectPropertyString obj "pattern" setDOMHTMLInputElementPattern :: (MonadIO m, DOMHTMLInputElementK o) => o -> T.Text -> m () setDOMHTMLInputElementPattern obj val = liftIO $ setObjectPropertyString obj "pattern" val constructDOMHTMLInputElementPattern :: T.Text -> IO ([Char], GValue) constructDOMHTMLInputElementPattern val = constructObjectPropertyString "pattern" val data DOMHTMLInputElementPatternPropertyInfo instance AttrInfo DOMHTMLInputElementPatternPropertyInfo where type AttrAllowedOps DOMHTMLInputElementPatternPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLInputElementPatternPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLInputElementPatternPropertyInfo = DOMHTMLInputElementK type AttrGetType DOMHTMLInputElementPatternPropertyInfo = T.Text type AttrLabel DOMHTMLInputElementPatternPropertyInfo = "DOMHTMLInputElement::pattern" attrGet _ = getDOMHTMLInputElementPattern attrSet _ = setDOMHTMLInputElementPattern attrConstruct _ = constructDOMHTMLInputElementPattern -- VVV Prop "placeholder" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLInputElementPlaceholder :: (MonadIO m, DOMHTMLInputElementK o) => o -> m T.Text getDOMHTMLInputElementPlaceholder obj = liftIO $ getObjectPropertyString obj "placeholder" setDOMHTMLInputElementPlaceholder :: (MonadIO m, DOMHTMLInputElementK o) => o -> T.Text -> m () setDOMHTMLInputElementPlaceholder obj val = liftIO $ setObjectPropertyString obj "placeholder" val constructDOMHTMLInputElementPlaceholder :: T.Text -> IO ([Char], GValue) constructDOMHTMLInputElementPlaceholder val = constructObjectPropertyString "placeholder" val data DOMHTMLInputElementPlaceholderPropertyInfo instance AttrInfo DOMHTMLInputElementPlaceholderPropertyInfo where type AttrAllowedOps DOMHTMLInputElementPlaceholderPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLInputElementPlaceholderPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLInputElementPlaceholderPropertyInfo = DOMHTMLInputElementK type AttrGetType DOMHTMLInputElementPlaceholderPropertyInfo = T.Text type AttrLabel DOMHTMLInputElementPlaceholderPropertyInfo = "DOMHTMLInputElement::placeholder" attrGet _ = getDOMHTMLInputElementPlaceholder attrSet _ = setDOMHTMLInputElementPlaceholder attrConstruct _ = constructDOMHTMLInputElementPlaceholder -- VVV Prop "read-only" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLInputElementReadOnly :: (MonadIO m, DOMHTMLInputElementK o) => o -> m Bool getDOMHTMLInputElementReadOnly obj = liftIO $ getObjectPropertyBool obj "read-only" setDOMHTMLInputElementReadOnly :: (MonadIO m, DOMHTMLInputElementK o) => o -> Bool -> m () setDOMHTMLInputElementReadOnly obj val = liftIO $ setObjectPropertyBool obj "read-only" val constructDOMHTMLInputElementReadOnly :: Bool -> IO ([Char], GValue) constructDOMHTMLInputElementReadOnly val = constructObjectPropertyBool "read-only" val data DOMHTMLInputElementReadOnlyPropertyInfo instance AttrInfo DOMHTMLInputElementReadOnlyPropertyInfo where type AttrAllowedOps DOMHTMLInputElementReadOnlyPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLInputElementReadOnlyPropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLInputElementReadOnlyPropertyInfo = DOMHTMLInputElementK type AttrGetType DOMHTMLInputElementReadOnlyPropertyInfo = Bool type AttrLabel DOMHTMLInputElementReadOnlyPropertyInfo = "DOMHTMLInputElement::read-only" attrGet _ = getDOMHTMLInputElementReadOnly attrSet _ = setDOMHTMLInputElementReadOnly attrConstruct _ = constructDOMHTMLInputElementReadOnly -- VVV Prop "required" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLInputElementRequired :: (MonadIO m, DOMHTMLInputElementK o) => o -> m Bool getDOMHTMLInputElementRequired obj = liftIO $ getObjectPropertyBool obj "required" setDOMHTMLInputElementRequired :: (MonadIO m, DOMHTMLInputElementK o) => o -> Bool -> m () setDOMHTMLInputElementRequired obj val = liftIO $ setObjectPropertyBool obj "required" val constructDOMHTMLInputElementRequired :: Bool -> IO ([Char], GValue) constructDOMHTMLInputElementRequired val = constructObjectPropertyBool "required" val data DOMHTMLInputElementRequiredPropertyInfo instance AttrInfo DOMHTMLInputElementRequiredPropertyInfo where type AttrAllowedOps DOMHTMLInputElementRequiredPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLInputElementRequiredPropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLInputElementRequiredPropertyInfo = DOMHTMLInputElementK type AttrGetType DOMHTMLInputElementRequiredPropertyInfo = Bool type AttrLabel DOMHTMLInputElementRequiredPropertyInfo = "DOMHTMLInputElement::required" attrGet _ = getDOMHTMLInputElementRequired attrSet _ = setDOMHTMLInputElementRequired attrConstruct _ = constructDOMHTMLInputElementRequired -- VVV Prop "size" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLInputElementSize :: (MonadIO m, DOMHTMLInputElementK o) => o -> m Word64 getDOMHTMLInputElementSize obj = liftIO $ getObjectPropertyUInt64 obj "size" setDOMHTMLInputElementSize :: (MonadIO m, DOMHTMLInputElementK o) => o -> Word64 -> m () setDOMHTMLInputElementSize obj val = liftIO $ setObjectPropertyUInt64 obj "size" val constructDOMHTMLInputElementSize :: Word64 -> IO ([Char], GValue) constructDOMHTMLInputElementSize val = constructObjectPropertyUInt64 "size" val data DOMHTMLInputElementSizePropertyInfo instance AttrInfo DOMHTMLInputElementSizePropertyInfo where type AttrAllowedOps DOMHTMLInputElementSizePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLInputElementSizePropertyInfo = (~) Word64 type AttrBaseTypeConstraint DOMHTMLInputElementSizePropertyInfo = DOMHTMLInputElementK type AttrGetType DOMHTMLInputElementSizePropertyInfo = Word64 type AttrLabel DOMHTMLInputElementSizePropertyInfo = "DOMHTMLInputElement::size" attrGet _ = getDOMHTMLInputElementSize attrSet _ = setDOMHTMLInputElementSize attrConstruct _ = constructDOMHTMLInputElementSize -- VVV Prop "src" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLInputElementSrc :: (MonadIO m, DOMHTMLInputElementK o) => o -> m T.Text getDOMHTMLInputElementSrc obj = liftIO $ getObjectPropertyString obj "src" setDOMHTMLInputElementSrc :: (MonadIO m, DOMHTMLInputElementK o) => o -> T.Text -> m () setDOMHTMLInputElementSrc obj val = liftIO $ setObjectPropertyString obj "src" val constructDOMHTMLInputElementSrc :: T.Text -> IO ([Char], GValue) constructDOMHTMLInputElementSrc val = constructObjectPropertyString "src" val data DOMHTMLInputElementSrcPropertyInfo instance AttrInfo DOMHTMLInputElementSrcPropertyInfo where type AttrAllowedOps DOMHTMLInputElementSrcPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLInputElementSrcPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLInputElementSrcPropertyInfo = DOMHTMLInputElementK type AttrGetType DOMHTMLInputElementSrcPropertyInfo = T.Text type AttrLabel DOMHTMLInputElementSrcPropertyInfo = "DOMHTMLInputElement::src" attrGet _ = getDOMHTMLInputElementSrc attrSet _ = setDOMHTMLInputElementSrc attrConstruct _ = constructDOMHTMLInputElementSrc -- VVV Prop "step" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLInputElementStep :: (MonadIO m, DOMHTMLInputElementK o) => o -> m T.Text getDOMHTMLInputElementStep obj = liftIO $ getObjectPropertyString obj "step" setDOMHTMLInputElementStep :: (MonadIO m, DOMHTMLInputElementK o) => o -> T.Text -> m () setDOMHTMLInputElementStep obj val = liftIO $ setObjectPropertyString obj "step" val constructDOMHTMLInputElementStep :: T.Text -> IO ([Char], GValue) constructDOMHTMLInputElementStep val = constructObjectPropertyString "step" val data DOMHTMLInputElementStepPropertyInfo instance AttrInfo DOMHTMLInputElementStepPropertyInfo where type AttrAllowedOps DOMHTMLInputElementStepPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLInputElementStepPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLInputElementStepPropertyInfo = DOMHTMLInputElementK type AttrGetType DOMHTMLInputElementStepPropertyInfo = T.Text type AttrLabel DOMHTMLInputElementStepPropertyInfo = "DOMHTMLInputElement::step" attrGet _ = getDOMHTMLInputElementStep attrSet _ = setDOMHTMLInputElementStep attrConstruct _ = constructDOMHTMLInputElementStep -- VVV Prop "type" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLInputElementType :: (MonadIO m, DOMHTMLInputElementK o) => o -> m T.Text getDOMHTMLInputElementType obj = liftIO $ getObjectPropertyString obj "type" setDOMHTMLInputElementType :: (MonadIO m, DOMHTMLInputElementK o) => o -> T.Text -> m () setDOMHTMLInputElementType obj val = liftIO $ setObjectPropertyString obj "type" val constructDOMHTMLInputElementType :: T.Text -> IO ([Char], GValue) constructDOMHTMLInputElementType val = constructObjectPropertyString "type" val data DOMHTMLInputElementTypePropertyInfo instance AttrInfo DOMHTMLInputElementTypePropertyInfo where type AttrAllowedOps DOMHTMLInputElementTypePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLInputElementTypePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLInputElementTypePropertyInfo = DOMHTMLInputElementK type AttrGetType DOMHTMLInputElementTypePropertyInfo = T.Text type AttrLabel DOMHTMLInputElementTypePropertyInfo = "DOMHTMLInputElement::type" attrGet _ = getDOMHTMLInputElementType attrSet _ = setDOMHTMLInputElementType attrConstruct _ = constructDOMHTMLInputElementType -- VVV Prop "use-map" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLInputElementUseMap :: (MonadIO m, DOMHTMLInputElementK o) => o -> m T.Text getDOMHTMLInputElementUseMap obj = liftIO $ getObjectPropertyString obj "use-map" setDOMHTMLInputElementUseMap :: (MonadIO m, DOMHTMLInputElementK o) => o -> T.Text -> m () setDOMHTMLInputElementUseMap obj val = liftIO $ setObjectPropertyString obj "use-map" val constructDOMHTMLInputElementUseMap :: T.Text -> IO ([Char], GValue) constructDOMHTMLInputElementUseMap val = constructObjectPropertyString "use-map" val data DOMHTMLInputElementUseMapPropertyInfo instance AttrInfo DOMHTMLInputElementUseMapPropertyInfo where type AttrAllowedOps DOMHTMLInputElementUseMapPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLInputElementUseMapPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLInputElementUseMapPropertyInfo = DOMHTMLInputElementK type AttrGetType DOMHTMLInputElementUseMapPropertyInfo = T.Text type AttrLabel DOMHTMLInputElementUseMapPropertyInfo = "DOMHTMLInputElement::use-map" attrGet _ = getDOMHTMLInputElementUseMap attrSet _ = setDOMHTMLInputElementUseMap attrConstruct _ = constructDOMHTMLInputElementUseMap -- VVV Prop "validation-message" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMHTMLInputElementValidationMessage :: (MonadIO m, DOMHTMLInputElementK o) => o -> m T.Text getDOMHTMLInputElementValidationMessage obj = liftIO $ getObjectPropertyString obj "validation-message" data DOMHTMLInputElementValidationMessagePropertyInfo instance AttrInfo DOMHTMLInputElementValidationMessagePropertyInfo where type AttrAllowedOps DOMHTMLInputElementValidationMessagePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLInputElementValidationMessagePropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLInputElementValidationMessagePropertyInfo = DOMHTMLInputElementK type AttrGetType DOMHTMLInputElementValidationMessagePropertyInfo = T.Text type AttrLabel DOMHTMLInputElementValidationMessagePropertyInfo = "DOMHTMLInputElement::validation-message" attrGet _ = getDOMHTMLInputElementValidationMessage attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "validity" -- Type: TInterface "WebKit" "DOMValidityState" -- Flags: [PropertyReadable] getDOMHTMLInputElementValidity :: (MonadIO m, DOMHTMLInputElementK o) => o -> m DOMValidityState getDOMHTMLInputElementValidity obj = liftIO $ getObjectPropertyObject obj "validity" DOMValidityState data DOMHTMLInputElementValidityPropertyInfo instance AttrInfo DOMHTMLInputElementValidityPropertyInfo where type AttrAllowedOps DOMHTMLInputElementValidityPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLInputElementValidityPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLInputElementValidityPropertyInfo = DOMHTMLInputElementK type AttrGetType DOMHTMLInputElementValidityPropertyInfo = DOMValidityState type AttrLabel DOMHTMLInputElementValidityPropertyInfo = "DOMHTMLInputElement::validity" attrGet _ = getDOMHTMLInputElementValidity attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "value" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLInputElementValue :: (MonadIO m, DOMHTMLInputElementK o) => o -> m T.Text getDOMHTMLInputElementValue obj = liftIO $ getObjectPropertyString obj "value" setDOMHTMLInputElementValue :: (MonadIO m, DOMHTMLInputElementK o) => o -> T.Text -> m () setDOMHTMLInputElementValue obj val = liftIO $ setObjectPropertyString obj "value" val constructDOMHTMLInputElementValue :: T.Text -> IO ([Char], GValue) constructDOMHTMLInputElementValue val = constructObjectPropertyString "value" val data DOMHTMLInputElementValuePropertyInfo instance AttrInfo DOMHTMLInputElementValuePropertyInfo where type AttrAllowedOps DOMHTMLInputElementValuePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLInputElementValuePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLInputElementValuePropertyInfo = DOMHTMLInputElementK type AttrGetType DOMHTMLInputElementValuePropertyInfo = T.Text type AttrLabel DOMHTMLInputElementValuePropertyInfo = "DOMHTMLInputElement::value" attrGet _ = getDOMHTMLInputElementValue attrSet _ = setDOMHTMLInputElementValue attrConstruct _ = constructDOMHTMLInputElementValue -- VVV Prop "value-as-number" -- Type: TBasicType TDouble -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLInputElementValueAsNumber :: (MonadIO m, DOMHTMLInputElementK o) => o -> m Double getDOMHTMLInputElementValueAsNumber obj = liftIO $ getObjectPropertyDouble obj "value-as-number" setDOMHTMLInputElementValueAsNumber :: (MonadIO m, DOMHTMLInputElementK o) => o -> Double -> m () setDOMHTMLInputElementValueAsNumber obj val = liftIO $ setObjectPropertyDouble obj "value-as-number" val constructDOMHTMLInputElementValueAsNumber :: Double -> IO ([Char], GValue) constructDOMHTMLInputElementValueAsNumber val = constructObjectPropertyDouble "value-as-number" val data DOMHTMLInputElementValueAsNumberPropertyInfo instance AttrInfo DOMHTMLInputElementValueAsNumberPropertyInfo where type AttrAllowedOps DOMHTMLInputElementValueAsNumberPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLInputElementValueAsNumberPropertyInfo = (~) Double type AttrBaseTypeConstraint DOMHTMLInputElementValueAsNumberPropertyInfo = DOMHTMLInputElementK type AttrGetType DOMHTMLInputElementValueAsNumberPropertyInfo = Double type AttrLabel DOMHTMLInputElementValueAsNumberPropertyInfo = "DOMHTMLInputElement::value-as-number" attrGet _ = getDOMHTMLInputElementValueAsNumber attrSet _ = setDOMHTMLInputElementValueAsNumber attrConstruct _ = constructDOMHTMLInputElementValueAsNumber -- VVV Prop "webkit-grammar" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLInputElementWebkitGrammar :: (MonadIO m, DOMHTMLInputElementK o) => o -> m Bool getDOMHTMLInputElementWebkitGrammar obj = liftIO $ getObjectPropertyBool obj "webkit-grammar" setDOMHTMLInputElementWebkitGrammar :: (MonadIO m, DOMHTMLInputElementK o) => o -> Bool -> m () setDOMHTMLInputElementWebkitGrammar obj val = liftIO $ setObjectPropertyBool obj "webkit-grammar" val constructDOMHTMLInputElementWebkitGrammar :: Bool -> IO ([Char], GValue) constructDOMHTMLInputElementWebkitGrammar val = constructObjectPropertyBool "webkit-grammar" val data DOMHTMLInputElementWebkitGrammarPropertyInfo instance AttrInfo DOMHTMLInputElementWebkitGrammarPropertyInfo where type AttrAllowedOps DOMHTMLInputElementWebkitGrammarPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLInputElementWebkitGrammarPropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLInputElementWebkitGrammarPropertyInfo = DOMHTMLInputElementK type AttrGetType DOMHTMLInputElementWebkitGrammarPropertyInfo = Bool type AttrLabel DOMHTMLInputElementWebkitGrammarPropertyInfo = "DOMHTMLInputElement::webkit-grammar" attrGet _ = getDOMHTMLInputElementWebkitGrammar attrSet _ = setDOMHTMLInputElementWebkitGrammar attrConstruct _ = constructDOMHTMLInputElementWebkitGrammar -- VVV Prop "webkit-speech" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLInputElementWebkitSpeech :: (MonadIO m, DOMHTMLInputElementK o) => o -> m Bool getDOMHTMLInputElementWebkitSpeech obj = liftIO $ getObjectPropertyBool obj "webkit-speech" setDOMHTMLInputElementWebkitSpeech :: (MonadIO m, DOMHTMLInputElementK o) => o -> Bool -> m () setDOMHTMLInputElementWebkitSpeech obj val = liftIO $ setObjectPropertyBool obj "webkit-speech" val constructDOMHTMLInputElementWebkitSpeech :: Bool -> IO ([Char], GValue) constructDOMHTMLInputElementWebkitSpeech val = constructObjectPropertyBool "webkit-speech" val data DOMHTMLInputElementWebkitSpeechPropertyInfo instance AttrInfo DOMHTMLInputElementWebkitSpeechPropertyInfo where type AttrAllowedOps DOMHTMLInputElementWebkitSpeechPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLInputElementWebkitSpeechPropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLInputElementWebkitSpeechPropertyInfo = DOMHTMLInputElementK type AttrGetType DOMHTMLInputElementWebkitSpeechPropertyInfo = Bool type AttrLabel DOMHTMLInputElementWebkitSpeechPropertyInfo = "DOMHTMLInputElement::webkit-speech" attrGet _ = getDOMHTMLInputElementWebkitSpeech attrSet _ = setDOMHTMLInputElementWebkitSpeech attrConstruct _ = constructDOMHTMLInputElementWebkitSpeech -- VVV Prop "webkitdirectory" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLInputElementWebkitdirectory :: (MonadIO m, DOMHTMLInputElementK o) => o -> m Bool getDOMHTMLInputElementWebkitdirectory obj = liftIO $ getObjectPropertyBool obj "webkitdirectory" setDOMHTMLInputElementWebkitdirectory :: (MonadIO m, DOMHTMLInputElementK o) => o -> Bool -> m () setDOMHTMLInputElementWebkitdirectory obj val = liftIO $ setObjectPropertyBool obj "webkitdirectory" val constructDOMHTMLInputElementWebkitdirectory :: Bool -> IO ([Char], GValue) constructDOMHTMLInputElementWebkitdirectory val = constructObjectPropertyBool "webkitdirectory" val data DOMHTMLInputElementWebkitdirectoryPropertyInfo instance AttrInfo DOMHTMLInputElementWebkitdirectoryPropertyInfo where type AttrAllowedOps DOMHTMLInputElementWebkitdirectoryPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLInputElementWebkitdirectoryPropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLInputElementWebkitdirectoryPropertyInfo = DOMHTMLInputElementK type AttrGetType DOMHTMLInputElementWebkitdirectoryPropertyInfo = Bool type AttrLabel DOMHTMLInputElementWebkitdirectoryPropertyInfo = "DOMHTMLInputElement::webkitdirectory" attrGet _ = getDOMHTMLInputElementWebkitdirectory attrSet _ = setDOMHTMLInputElementWebkitdirectory attrConstruct _ = constructDOMHTMLInputElementWebkitdirectory -- VVV Prop "width" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLInputElementWidth :: (MonadIO m, DOMHTMLInputElementK o) => o -> m Word64 getDOMHTMLInputElementWidth obj = liftIO $ getObjectPropertyUInt64 obj "width" setDOMHTMLInputElementWidth :: (MonadIO m, DOMHTMLInputElementK o) => o -> Word64 -> m () setDOMHTMLInputElementWidth obj val = liftIO $ setObjectPropertyUInt64 obj "width" val constructDOMHTMLInputElementWidth :: Word64 -> IO ([Char], GValue) constructDOMHTMLInputElementWidth val = constructObjectPropertyUInt64 "width" val data DOMHTMLInputElementWidthPropertyInfo instance AttrInfo DOMHTMLInputElementWidthPropertyInfo where type AttrAllowedOps DOMHTMLInputElementWidthPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLInputElementWidthPropertyInfo = (~) Word64 type AttrBaseTypeConstraint DOMHTMLInputElementWidthPropertyInfo = DOMHTMLInputElementK type AttrGetType DOMHTMLInputElementWidthPropertyInfo = Word64 type AttrLabel DOMHTMLInputElementWidthPropertyInfo = "DOMHTMLInputElement::width" attrGet _ = getDOMHTMLInputElementWidth attrSet _ = setDOMHTMLInputElementWidth attrConstruct _ = constructDOMHTMLInputElementWidth -- VVV Prop "will-validate" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMHTMLInputElementWillValidate :: (MonadIO m, DOMHTMLInputElementK o) => o -> m Bool getDOMHTMLInputElementWillValidate obj = liftIO $ getObjectPropertyBool obj "will-validate" data DOMHTMLInputElementWillValidatePropertyInfo instance AttrInfo DOMHTMLInputElementWillValidatePropertyInfo where type AttrAllowedOps DOMHTMLInputElementWillValidatePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLInputElementWillValidatePropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLInputElementWillValidatePropertyInfo = DOMHTMLInputElementK type AttrGetType DOMHTMLInputElementWillValidatePropertyInfo = Bool type AttrLabel DOMHTMLInputElementWillValidatePropertyInfo = "DOMHTMLInputElement::will-validate" attrGet _ = getDOMHTMLInputElementWillValidate attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMHTMLInputElement = '[ '("accept", DOMHTMLInputElementAcceptPropertyInfo), '("access-key", DOMHTMLElementAccessKeyPropertyInfo), '("align", DOMHTMLInputElementAlignPropertyInfo), '("alt", DOMHTMLInputElementAltPropertyInfo), '("attributes", DOMElementAttributesPropertyInfo), '("autocapitalize", DOMHTMLInputElementAutocapitalizePropertyInfo), '("autocomplete", DOMHTMLInputElementAutocompletePropertyInfo), '("autocorrect", DOMHTMLInputElementAutocorrectPropertyInfo), '("autofocus", DOMHTMLInputElementAutofocusPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("capture", DOMHTMLInputElementCapturePropertyInfo), '("checked", DOMHTMLInputElementCheckedPropertyInfo), '("child-element-count", DOMElementChildElementCountPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("children", DOMHTMLElementChildrenPropertyInfo), '("class-list", DOMElementClassListPropertyInfo), '("class-name", DOMElementClassNamePropertyInfo), '("client-height", DOMElementClientHeightPropertyInfo), '("client-left", DOMElementClientLeftPropertyInfo), '("client-top", DOMElementClientTopPropertyInfo), '("client-width", DOMElementClientWidthPropertyInfo), '("content-editable", DOMHTMLElementContentEditablePropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("default-checked", DOMHTMLInputElementDefaultCheckedPropertyInfo), '("default-value", DOMHTMLInputElementDefaultValuePropertyInfo), '("dir", DOMHTMLElementDirPropertyInfo), '("dir-name", DOMHTMLInputElementDirNamePropertyInfo), '("disabled", DOMHTMLInputElementDisabledPropertyInfo), '("draggable", DOMHTMLElementDraggablePropertyInfo), '("files", DOMHTMLInputElementFilesPropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("first-element-child", DOMElementFirstElementChildPropertyInfo), '("form", DOMHTMLInputElementFormPropertyInfo), '("form-action", DOMHTMLInputElementFormActionPropertyInfo), '("form-enctype", DOMHTMLInputElementFormEnctypePropertyInfo), '("form-method", DOMHTMLInputElementFormMethodPropertyInfo), '("form-no-validate", DOMHTMLInputElementFormNoValidatePropertyInfo), '("form-target", DOMHTMLInputElementFormTargetPropertyInfo), '("height", DOMHTMLInputElementHeightPropertyInfo), '("hidden", DOMHTMLElementHiddenPropertyInfo), '("id", DOMElementIdPropertyInfo), '("incremental", DOMHTMLInputElementIncrementalPropertyInfo), '("indeterminate", DOMHTMLInputElementIndeterminatePropertyInfo), '("inner-html", DOMHTMLElementInnerHtmlPropertyInfo), '("inner-text", DOMHTMLElementInnerTextPropertyInfo), '("is-content-editable", DOMHTMLElementIsContentEditablePropertyInfo), '("labels", DOMHTMLInputElementLabelsPropertyInfo), '("lang", DOMHTMLElementLangPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-element-child", DOMElementLastElementChildPropertyInfo), '("list", DOMHTMLInputElementListPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("max", DOMHTMLInputElementMaxPropertyInfo), '("max-length", DOMHTMLInputElementMaxLengthPropertyInfo), '("min", DOMHTMLInputElementMinPropertyInfo), '("multiple", DOMHTMLInputElementMultiplePropertyInfo), '("name", DOMHTMLInputElementNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-element-sibling", DOMElementNextElementSiblingPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("offset-height", DOMElementOffsetHeightPropertyInfo), '("offset-left", DOMElementOffsetLeftPropertyInfo), '("offset-parent", DOMElementOffsetParentPropertyInfo), '("offset-top", DOMElementOffsetTopPropertyInfo), '("offset-width", DOMElementOffsetWidthPropertyInfo), '("outer-html", DOMHTMLElementOuterHtmlPropertyInfo), '("outer-text", DOMHTMLElementOuterTextPropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("pattern", DOMHTMLInputElementPatternPropertyInfo), '("placeholder", DOMHTMLInputElementPlaceholderPropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-element-sibling", DOMElementPreviousElementSiblingPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("read-only", DOMHTMLInputElementReadOnlyPropertyInfo), '("required", DOMHTMLInputElementRequiredPropertyInfo), '("scroll-height", DOMElementScrollHeightPropertyInfo), '("scroll-left", DOMElementScrollLeftPropertyInfo), '("scroll-top", DOMElementScrollTopPropertyInfo), '("scroll-width", DOMElementScrollWidthPropertyInfo), '("size", DOMHTMLInputElementSizePropertyInfo), '("spellcheck", DOMHTMLElementSpellcheckPropertyInfo), '("src", DOMHTMLInputElementSrcPropertyInfo), '("step", DOMHTMLInputElementStepPropertyInfo), '("style", DOMElementStylePropertyInfo), '("tab-index", DOMHTMLElementTabIndexPropertyInfo), '("tag-name", DOMElementTagNamePropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("title", DOMHTMLElementTitlePropertyInfo), '("translate", DOMHTMLElementTranslatePropertyInfo), '("type", DOMHTMLInputElementTypePropertyInfo), '("use-map", DOMHTMLInputElementUseMapPropertyInfo), '("validation-message", DOMHTMLInputElementValidationMessagePropertyInfo), '("validity", DOMHTMLInputElementValidityPropertyInfo), '("value", DOMHTMLInputElementValuePropertyInfo), '("value-as-number", DOMHTMLInputElementValueAsNumberPropertyInfo), '("webkit-grammar", DOMHTMLInputElementWebkitGrammarPropertyInfo), '("webkit-region-overset", DOMElementWebkitRegionOversetPropertyInfo), '("webkit-speech", DOMHTMLInputElementWebkitSpeechPropertyInfo), '("webkitdirectory", DOMHTMLInputElementWebkitdirectoryPropertyInfo), '("webkitdropzone", DOMHTMLElementWebkitdropzonePropertyInfo), '("width", DOMHTMLInputElementWidthPropertyInfo), '("will-validate", DOMHTMLInputElementWillValidatePropertyInfo)] -- VVV Prop "autofocus" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLKeygenElementAutofocus :: (MonadIO m, DOMHTMLKeygenElementK o) => o -> m Bool getDOMHTMLKeygenElementAutofocus obj = liftIO $ getObjectPropertyBool obj "autofocus" setDOMHTMLKeygenElementAutofocus :: (MonadIO m, DOMHTMLKeygenElementK o) => o -> Bool -> m () setDOMHTMLKeygenElementAutofocus obj val = liftIO $ setObjectPropertyBool obj "autofocus" val constructDOMHTMLKeygenElementAutofocus :: Bool -> IO ([Char], GValue) constructDOMHTMLKeygenElementAutofocus val = constructObjectPropertyBool "autofocus" val data DOMHTMLKeygenElementAutofocusPropertyInfo instance AttrInfo DOMHTMLKeygenElementAutofocusPropertyInfo where type AttrAllowedOps DOMHTMLKeygenElementAutofocusPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLKeygenElementAutofocusPropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLKeygenElementAutofocusPropertyInfo = DOMHTMLKeygenElementK type AttrGetType DOMHTMLKeygenElementAutofocusPropertyInfo = Bool type AttrLabel DOMHTMLKeygenElementAutofocusPropertyInfo = "DOMHTMLKeygenElement::autofocus" attrGet _ = getDOMHTMLKeygenElementAutofocus attrSet _ = setDOMHTMLKeygenElementAutofocus attrConstruct _ = constructDOMHTMLKeygenElementAutofocus -- VVV Prop "challenge" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLKeygenElementChallenge :: (MonadIO m, DOMHTMLKeygenElementK o) => o -> m T.Text getDOMHTMLKeygenElementChallenge obj = liftIO $ getObjectPropertyString obj "challenge" setDOMHTMLKeygenElementChallenge :: (MonadIO m, DOMHTMLKeygenElementK o) => o -> T.Text -> m () setDOMHTMLKeygenElementChallenge obj val = liftIO $ setObjectPropertyString obj "challenge" val constructDOMHTMLKeygenElementChallenge :: T.Text -> IO ([Char], GValue) constructDOMHTMLKeygenElementChallenge val = constructObjectPropertyString "challenge" val data DOMHTMLKeygenElementChallengePropertyInfo instance AttrInfo DOMHTMLKeygenElementChallengePropertyInfo where type AttrAllowedOps DOMHTMLKeygenElementChallengePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLKeygenElementChallengePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLKeygenElementChallengePropertyInfo = DOMHTMLKeygenElementK type AttrGetType DOMHTMLKeygenElementChallengePropertyInfo = T.Text type AttrLabel DOMHTMLKeygenElementChallengePropertyInfo = "DOMHTMLKeygenElement::challenge" attrGet _ = getDOMHTMLKeygenElementChallenge attrSet _ = setDOMHTMLKeygenElementChallenge attrConstruct _ = constructDOMHTMLKeygenElementChallenge -- VVV Prop "disabled" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLKeygenElementDisabled :: (MonadIO m, DOMHTMLKeygenElementK o) => o -> m Bool getDOMHTMLKeygenElementDisabled obj = liftIO $ getObjectPropertyBool obj "disabled" setDOMHTMLKeygenElementDisabled :: (MonadIO m, DOMHTMLKeygenElementK o) => o -> Bool -> m () setDOMHTMLKeygenElementDisabled obj val = liftIO $ setObjectPropertyBool obj "disabled" val constructDOMHTMLKeygenElementDisabled :: Bool -> IO ([Char], GValue) constructDOMHTMLKeygenElementDisabled val = constructObjectPropertyBool "disabled" val data DOMHTMLKeygenElementDisabledPropertyInfo instance AttrInfo DOMHTMLKeygenElementDisabledPropertyInfo where type AttrAllowedOps DOMHTMLKeygenElementDisabledPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLKeygenElementDisabledPropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLKeygenElementDisabledPropertyInfo = DOMHTMLKeygenElementK type AttrGetType DOMHTMLKeygenElementDisabledPropertyInfo = Bool type AttrLabel DOMHTMLKeygenElementDisabledPropertyInfo = "DOMHTMLKeygenElement::disabled" attrGet _ = getDOMHTMLKeygenElementDisabled attrSet _ = setDOMHTMLKeygenElementDisabled attrConstruct _ = constructDOMHTMLKeygenElementDisabled -- VVV Prop "form" -- Type: TInterface "WebKit" "DOMHTMLFormElement" -- Flags: [PropertyReadable] getDOMHTMLKeygenElementForm :: (MonadIO m, DOMHTMLKeygenElementK o) => o -> m DOMHTMLFormElement getDOMHTMLKeygenElementForm obj = liftIO $ getObjectPropertyObject obj "form" DOMHTMLFormElement data DOMHTMLKeygenElementFormPropertyInfo instance AttrInfo DOMHTMLKeygenElementFormPropertyInfo where type AttrAllowedOps DOMHTMLKeygenElementFormPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLKeygenElementFormPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLKeygenElementFormPropertyInfo = DOMHTMLKeygenElementK type AttrGetType DOMHTMLKeygenElementFormPropertyInfo = DOMHTMLFormElement type AttrLabel DOMHTMLKeygenElementFormPropertyInfo = "DOMHTMLKeygenElement::form" attrGet _ = getDOMHTMLKeygenElementForm attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "keytype" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLKeygenElementKeytype :: (MonadIO m, DOMHTMLKeygenElementK o) => o -> m T.Text getDOMHTMLKeygenElementKeytype obj = liftIO $ getObjectPropertyString obj "keytype" setDOMHTMLKeygenElementKeytype :: (MonadIO m, DOMHTMLKeygenElementK o) => o -> T.Text -> m () setDOMHTMLKeygenElementKeytype obj val = liftIO $ setObjectPropertyString obj "keytype" val constructDOMHTMLKeygenElementKeytype :: T.Text -> IO ([Char], GValue) constructDOMHTMLKeygenElementKeytype val = constructObjectPropertyString "keytype" val data DOMHTMLKeygenElementKeytypePropertyInfo instance AttrInfo DOMHTMLKeygenElementKeytypePropertyInfo where type AttrAllowedOps DOMHTMLKeygenElementKeytypePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLKeygenElementKeytypePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLKeygenElementKeytypePropertyInfo = DOMHTMLKeygenElementK type AttrGetType DOMHTMLKeygenElementKeytypePropertyInfo = T.Text type AttrLabel DOMHTMLKeygenElementKeytypePropertyInfo = "DOMHTMLKeygenElement::keytype" attrGet _ = getDOMHTMLKeygenElementKeytype attrSet _ = setDOMHTMLKeygenElementKeytype attrConstruct _ = constructDOMHTMLKeygenElementKeytype -- VVV Prop "labels" -- Type: TInterface "WebKit" "DOMNodeList" -- Flags: [PropertyReadable] getDOMHTMLKeygenElementLabels :: (MonadIO m, DOMHTMLKeygenElementK o) => o -> m DOMNodeList getDOMHTMLKeygenElementLabels obj = liftIO $ getObjectPropertyObject obj "labels" DOMNodeList data DOMHTMLKeygenElementLabelsPropertyInfo instance AttrInfo DOMHTMLKeygenElementLabelsPropertyInfo where type AttrAllowedOps DOMHTMLKeygenElementLabelsPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLKeygenElementLabelsPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLKeygenElementLabelsPropertyInfo = DOMHTMLKeygenElementK type AttrGetType DOMHTMLKeygenElementLabelsPropertyInfo = DOMNodeList type AttrLabel DOMHTMLKeygenElementLabelsPropertyInfo = "DOMHTMLKeygenElement::labels" attrGet _ = getDOMHTMLKeygenElementLabels attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "name" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLKeygenElementName :: (MonadIO m, DOMHTMLKeygenElementK o) => o -> m T.Text getDOMHTMLKeygenElementName obj = liftIO $ getObjectPropertyString obj "name" setDOMHTMLKeygenElementName :: (MonadIO m, DOMHTMLKeygenElementK o) => o -> T.Text -> m () setDOMHTMLKeygenElementName obj val = liftIO $ setObjectPropertyString obj "name" val constructDOMHTMLKeygenElementName :: T.Text -> IO ([Char], GValue) constructDOMHTMLKeygenElementName val = constructObjectPropertyString "name" val data DOMHTMLKeygenElementNamePropertyInfo instance AttrInfo DOMHTMLKeygenElementNamePropertyInfo where type AttrAllowedOps DOMHTMLKeygenElementNamePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLKeygenElementNamePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLKeygenElementNamePropertyInfo = DOMHTMLKeygenElementK type AttrGetType DOMHTMLKeygenElementNamePropertyInfo = T.Text type AttrLabel DOMHTMLKeygenElementNamePropertyInfo = "DOMHTMLKeygenElement::name" attrGet _ = getDOMHTMLKeygenElementName attrSet _ = setDOMHTMLKeygenElementName attrConstruct _ = constructDOMHTMLKeygenElementName -- VVV Prop "type" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMHTMLKeygenElementType :: (MonadIO m, DOMHTMLKeygenElementK o) => o -> m T.Text getDOMHTMLKeygenElementType obj = liftIO $ getObjectPropertyString obj "type" data DOMHTMLKeygenElementTypePropertyInfo instance AttrInfo DOMHTMLKeygenElementTypePropertyInfo where type AttrAllowedOps DOMHTMLKeygenElementTypePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLKeygenElementTypePropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLKeygenElementTypePropertyInfo = DOMHTMLKeygenElementK type AttrGetType DOMHTMLKeygenElementTypePropertyInfo = T.Text type AttrLabel DOMHTMLKeygenElementTypePropertyInfo = "DOMHTMLKeygenElement::type" attrGet _ = getDOMHTMLKeygenElementType attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "validation-message" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMHTMLKeygenElementValidationMessage :: (MonadIO m, DOMHTMLKeygenElementK o) => o -> m T.Text getDOMHTMLKeygenElementValidationMessage obj = liftIO $ getObjectPropertyString obj "validation-message" data DOMHTMLKeygenElementValidationMessagePropertyInfo instance AttrInfo DOMHTMLKeygenElementValidationMessagePropertyInfo where type AttrAllowedOps DOMHTMLKeygenElementValidationMessagePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLKeygenElementValidationMessagePropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLKeygenElementValidationMessagePropertyInfo = DOMHTMLKeygenElementK type AttrGetType DOMHTMLKeygenElementValidationMessagePropertyInfo = T.Text type AttrLabel DOMHTMLKeygenElementValidationMessagePropertyInfo = "DOMHTMLKeygenElement::validation-message" attrGet _ = getDOMHTMLKeygenElementValidationMessage attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "validity" -- Type: TInterface "WebKit" "DOMValidityState" -- Flags: [PropertyReadable] getDOMHTMLKeygenElementValidity :: (MonadIO m, DOMHTMLKeygenElementK o) => o -> m DOMValidityState getDOMHTMLKeygenElementValidity obj = liftIO $ getObjectPropertyObject obj "validity" DOMValidityState data DOMHTMLKeygenElementValidityPropertyInfo instance AttrInfo DOMHTMLKeygenElementValidityPropertyInfo where type AttrAllowedOps DOMHTMLKeygenElementValidityPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLKeygenElementValidityPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLKeygenElementValidityPropertyInfo = DOMHTMLKeygenElementK type AttrGetType DOMHTMLKeygenElementValidityPropertyInfo = DOMValidityState type AttrLabel DOMHTMLKeygenElementValidityPropertyInfo = "DOMHTMLKeygenElement::validity" attrGet _ = getDOMHTMLKeygenElementValidity attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "will-validate" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMHTMLKeygenElementWillValidate :: (MonadIO m, DOMHTMLKeygenElementK o) => o -> m Bool getDOMHTMLKeygenElementWillValidate obj = liftIO $ getObjectPropertyBool obj "will-validate" data DOMHTMLKeygenElementWillValidatePropertyInfo instance AttrInfo DOMHTMLKeygenElementWillValidatePropertyInfo where type AttrAllowedOps DOMHTMLKeygenElementWillValidatePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLKeygenElementWillValidatePropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLKeygenElementWillValidatePropertyInfo = DOMHTMLKeygenElementK type AttrGetType DOMHTMLKeygenElementWillValidatePropertyInfo = Bool type AttrLabel DOMHTMLKeygenElementWillValidatePropertyInfo = "DOMHTMLKeygenElement::will-validate" attrGet _ = getDOMHTMLKeygenElementWillValidate attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMHTMLKeygenElement = '[ '("access-key", DOMHTMLElementAccessKeyPropertyInfo), '("attributes", DOMElementAttributesPropertyInfo), '("autofocus", DOMHTMLKeygenElementAutofocusPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("challenge", DOMHTMLKeygenElementChallengePropertyInfo), '("child-element-count", DOMElementChildElementCountPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("children", DOMHTMLElementChildrenPropertyInfo), '("class-list", DOMElementClassListPropertyInfo), '("class-name", DOMElementClassNamePropertyInfo), '("client-height", DOMElementClientHeightPropertyInfo), '("client-left", DOMElementClientLeftPropertyInfo), '("client-top", DOMElementClientTopPropertyInfo), '("client-width", DOMElementClientWidthPropertyInfo), '("content-editable", DOMHTMLElementContentEditablePropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("dir", DOMHTMLElementDirPropertyInfo), '("disabled", DOMHTMLKeygenElementDisabledPropertyInfo), '("draggable", DOMHTMLElementDraggablePropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("first-element-child", DOMElementFirstElementChildPropertyInfo), '("form", DOMHTMLKeygenElementFormPropertyInfo), '("hidden", DOMHTMLElementHiddenPropertyInfo), '("id", DOMElementIdPropertyInfo), '("inner-html", DOMHTMLElementInnerHtmlPropertyInfo), '("inner-text", DOMHTMLElementInnerTextPropertyInfo), '("is-content-editable", DOMHTMLElementIsContentEditablePropertyInfo), '("keytype", DOMHTMLKeygenElementKeytypePropertyInfo), '("labels", DOMHTMLKeygenElementLabelsPropertyInfo), '("lang", DOMHTMLElementLangPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-element-child", DOMElementLastElementChildPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("name", DOMHTMLKeygenElementNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-element-sibling", DOMElementNextElementSiblingPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("offset-height", DOMElementOffsetHeightPropertyInfo), '("offset-left", DOMElementOffsetLeftPropertyInfo), '("offset-parent", DOMElementOffsetParentPropertyInfo), '("offset-top", DOMElementOffsetTopPropertyInfo), '("offset-width", DOMElementOffsetWidthPropertyInfo), '("outer-html", DOMHTMLElementOuterHtmlPropertyInfo), '("outer-text", DOMHTMLElementOuterTextPropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-element-sibling", DOMElementPreviousElementSiblingPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("scroll-height", DOMElementScrollHeightPropertyInfo), '("scroll-left", DOMElementScrollLeftPropertyInfo), '("scroll-top", DOMElementScrollTopPropertyInfo), '("scroll-width", DOMElementScrollWidthPropertyInfo), '("spellcheck", DOMHTMLElementSpellcheckPropertyInfo), '("style", DOMElementStylePropertyInfo), '("tab-index", DOMHTMLElementTabIndexPropertyInfo), '("tag-name", DOMElementTagNamePropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("title", DOMHTMLElementTitlePropertyInfo), '("translate", DOMHTMLElementTranslatePropertyInfo), '("type", DOMHTMLKeygenElementTypePropertyInfo), '("validation-message", DOMHTMLKeygenElementValidationMessagePropertyInfo), '("validity", DOMHTMLKeygenElementValidityPropertyInfo), '("webkit-region-overset", DOMElementWebkitRegionOversetPropertyInfo), '("webkitdropzone", DOMHTMLElementWebkitdropzonePropertyInfo), '("will-validate", DOMHTMLKeygenElementWillValidatePropertyInfo)] -- VVV Prop "type" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLLIElementType :: (MonadIO m, DOMHTMLLIElementK o) => o -> m T.Text getDOMHTMLLIElementType obj = liftIO $ getObjectPropertyString obj "type" setDOMHTMLLIElementType :: (MonadIO m, DOMHTMLLIElementK o) => o -> T.Text -> m () setDOMHTMLLIElementType obj val = liftIO $ setObjectPropertyString obj "type" val constructDOMHTMLLIElementType :: T.Text -> IO ([Char], GValue) constructDOMHTMLLIElementType val = constructObjectPropertyString "type" val data DOMHTMLLIElementTypePropertyInfo instance AttrInfo DOMHTMLLIElementTypePropertyInfo where type AttrAllowedOps DOMHTMLLIElementTypePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLLIElementTypePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLLIElementTypePropertyInfo = DOMHTMLLIElementK type AttrGetType DOMHTMLLIElementTypePropertyInfo = T.Text type AttrLabel DOMHTMLLIElementTypePropertyInfo = "DOMHTMLLIElement::type" attrGet _ = getDOMHTMLLIElementType attrSet _ = setDOMHTMLLIElementType attrConstruct _ = constructDOMHTMLLIElementType -- VVV Prop "value" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLLIElementValue :: (MonadIO m, DOMHTMLLIElementK o) => o -> m Int64 getDOMHTMLLIElementValue obj = liftIO $ getObjectPropertyInt64 obj "value" setDOMHTMLLIElementValue :: (MonadIO m, DOMHTMLLIElementK o) => o -> Int64 -> m () setDOMHTMLLIElementValue obj val = liftIO $ setObjectPropertyInt64 obj "value" val constructDOMHTMLLIElementValue :: Int64 -> IO ([Char], GValue) constructDOMHTMLLIElementValue val = constructObjectPropertyInt64 "value" val data DOMHTMLLIElementValuePropertyInfo instance AttrInfo DOMHTMLLIElementValuePropertyInfo where type AttrAllowedOps DOMHTMLLIElementValuePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLLIElementValuePropertyInfo = (~) Int64 type AttrBaseTypeConstraint DOMHTMLLIElementValuePropertyInfo = DOMHTMLLIElementK type AttrGetType DOMHTMLLIElementValuePropertyInfo = Int64 type AttrLabel DOMHTMLLIElementValuePropertyInfo = "DOMHTMLLIElement::value" attrGet _ = getDOMHTMLLIElementValue attrSet _ = setDOMHTMLLIElementValue attrConstruct _ = constructDOMHTMLLIElementValue type instance AttributeList DOMHTMLLIElement = '[ '("access-key", DOMHTMLElementAccessKeyPropertyInfo), '("attributes", DOMElementAttributesPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("child-element-count", DOMElementChildElementCountPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("children", DOMHTMLElementChildrenPropertyInfo), '("class-list", DOMElementClassListPropertyInfo), '("class-name", DOMElementClassNamePropertyInfo), '("client-height", DOMElementClientHeightPropertyInfo), '("client-left", DOMElementClientLeftPropertyInfo), '("client-top", DOMElementClientTopPropertyInfo), '("client-width", DOMElementClientWidthPropertyInfo), '("content-editable", DOMHTMLElementContentEditablePropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("dir", DOMHTMLElementDirPropertyInfo), '("draggable", DOMHTMLElementDraggablePropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("first-element-child", DOMElementFirstElementChildPropertyInfo), '("hidden", DOMHTMLElementHiddenPropertyInfo), '("id", DOMElementIdPropertyInfo), '("inner-html", DOMHTMLElementInnerHtmlPropertyInfo), '("inner-text", DOMHTMLElementInnerTextPropertyInfo), '("is-content-editable", DOMHTMLElementIsContentEditablePropertyInfo), '("lang", DOMHTMLElementLangPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-element-child", DOMElementLastElementChildPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-element-sibling", DOMElementNextElementSiblingPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("offset-height", DOMElementOffsetHeightPropertyInfo), '("offset-left", DOMElementOffsetLeftPropertyInfo), '("offset-parent", DOMElementOffsetParentPropertyInfo), '("offset-top", DOMElementOffsetTopPropertyInfo), '("offset-width", DOMElementOffsetWidthPropertyInfo), '("outer-html", DOMHTMLElementOuterHtmlPropertyInfo), '("outer-text", DOMHTMLElementOuterTextPropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-element-sibling", DOMElementPreviousElementSiblingPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("scroll-height", DOMElementScrollHeightPropertyInfo), '("scroll-left", DOMElementScrollLeftPropertyInfo), '("scroll-top", DOMElementScrollTopPropertyInfo), '("scroll-width", DOMElementScrollWidthPropertyInfo), '("spellcheck", DOMHTMLElementSpellcheckPropertyInfo), '("style", DOMElementStylePropertyInfo), '("tab-index", DOMHTMLElementTabIndexPropertyInfo), '("tag-name", DOMElementTagNamePropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("title", DOMHTMLElementTitlePropertyInfo), '("translate", DOMHTMLElementTranslatePropertyInfo), '("type", DOMHTMLLIElementTypePropertyInfo), '("value", DOMHTMLLIElementValuePropertyInfo), '("webkit-region-overset", DOMElementWebkitRegionOversetPropertyInfo), '("webkitdropzone", DOMHTMLElementWebkitdropzonePropertyInfo)] -- VVV Prop "control" -- Type: TInterface "WebKit" "DOMHTMLElement" -- Flags: [PropertyReadable] getDOMHTMLLabelElementControl :: (MonadIO m, DOMHTMLLabelElementK o) => o -> m DOMHTMLElement getDOMHTMLLabelElementControl obj = liftIO $ getObjectPropertyObject obj "control" DOMHTMLElement data DOMHTMLLabelElementControlPropertyInfo instance AttrInfo DOMHTMLLabelElementControlPropertyInfo where type AttrAllowedOps DOMHTMLLabelElementControlPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLLabelElementControlPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLLabelElementControlPropertyInfo = DOMHTMLLabelElementK type AttrGetType DOMHTMLLabelElementControlPropertyInfo = DOMHTMLElement type AttrLabel DOMHTMLLabelElementControlPropertyInfo = "DOMHTMLLabelElement::control" attrGet _ = getDOMHTMLLabelElementControl attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "form" -- Type: TInterface "WebKit" "DOMHTMLFormElement" -- Flags: [PropertyReadable] getDOMHTMLLabelElementForm :: (MonadIO m, DOMHTMLLabelElementK o) => o -> m DOMHTMLFormElement getDOMHTMLLabelElementForm obj = liftIO $ getObjectPropertyObject obj "form" DOMHTMLFormElement data DOMHTMLLabelElementFormPropertyInfo instance AttrInfo DOMHTMLLabelElementFormPropertyInfo where type AttrAllowedOps DOMHTMLLabelElementFormPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLLabelElementFormPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLLabelElementFormPropertyInfo = DOMHTMLLabelElementK type AttrGetType DOMHTMLLabelElementFormPropertyInfo = DOMHTMLFormElement type AttrLabel DOMHTMLLabelElementFormPropertyInfo = "DOMHTMLLabelElement::form" attrGet _ = getDOMHTMLLabelElementForm attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "html-for" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLLabelElementHtmlFor :: (MonadIO m, DOMHTMLLabelElementK o) => o -> m T.Text getDOMHTMLLabelElementHtmlFor obj = liftIO $ getObjectPropertyString obj "html-for" setDOMHTMLLabelElementHtmlFor :: (MonadIO m, DOMHTMLLabelElementK o) => o -> T.Text -> m () setDOMHTMLLabelElementHtmlFor obj val = liftIO $ setObjectPropertyString obj "html-for" val constructDOMHTMLLabelElementHtmlFor :: T.Text -> IO ([Char], GValue) constructDOMHTMLLabelElementHtmlFor val = constructObjectPropertyString "html-for" val data DOMHTMLLabelElementHtmlForPropertyInfo instance AttrInfo DOMHTMLLabelElementHtmlForPropertyInfo where type AttrAllowedOps DOMHTMLLabelElementHtmlForPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLLabelElementHtmlForPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLLabelElementHtmlForPropertyInfo = DOMHTMLLabelElementK type AttrGetType DOMHTMLLabelElementHtmlForPropertyInfo = T.Text type AttrLabel DOMHTMLLabelElementHtmlForPropertyInfo = "DOMHTMLLabelElement::html-for" attrGet _ = getDOMHTMLLabelElementHtmlFor attrSet _ = setDOMHTMLLabelElementHtmlFor attrConstruct _ = constructDOMHTMLLabelElementHtmlFor type instance AttributeList DOMHTMLLabelElement = '[ '("access-key", DOMHTMLElementAccessKeyPropertyInfo), '("attributes", DOMElementAttributesPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("child-element-count", DOMElementChildElementCountPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("children", DOMHTMLElementChildrenPropertyInfo), '("class-list", DOMElementClassListPropertyInfo), '("class-name", DOMElementClassNamePropertyInfo), '("client-height", DOMElementClientHeightPropertyInfo), '("client-left", DOMElementClientLeftPropertyInfo), '("client-top", DOMElementClientTopPropertyInfo), '("client-width", DOMElementClientWidthPropertyInfo), '("content-editable", DOMHTMLElementContentEditablePropertyInfo), '("control", DOMHTMLLabelElementControlPropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("dir", DOMHTMLElementDirPropertyInfo), '("draggable", DOMHTMLElementDraggablePropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("first-element-child", DOMElementFirstElementChildPropertyInfo), '("form", DOMHTMLLabelElementFormPropertyInfo), '("hidden", DOMHTMLElementHiddenPropertyInfo), '("html-for", DOMHTMLLabelElementHtmlForPropertyInfo), '("id", DOMElementIdPropertyInfo), '("inner-html", DOMHTMLElementInnerHtmlPropertyInfo), '("inner-text", DOMHTMLElementInnerTextPropertyInfo), '("is-content-editable", DOMHTMLElementIsContentEditablePropertyInfo), '("lang", DOMHTMLElementLangPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-element-child", DOMElementLastElementChildPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-element-sibling", DOMElementNextElementSiblingPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("offset-height", DOMElementOffsetHeightPropertyInfo), '("offset-left", DOMElementOffsetLeftPropertyInfo), '("offset-parent", DOMElementOffsetParentPropertyInfo), '("offset-top", DOMElementOffsetTopPropertyInfo), '("offset-width", DOMElementOffsetWidthPropertyInfo), '("outer-html", DOMHTMLElementOuterHtmlPropertyInfo), '("outer-text", DOMHTMLElementOuterTextPropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-element-sibling", DOMElementPreviousElementSiblingPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("scroll-height", DOMElementScrollHeightPropertyInfo), '("scroll-left", DOMElementScrollLeftPropertyInfo), '("scroll-top", DOMElementScrollTopPropertyInfo), '("scroll-width", DOMElementScrollWidthPropertyInfo), '("spellcheck", DOMHTMLElementSpellcheckPropertyInfo), '("style", DOMElementStylePropertyInfo), '("tab-index", DOMHTMLElementTabIndexPropertyInfo), '("tag-name", DOMElementTagNamePropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("title", DOMHTMLElementTitlePropertyInfo), '("translate", DOMHTMLElementTranslatePropertyInfo), '("webkit-region-overset", DOMElementWebkitRegionOversetPropertyInfo), '("webkitdropzone", DOMHTMLElementWebkitdropzonePropertyInfo)] -- VVV Prop "align" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLLegendElementAlign :: (MonadIO m, DOMHTMLLegendElementK o) => o -> m T.Text getDOMHTMLLegendElementAlign obj = liftIO $ getObjectPropertyString obj "align" setDOMHTMLLegendElementAlign :: (MonadIO m, DOMHTMLLegendElementK o) => o -> T.Text -> m () setDOMHTMLLegendElementAlign obj val = liftIO $ setObjectPropertyString obj "align" val constructDOMHTMLLegendElementAlign :: T.Text -> IO ([Char], GValue) constructDOMHTMLLegendElementAlign val = constructObjectPropertyString "align" val data DOMHTMLLegendElementAlignPropertyInfo instance AttrInfo DOMHTMLLegendElementAlignPropertyInfo where type AttrAllowedOps DOMHTMLLegendElementAlignPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLLegendElementAlignPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLLegendElementAlignPropertyInfo = DOMHTMLLegendElementK type AttrGetType DOMHTMLLegendElementAlignPropertyInfo = T.Text type AttrLabel DOMHTMLLegendElementAlignPropertyInfo = "DOMHTMLLegendElement::align" attrGet _ = getDOMHTMLLegendElementAlign attrSet _ = setDOMHTMLLegendElementAlign attrConstruct _ = constructDOMHTMLLegendElementAlign -- VVV Prop "form" -- Type: TInterface "WebKit" "DOMHTMLFormElement" -- Flags: [PropertyReadable] getDOMHTMLLegendElementForm :: (MonadIO m, DOMHTMLLegendElementK o) => o -> m DOMHTMLFormElement getDOMHTMLLegendElementForm obj = liftIO $ getObjectPropertyObject obj "form" DOMHTMLFormElement data DOMHTMLLegendElementFormPropertyInfo instance AttrInfo DOMHTMLLegendElementFormPropertyInfo where type AttrAllowedOps DOMHTMLLegendElementFormPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLLegendElementFormPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLLegendElementFormPropertyInfo = DOMHTMLLegendElementK type AttrGetType DOMHTMLLegendElementFormPropertyInfo = DOMHTMLFormElement type AttrLabel DOMHTMLLegendElementFormPropertyInfo = "DOMHTMLLegendElement::form" attrGet _ = getDOMHTMLLegendElementForm attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMHTMLLegendElement = '[ '("access-key", DOMHTMLElementAccessKeyPropertyInfo), '("align", DOMHTMLLegendElementAlignPropertyInfo), '("attributes", DOMElementAttributesPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("child-element-count", DOMElementChildElementCountPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("children", DOMHTMLElementChildrenPropertyInfo), '("class-list", DOMElementClassListPropertyInfo), '("class-name", DOMElementClassNamePropertyInfo), '("client-height", DOMElementClientHeightPropertyInfo), '("client-left", DOMElementClientLeftPropertyInfo), '("client-top", DOMElementClientTopPropertyInfo), '("client-width", DOMElementClientWidthPropertyInfo), '("content-editable", DOMHTMLElementContentEditablePropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("dir", DOMHTMLElementDirPropertyInfo), '("draggable", DOMHTMLElementDraggablePropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("first-element-child", DOMElementFirstElementChildPropertyInfo), '("form", DOMHTMLLegendElementFormPropertyInfo), '("hidden", DOMHTMLElementHiddenPropertyInfo), '("id", DOMElementIdPropertyInfo), '("inner-html", DOMHTMLElementInnerHtmlPropertyInfo), '("inner-text", DOMHTMLElementInnerTextPropertyInfo), '("is-content-editable", DOMHTMLElementIsContentEditablePropertyInfo), '("lang", DOMHTMLElementLangPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-element-child", DOMElementLastElementChildPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-element-sibling", DOMElementNextElementSiblingPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("offset-height", DOMElementOffsetHeightPropertyInfo), '("offset-left", DOMElementOffsetLeftPropertyInfo), '("offset-parent", DOMElementOffsetParentPropertyInfo), '("offset-top", DOMElementOffsetTopPropertyInfo), '("offset-width", DOMElementOffsetWidthPropertyInfo), '("outer-html", DOMHTMLElementOuterHtmlPropertyInfo), '("outer-text", DOMHTMLElementOuterTextPropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-element-sibling", DOMElementPreviousElementSiblingPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("scroll-height", DOMElementScrollHeightPropertyInfo), '("scroll-left", DOMElementScrollLeftPropertyInfo), '("scroll-top", DOMElementScrollTopPropertyInfo), '("scroll-width", DOMElementScrollWidthPropertyInfo), '("spellcheck", DOMHTMLElementSpellcheckPropertyInfo), '("style", DOMElementStylePropertyInfo), '("tab-index", DOMHTMLElementTabIndexPropertyInfo), '("tag-name", DOMElementTagNamePropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("title", DOMHTMLElementTitlePropertyInfo), '("translate", DOMHTMLElementTranslatePropertyInfo), '("webkit-region-overset", DOMElementWebkitRegionOversetPropertyInfo), '("webkitdropzone", DOMHTMLElementWebkitdropzonePropertyInfo)] -- VVV Prop "charset" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLLinkElementCharset :: (MonadIO m, DOMHTMLLinkElementK o) => o -> m T.Text getDOMHTMLLinkElementCharset obj = liftIO $ getObjectPropertyString obj "charset" setDOMHTMLLinkElementCharset :: (MonadIO m, DOMHTMLLinkElementK o) => o -> T.Text -> m () setDOMHTMLLinkElementCharset obj val = liftIO $ setObjectPropertyString obj "charset" val constructDOMHTMLLinkElementCharset :: T.Text -> IO ([Char], GValue) constructDOMHTMLLinkElementCharset val = constructObjectPropertyString "charset" val data DOMHTMLLinkElementCharsetPropertyInfo instance AttrInfo DOMHTMLLinkElementCharsetPropertyInfo where type AttrAllowedOps DOMHTMLLinkElementCharsetPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLLinkElementCharsetPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLLinkElementCharsetPropertyInfo = DOMHTMLLinkElementK type AttrGetType DOMHTMLLinkElementCharsetPropertyInfo = T.Text type AttrLabel DOMHTMLLinkElementCharsetPropertyInfo = "DOMHTMLLinkElement::charset" attrGet _ = getDOMHTMLLinkElementCharset attrSet _ = setDOMHTMLLinkElementCharset attrConstruct _ = constructDOMHTMLLinkElementCharset -- VVV Prop "disabled" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLLinkElementDisabled :: (MonadIO m, DOMHTMLLinkElementK o) => o -> m Bool getDOMHTMLLinkElementDisabled obj = liftIO $ getObjectPropertyBool obj "disabled" setDOMHTMLLinkElementDisabled :: (MonadIO m, DOMHTMLLinkElementK o) => o -> Bool -> m () setDOMHTMLLinkElementDisabled obj val = liftIO $ setObjectPropertyBool obj "disabled" val constructDOMHTMLLinkElementDisabled :: Bool -> IO ([Char], GValue) constructDOMHTMLLinkElementDisabled val = constructObjectPropertyBool "disabled" val data DOMHTMLLinkElementDisabledPropertyInfo instance AttrInfo DOMHTMLLinkElementDisabledPropertyInfo where type AttrAllowedOps DOMHTMLLinkElementDisabledPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLLinkElementDisabledPropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLLinkElementDisabledPropertyInfo = DOMHTMLLinkElementK type AttrGetType DOMHTMLLinkElementDisabledPropertyInfo = Bool type AttrLabel DOMHTMLLinkElementDisabledPropertyInfo = "DOMHTMLLinkElement::disabled" attrGet _ = getDOMHTMLLinkElementDisabled attrSet _ = setDOMHTMLLinkElementDisabled attrConstruct _ = constructDOMHTMLLinkElementDisabled -- VVV Prop "href" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLLinkElementHref :: (MonadIO m, DOMHTMLLinkElementK o) => o -> m T.Text getDOMHTMLLinkElementHref obj = liftIO $ getObjectPropertyString obj "href" setDOMHTMLLinkElementHref :: (MonadIO m, DOMHTMLLinkElementK o) => o -> T.Text -> m () setDOMHTMLLinkElementHref obj val = liftIO $ setObjectPropertyString obj "href" val constructDOMHTMLLinkElementHref :: T.Text -> IO ([Char], GValue) constructDOMHTMLLinkElementHref val = constructObjectPropertyString "href" val data DOMHTMLLinkElementHrefPropertyInfo instance AttrInfo DOMHTMLLinkElementHrefPropertyInfo where type AttrAllowedOps DOMHTMLLinkElementHrefPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLLinkElementHrefPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLLinkElementHrefPropertyInfo = DOMHTMLLinkElementK type AttrGetType DOMHTMLLinkElementHrefPropertyInfo = T.Text type AttrLabel DOMHTMLLinkElementHrefPropertyInfo = "DOMHTMLLinkElement::href" attrGet _ = getDOMHTMLLinkElementHref attrSet _ = setDOMHTMLLinkElementHref attrConstruct _ = constructDOMHTMLLinkElementHref -- VVV Prop "hreflang" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLLinkElementHreflang :: (MonadIO m, DOMHTMLLinkElementK o) => o -> m T.Text getDOMHTMLLinkElementHreflang obj = liftIO $ getObjectPropertyString obj "hreflang" setDOMHTMLLinkElementHreflang :: (MonadIO m, DOMHTMLLinkElementK o) => o -> T.Text -> m () setDOMHTMLLinkElementHreflang obj val = liftIO $ setObjectPropertyString obj "hreflang" val constructDOMHTMLLinkElementHreflang :: T.Text -> IO ([Char], GValue) constructDOMHTMLLinkElementHreflang val = constructObjectPropertyString "hreflang" val data DOMHTMLLinkElementHreflangPropertyInfo instance AttrInfo DOMHTMLLinkElementHreflangPropertyInfo where type AttrAllowedOps DOMHTMLLinkElementHreflangPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLLinkElementHreflangPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLLinkElementHreflangPropertyInfo = DOMHTMLLinkElementK type AttrGetType DOMHTMLLinkElementHreflangPropertyInfo = T.Text type AttrLabel DOMHTMLLinkElementHreflangPropertyInfo = "DOMHTMLLinkElement::hreflang" attrGet _ = getDOMHTMLLinkElementHreflang attrSet _ = setDOMHTMLLinkElementHreflang attrConstruct _ = constructDOMHTMLLinkElementHreflang -- VVV Prop "media" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLLinkElementMedia :: (MonadIO m, DOMHTMLLinkElementK o) => o -> m T.Text getDOMHTMLLinkElementMedia obj = liftIO $ getObjectPropertyString obj "media" setDOMHTMLLinkElementMedia :: (MonadIO m, DOMHTMLLinkElementK o) => o -> T.Text -> m () setDOMHTMLLinkElementMedia obj val = liftIO $ setObjectPropertyString obj "media" val constructDOMHTMLLinkElementMedia :: T.Text -> IO ([Char], GValue) constructDOMHTMLLinkElementMedia val = constructObjectPropertyString "media" val data DOMHTMLLinkElementMediaPropertyInfo instance AttrInfo DOMHTMLLinkElementMediaPropertyInfo where type AttrAllowedOps DOMHTMLLinkElementMediaPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLLinkElementMediaPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLLinkElementMediaPropertyInfo = DOMHTMLLinkElementK type AttrGetType DOMHTMLLinkElementMediaPropertyInfo = T.Text type AttrLabel DOMHTMLLinkElementMediaPropertyInfo = "DOMHTMLLinkElement::media" attrGet _ = getDOMHTMLLinkElementMedia attrSet _ = setDOMHTMLLinkElementMedia attrConstruct _ = constructDOMHTMLLinkElementMedia -- VVV Prop "rel" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLLinkElementRel :: (MonadIO m, DOMHTMLLinkElementK o) => o -> m T.Text getDOMHTMLLinkElementRel obj = liftIO $ getObjectPropertyString obj "rel" setDOMHTMLLinkElementRel :: (MonadIO m, DOMHTMLLinkElementK o) => o -> T.Text -> m () setDOMHTMLLinkElementRel obj val = liftIO $ setObjectPropertyString obj "rel" val constructDOMHTMLLinkElementRel :: T.Text -> IO ([Char], GValue) constructDOMHTMLLinkElementRel val = constructObjectPropertyString "rel" val data DOMHTMLLinkElementRelPropertyInfo instance AttrInfo DOMHTMLLinkElementRelPropertyInfo where type AttrAllowedOps DOMHTMLLinkElementRelPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLLinkElementRelPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLLinkElementRelPropertyInfo = DOMHTMLLinkElementK type AttrGetType DOMHTMLLinkElementRelPropertyInfo = T.Text type AttrLabel DOMHTMLLinkElementRelPropertyInfo = "DOMHTMLLinkElement::rel" attrGet _ = getDOMHTMLLinkElementRel attrSet _ = setDOMHTMLLinkElementRel attrConstruct _ = constructDOMHTMLLinkElementRel -- VVV Prop "rev" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLLinkElementRev :: (MonadIO m, DOMHTMLLinkElementK o) => o -> m T.Text getDOMHTMLLinkElementRev obj = liftIO $ getObjectPropertyString obj "rev" setDOMHTMLLinkElementRev :: (MonadIO m, DOMHTMLLinkElementK o) => o -> T.Text -> m () setDOMHTMLLinkElementRev obj val = liftIO $ setObjectPropertyString obj "rev" val constructDOMHTMLLinkElementRev :: T.Text -> IO ([Char], GValue) constructDOMHTMLLinkElementRev val = constructObjectPropertyString "rev" val data DOMHTMLLinkElementRevPropertyInfo instance AttrInfo DOMHTMLLinkElementRevPropertyInfo where type AttrAllowedOps DOMHTMLLinkElementRevPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLLinkElementRevPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLLinkElementRevPropertyInfo = DOMHTMLLinkElementK type AttrGetType DOMHTMLLinkElementRevPropertyInfo = T.Text type AttrLabel DOMHTMLLinkElementRevPropertyInfo = "DOMHTMLLinkElement::rev" attrGet _ = getDOMHTMLLinkElementRev attrSet _ = setDOMHTMLLinkElementRev attrConstruct _ = constructDOMHTMLLinkElementRev -- VVV Prop "sheet" -- Type: TInterface "WebKit" "DOMStyleSheet" -- Flags: [PropertyReadable] getDOMHTMLLinkElementSheet :: (MonadIO m, DOMHTMLLinkElementK o) => o -> m DOMStyleSheet getDOMHTMLLinkElementSheet obj = liftIO $ getObjectPropertyObject obj "sheet" DOMStyleSheet data DOMHTMLLinkElementSheetPropertyInfo instance AttrInfo DOMHTMLLinkElementSheetPropertyInfo where type AttrAllowedOps DOMHTMLLinkElementSheetPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLLinkElementSheetPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLLinkElementSheetPropertyInfo = DOMHTMLLinkElementK type AttrGetType DOMHTMLLinkElementSheetPropertyInfo = DOMStyleSheet type AttrLabel DOMHTMLLinkElementSheetPropertyInfo = "DOMHTMLLinkElement::sheet" attrGet _ = getDOMHTMLLinkElementSheet attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "target" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLLinkElementTarget :: (MonadIO m, DOMHTMLLinkElementK o) => o -> m T.Text getDOMHTMLLinkElementTarget obj = liftIO $ getObjectPropertyString obj "target" setDOMHTMLLinkElementTarget :: (MonadIO m, DOMHTMLLinkElementK o) => o -> T.Text -> m () setDOMHTMLLinkElementTarget obj val = liftIO $ setObjectPropertyString obj "target" val constructDOMHTMLLinkElementTarget :: T.Text -> IO ([Char], GValue) constructDOMHTMLLinkElementTarget val = constructObjectPropertyString "target" val data DOMHTMLLinkElementTargetPropertyInfo instance AttrInfo DOMHTMLLinkElementTargetPropertyInfo where type AttrAllowedOps DOMHTMLLinkElementTargetPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLLinkElementTargetPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLLinkElementTargetPropertyInfo = DOMHTMLLinkElementK type AttrGetType DOMHTMLLinkElementTargetPropertyInfo = T.Text type AttrLabel DOMHTMLLinkElementTargetPropertyInfo = "DOMHTMLLinkElement::target" attrGet _ = getDOMHTMLLinkElementTarget attrSet _ = setDOMHTMLLinkElementTarget attrConstruct _ = constructDOMHTMLLinkElementTarget -- VVV Prop "type" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLLinkElementType :: (MonadIO m, DOMHTMLLinkElementK o) => o -> m T.Text getDOMHTMLLinkElementType obj = liftIO $ getObjectPropertyString obj "type" setDOMHTMLLinkElementType :: (MonadIO m, DOMHTMLLinkElementK o) => o -> T.Text -> m () setDOMHTMLLinkElementType obj val = liftIO $ setObjectPropertyString obj "type" val constructDOMHTMLLinkElementType :: T.Text -> IO ([Char], GValue) constructDOMHTMLLinkElementType val = constructObjectPropertyString "type" val data DOMHTMLLinkElementTypePropertyInfo instance AttrInfo DOMHTMLLinkElementTypePropertyInfo where type AttrAllowedOps DOMHTMLLinkElementTypePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLLinkElementTypePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLLinkElementTypePropertyInfo = DOMHTMLLinkElementK type AttrGetType DOMHTMLLinkElementTypePropertyInfo = T.Text type AttrLabel DOMHTMLLinkElementTypePropertyInfo = "DOMHTMLLinkElement::type" attrGet _ = getDOMHTMLLinkElementType attrSet _ = setDOMHTMLLinkElementType attrConstruct _ = constructDOMHTMLLinkElementType type instance AttributeList DOMHTMLLinkElement = '[ '("access-key", DOMHTMLElementAccessKeyPropertyInfo), '("attributes", DOMElementAttributesPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("charset", DOMHTMLLinkElementCharsetPropertyInfo), '("child-element-count", DOMElementChildElementCountPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("children", DOMHTMLElementChildrenPropertyInfo), '("class-list", DOMElementClassListPropertyInfo), '("class-name", DOMElementClassNamePropertyInfo), '("client-height", DOMElementClientHeightPropertyInfo), '("client-left", DOMElementClientLeftPropertyInfo), '("client-top", DOMElementClientTopPropertyInfo), '("client-width", DOMElementClientWidthPropertyInfo), '("content-editable", DOMHTMLElementContentEditablePropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("dir", DOMHTMLElementDirPropertyInfo), '("disabled", DOMHTMLLinkElementDisabledPropertyInfo), '("draggable", DOMHTMLElementDraggablePropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("first-element-child", DOMElementFirstElementChildPropertyInfo), '("hidden", DOMHTMLElementHiddenPropertyInfo), '("href", DOMHTMLLinkElementHrefPropertyInfo), '("hreflang", DOMHTMLLinkElementHreflangPropertyInfo), '("id", DOMElementIdPropertyInfo), '("inner-html", DOMHTMLElementInnerHtmlPropertyInfo), '("inner-text", DOMHTMLElementInnerTextPropertyInfo), '("is-content-editable", DOMHTMLElementIsContentEditablePropertyInfo), '("lang", DOMHTMLElementLangPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-element-child", DOMElementLastElementChildPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("media", DOMHTMLLinkElementMediaPropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-element-sibling", DOMElementNextElementSiblingPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("offset-height", DOMElementOffsetHeightPropertyInfo), '("offset-left", DOMElementOffsetLeftPropertyInfo), '("offset-parent", DOMElementOffsetParentPropertyInfo), '("offset-top", DOMElementOffsetTopPropertyInfo), '("offset-width", DOMElementOffsetWidthPropertyInfo), '("outer-html", DOMHTMLElementOuterHtmlPropertyInfo), '("outer-text", DOMHTMLElementOuterTextPropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-element-sibling", DOMElementPreviousElementSiblingPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("rel", DOMHTMLLinkElementRelPropertyInfo), '("rev", DOMHTMLLinkElementRevPropertyInfo), '("scroll-height", DOMElementScrollHeightPropertyInfo), '("scroll-left", DOMElementScrollLeftPropertyInfo), '("scroll-top", DOMElementScrollTopPropertyInfo), '("scroll-width", DOMElementScrollWidthPropertyInfo), '("sheet", DOMHTMLLinkElementSheetPropertyInfo), '("spellcheck", DOMHTMLElementSpellcheckPropertyInfo), '("style", DOMElementStylePropertyInfo), '("tab-index", DOMHTMLElementTabIndexPropertyInfo), '("tag-name", DOMElementTagNamePropertyInfo), '("target", DOMHTMLLinkElementTargetPropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("title", DOMHTMLElementTitlePropertyInfo), '("translate", DOMHTMLElementTranslatePropertyInfo), '("type", DOMHTMLLinkElementTypePropertyInfo), '("webkit-region-overset", DOMElementWebkitRegionOversetPropertyInfo), '("webkitdropzone", DOMHTMLElementWebkitdropzonePropertyInfo)] -- VVV Prop "areas" -- Type: TInterface "WebKit" "DOMHTMLCollection" -- Flags: [PropertyReadable] getDOMHTMLMapElementAreas :: (MonadIO m, DOMHTMLMapElementK o) => o -> m DOMHTMLCollection getDOMHTMLMapElementAreas obj = liftIO $ getObjectPropertyObject obj "areas" DOMHTMLCollection data DOMHTMLMapElementAreasPropertyInfo instance AttrInfo DOMHTMLMapElementAreasPropertyInfo where type AttrAllowedOps DOMHTMLMapElementAreasPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLMapElementAreasPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLMapElementAreasPropertyInfo = DOMHTMLMapElementK type AttrGetType DOMHTMLMapElementAreasPropertyInfo = DOMHTMLCollection type AttrLabel DOMHTMLMapElementAreasPropertyInfo = "DOMHTMLMapElement::areas" attrGet _ = getDOMHTMLMapElementAreas attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "name" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLMapElementName :: (MonadIO m, DOMHTMLMapElementK o) => o -> m T.Text getDOMHTMLMapElementName obj = liftIO $ getObjectPropertyString obj "name" setDOMHTMLMapElementName :: (MonadIO m, DOMHTMLMapElementK o) => o -> T.Text -> m () setDOMHTMLMapElementName obj val = liftIO $ setObjectPropertyString obj "name" val constructDOMHTMLMapElementName :: T.Text -> IO ([Char], GValue) constructDOMHTMLMapElementName val = constructObjectPropertyString "name" val data DOMHTMLMapElementNamePropertyInfo instance AttrInfo DOMHTMLMapElementNamePropertyInfo where type AttrAllowedOps DOMHTMLMapElementNamePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLMapElementNamePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLMapElementNamePropertyInfo = DOMHTMLMapElementK type AttrGetType DOMHTMLMapElementNamePropertyInfo = T.Text type AttrLabel DOMHTMLMapElementNamePropertyInfo = "DOMHTMLMapElement::name" attrGet _ = getDOMHTMLMapElementName attrSet _ = setDOMHTMLMapElementName attrConstruct _ = constructDOMHTMLMapElementName type instance AttributeList DOMHTMLMapElement = '[ '("access-key", DOMHTMLElementAccessKeyPropertyInfo), '("areas", DOMHTMLMapElementAreasPropertyInfo), '("attributes", DOMElementAttributesPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("child-element-count", DOMElementChildElementCountPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("children", DOMHTMLElementChildrenPropertyInfo), '("class-list", DOMElementClassListPropertyInfo), '("class-name", DOMElementClassNamePropertyInfo), '("client-height", DOMElementClientHeightPropertyInfo), '("client-left", DOMElementClientLeftPropertyInfo), '("client-top", DOMElementClientTopPropertyInfo), '("client-width", DOMElementClientWidthPropertyInfo), '("content-editable", DOMHTMLElementContentEditablePropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("dir", DOMHTMLElementDirPropertyInfo), '("draggable", DOMHTMLElementDraggablePropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("first-element-child", DOMElementFirstElementChildPropertyInfo), '("hidden", DOMHTMLElementHiddenPropertyInfo), '("id", DOMElementIdPropertyInfo), '("inner-html", DOMHTMLElementInnerHtmlPropertyInfo), '("inner-text", DOMHTMLElementInnerTextPropertyInfo), '("is-content-editable", DOMHTMLElementIsContentEditablePropertyInfo), '("lang", DOMHTMLElementLangPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-element-child", DOMElementLastElementChildPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("name", DOMHTMLMapElementNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-element-sibling", DOMElementNextElementSiblingPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("offset-height", DOMElementOffsetHeightPropertyInfo), '("offset-left", DOMElementOffsetLeftPropertyInfo), '("offset-parent", DOMElementOffsetParentPropertyInfo), '("offset-top", DOMElementOffsetTopPropertyInfo), '("offset-width", DOMElementOffsetWidthPropertyInfo), '("outer-html", DOMHTMLElementOuterHtmlPropertyInfo), '("outer-text", DOMHTMLElementOuterTextPropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-element-sibling", DOMElementPreviousElementSiblingPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("scroll-height", DOMElementScrollHeightPropertyInfo), '("scroll-left", DOMElementScrollLeftPropertyInfo), '("scroll-top", DOMElementScrollTopPropertyInfo), '("scroll-width", DOMElementScrollWidthPropertyInfo), '("spellcheck", DOMHTMLElementSpellcheckPropertyInfo), '("style", DOMElementStylePropertyInfo), '("tab-index", DOMHTMLElementTabIndexPropertyInfo), '("tag-name", DOMElementTagNamePropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("title", DOMHTMLElementTitlePropertyInfo), '("translate", DOMHTMLElementTranslatePropertyInfo), '("webkit-region-overset", DOMElementWebkitRegionOversetPropertyInfo), '("webkitdropzone", DOMHTMLElementWebkitdropzonePropertyInfo)] -- VVV Prop "behavior" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLMarqueeElementBehavior :: (MonadIO m, DOMHTMLMarqueeElementK o) => o -> m T.Text getDOMHTMLMarqueeElementBehavior obj = liftIO $ getObjectPropertyString obj "behavior" setDOMHTMLMarqueeElementBehavior :: (MonadIO m, DOMHTMLMarqueeElementK o) => o -> T.Text -> m () setDOMHTMLMarqueeElementBehavior obj val = liftIO $ setObjectPropertyString obj "behavior" val constructDOMHTMLMarqueeElementBehavior :: T.Text -> IO ([Char], GValue) constructDOMHTMLMarqueeElementBehavior val = constructObjectPropertyString "behavior" val data DOMHTMLMarqueeElementBehaviorPropertyInfo instance AttrInfo DOMHTMLMarqueeElementBehaviorPropertyInfo where type AttrAllowedOps DOMHTMLMarqueeElementBehaviorPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLMarqueeElementBehaviorPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLMarqueeElementBehaviorPropertyInfo = DOMHTMLMarqueeElementK type AttrGetType DOMHTMLMarqueeElementBehaviorPropertyInfo = T.Text type AttrLabel DOMHTMLMarqueeElementBehaviorPropertyInfo = "DOMHTMLMarqueeElement::behavior" attrGet _ = getDOMHTMLMarqueeElementBehavior attrSet _ = setDOMHTMLMarqueeElementBehavior attrConstruct _ = constructDOMHTMLMarqueeElementBehavior -- VVV Prop "bg-color" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLMarqueeElementBgColor :: (MonadIO m, DOMHTMLMarqueeElementK o) => o -> m T.Text getDOMHTMLMarqueeElementBgColor obj = liftIO $ getObjectPropertyString obj "bg-color" setDOMHTMLMarqueeElementBgColor :: (MonadIO m, DOMHTMLMarqueeElementK o) => o -> T.Text -> m () setDOMHTMLMarqueeElementBgColor obj val = liftIO $ setObjectPropertyString obj "bg-color" val constructDOMHTMLMarqueeElementBgColor :: T.Text -> IO ([Char], GValue) constructDOMHTMLMarqueeElementBgColor val = constructObjectPropertyString "bg-color" val data DOMHTMLMarqueeElementBgColorPropertyInfo instance AttrInfo DOMHTMLMarqueeElementBgColorPropertyInfo where type AttrAllowedOps DOMHTMLMarqueeElementBgColorPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLMarqueeElementBgColorPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLMarqueeElementBgColorPropertyInfo = DOMHTMLMarqueeElementK type AttrGetType DOMHTMLMarqueeElementBgColorPropertyInfo = T.Text type AttrLabel DOMHTMLMarqueeElementBgColorPropertyInfo = "DOMHTMLMarqueeElement::bg-color" attrGet _ = getDOMHTMLMarqueeElementBgColor attrSet _ = setDOMHTMLMarqueeElementBgColor attrConstruct _ = constructDOMHTMLMarqueeElementBgColor -- VVV Prop "direction" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLMarqueeElementDirection :: (MonadIO m, DOMHTMLMarqueeElementK o) => o -> m T.Text getDOMHTMLMarqueeElementDirection obj = liftIO $ getObjectPropertyString obj "direction" setDOMHTMLMarqueeElementDirection :: (MonadIO m, DOMHTMLMarqueeElementK o) => o -> T.Text -> m () setDOMHTMLMarqueeElementDirection obj val = liftIO $ setObjectPropertyString obj "direction" val constructDOMHTMLMarqueeElementDirection :: T.Text -> IO ([Char], GValue) constructDOMHTMLMarqueeElementDirection val = constructObjectPropertyString "direction" val data DOMHTMLMarqueeElementDirectionPropertyInfo instance AttrInfo DOMHTMLMarqueeElementDirectionPropertyInfo where type AttrAllowedOps DOMHTMLMarqueeElementDirectionPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLMarqueeElementDirectionPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLMarqueeElementDirectionPropertyInfo = DOMHTMLMarqueeElementK type AttrGetType DOMHTMLMarqueeElementDirectionPropertyInfo = T.Text type AttrLabel DOMHTMLMarqueeElementDirectionPropertyInfo = "DOMHTMLMarqueeElement::direction" attrGet _ = getDOMHTMLMarqueeElementDirection attrSet _ = setDOMHTMLMarqueeElementDirection attrConstruct _ = constructDOMHTMLMarqueeElementDirection -- VVV Prop "height" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLMarqueeElementHeight :: (MonadIO m, DOMHTMLMarqueeElementK o) => o -> m T.Text getDOMHTMLMarqueeElementHeight obj = liftIO $ getObjectPropertyString obj "height" setDOMHTMLMarqueeElementHeight :: (MonadIO m, DOMHTMLMarqueeElementK o) => o -> T.Text -> m () setDOMHTMLMarqueeElementHeight obj val = liftIO $ setObjectPropertyString obj "height" val constructDOMHTMLMarqueeElementHeight :: T.Text -> IO ([Char], GValue) constructDOMHTMLMarqueeElementHeight val = constructObjectPropertyString "height" val data DOMHTMLMarqueeElementHeightPropertyInfo instance AttrInfo DOMHTMLMarqueeElementHeightPropertyInfo where type AttrAllowedOps DOMHTMLMarqueeElementHeightPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLMarqueeElementHeightPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLMarqueeElementHeightPropertyInfo = DOMHTMLMarqueeElementK type AttrGetType DOMHTMLMarqueeElementHeightPropertyInfo = T.Text type AttrLabel DOMHTMLMarqueeElementHeightPropertyInfo = "DOMHTMLMarqueeElement::height" attrGet _ = getDOMHTMLMarqueeElementHeight attrSet _ = setDOMHTMLMarqueeElementHeight attrConstruct _ = constructDOMHTMLMarqueeElementHeight -- VVV Prop "hspace" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLMarqueeElementHspace :: (MonadIO m, DOMHTMLMarqueeElementK o) => o -> m Word64 getDOMHTMLMarqueeElementHspace obj = liftIO $ getObjectPropertyUInt64 obj "hspace" setDOMHTMLMarqueeElementHspace :: (MonadIO m, DOMHTMLMarqueeElementK o) => o -> Word64 -> m () setDOMHTMLMarqueeElementHspace obj val = liftIO $ setObjectPropertyUInt64 obj "hspace" val constructDOMHTMLMarqueeElementHspace :: Word64 -> IO ([Char], GValue) constructDOMHTMLMarqueeElementHspace val = constructObjectPropertyUInt64 "hspace" val data DOMHTMLMarqueeElementHspacePropertyInfo instance AttrInfo DOMHTMLMarqueeElementHspacePropertyInfo where type AttrAllowedOps DOMHTMLMarqueeElementHspacePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLMarqueeElementHspacePropertyInfo = (~) Word64 type AttrBaseTypeConstraint DOMHTMLMarqueeElementHspacePropertyInfo = DOMHTMLMarqueeElementK type AttrGetType DOMHTMLMarqueeElementHspacePropertyInfo = Word64 type AttrLabel DOMHTMLMarqueeElementHspacePropertyInfo = "DOMHTMLMarqueeElement::hspace" attrGet _ = getDOMHTMLMarqueeElementHspace attrSet _ = setDOMHTMLMarqueeElementHspace attrConstruct _ = constructDOMHTMLMarqueeElementHspace -- VVV Prop "loop" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLMarqueeElementLoop :: (MonadIO m, DOMHTMLMarqueeElementK o) => o -> m Int64 getDOMHTMLMarqueeElementLoop obj = liftIO $ getObjectPropertyInt64 obj "loop" setDOMHTMLMarqueeElementLoop :: (MonadIO m, DOMHTMLMarqueeElementK o) => o -> Int64 -> m () setDOMHTMLMarqueeElementLoop obj val = liftIO $ setObjectPropertyInt64 obj "loop" val constructDOMHTMLMarqueeElementLoop :: Int64 -> IO ([Char], GValue) constructDOMHTMLMarqueeElementLoop val = constructObjectPropertyInt64 "loop" val data DOMHTMLMarqueeElementLoopPropertyInfo instance AttrInfo DOMHTMLMarqueeElementLoopPropertyInfo where type AttrAllowedOps DOMHTMLMarqueeElementLoopPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLMarqueeElementLoopPropertyInfo = (~) Int64 type AttrBaseTypeConstraint DOMHTMLMarqueeElementLoopPropertyInfo = DOMHTMLMarqueeElementK type AttrGetType DOMHTMLMarqueeElementLoopPropertyInfo = Int64 type AttrLabel DOMHTMLMarqueeElementLoopPropertyInfo = "DOMHTMLMarqueeElement::loop" attrGet _ = getDOMHTMLMarqueeElementLoop attrSet _ = setDOMHTMLMarqueeElementLoop attrConstruct _ = constructDOMHTMLMarqueeElementLoop -- VVV Prop "scroll-amount" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLMarqueeElementScrollAmount :: (MonadIO m, DOMHTMLMarqueeElementK o) => o -> m Int64 getDOMHTMLMarqueeElementScrollAmount obj = liftIO $ getObjectPropertyInt64 obj "scroll-amount" setDOMHTMLMarqueeElementScrollAmount :: (MonadIO m, DOMHTMLMarqueeElementK o) => o -> Int64 -> m () setDOMHTMLMarqueeElementScrollAmount obj val = liftIO $ setObjectPropertyInt64 obj "scroll-amount" val constructDOMHTMLMarqueeElementScrollAmount :: Int64 -> IO ([Char], GValue) constructDOMHTMLMarqueeElementScrollAmount val = constructObjectPropertyInt64 "scroll-amount" val data DOMHTMLMarqueeElementScrollAmountPropertyInfo instance AttrInfo DOMHTMLMarqueeElementScrollAmountPropertyInfo where type AttrAllowedOps DOMHTMLMarqueeElementScrollAmountPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLMarqueeElementScrollAmountPropertyInfo = (~) Int64 type AttrBaseTypeConstraint DOMHTMLMarqueeElementScrollAmountPropertyInfo = DOMHTMLMarqueeElementK type AttrGetType DOMHTMLMarqueeElementScrollAmountPropertyInfo = Int64 type AttrLabel DOMHTMLMarqueeElementScrollAmountPropertyInfo = "DOMHTMLMarqueeElement::scroll-amount" attrGet _ = getDOMHTMLMarqueeElementScrollAmount attrSet _ = setDOMHTMLMarqueeElementScrollAmount attrConstruct _ = constructDOMHTMLMarqueeElementScrollAmount -- VVV Prop "scroll-delay" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLMarqueeElementScrollDelay :: (MonadIO m, DOMHTMLMarqueeElementK o) => o -> m Int64 getDOMHTMLMarqueeElementScrollDelay obj = liftIO $ getObjectPropertyInt64 obj "scroll-delay" setDOMHTMLMarqueeElementScrollDelay :: (MonadIO m, DOMHTMLMarqueeElementK o) => o -> Int64 -> m () setDOMHTMLMarqueeElementScrollDelay obj val = liftIO $ setObjectPropertyInt64 obj "scroll-delay" val constructDOMHTMLMarqueeElementScrollDelay :: Int64 -> IO ([Char], GValue) constructDOMHTMLMarqueeElementScrollDelay val = constructObjectPropertyInt64 "scroll-delay" val data DOMHTMLMarqueeElementScrollDelayPropertyInfo instance AttrInfo DOMHTMLMarqueeElementScrollDelayPropertyInfo where type AttrAllowedOps DOMHTMLMarqueeElementScrollDelayPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLMarqueeElementScrollDelayPropertyInfo = (~) Int64 type AttrBaseTypeConstraint DOMHTMLMarqueeElementScrollDelayPropertyInfo = DOMHTMLMarqueeElementK type AttrGetType DOMHTMLMarqueeElementScrollDelayPropertyInfo = Int64 type AttrLabel DOMHTMLMarqueeElementScrollDelayPropertyInfo = "DOMHTMLMarqueeElement::scroll-delay" attrGet _ = getDOMHTMLMarqueeElementScrollDelay attrSet _ = setDOMHTMLMarqueeElementScrollDelay attrConstruct _ = constructDOMHTMLMarqueeElementScrollDelay -- VVV Prop "true-speed" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLMarqueeElementTrueSpeed :: (MonadIO m, DOMHTMLMarqueeElementK o) => o -> m Bool getDOMHTMLMarqueeElementTrueSpeed obj = liftIO $ getObjectPropertyBool obj "true-speed" setDOMHTMLMarqueeElementTrueSpeed :: (MonadIO m, DOMHTMLMarqueeElementK o) => o -> Bool -> m () setDOMHTMLMarqueeElementTrueSpeed obj val = liftIO $ setObjectPropertyBool obj "true-speed" val constructDOMHTMLMarqueeElementTrueSpeed :: Bool -> IO ([Char], GValue) constructDOMHTMLMarqueeElementTrueSpeed val = constructObjectPropertyBool "true-speed" val data DOMHTMLMarqueeElementTrueSpeedPropertyInfo instance AttrInfo DOMHTMLMarqueeElementTrueSpeedPropertyInfo where type AttrAllowedOps DOMHTMLMarqueeElementTrueSpeedPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLMarqueeElementTrueSpeedPropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLMarqueeElementTrueSpeedPropertyInfo = DOMHTMLMarqueeElementK type AttrGetType DOMHTMLMarqueeElementTrueSpeedPropertyInfo = Bool type AttrLabel DOMHTMLMarqueeElementTrueSpeedPropertyInfo = "DOMHTMLMarqueeElement::true-speed" attrGet _ = getDOMHTMLMarqueeElementTrueSpeed attrSet _ = setDOMHTMLMarqueeElementTrueSpeed attrConstruct _ = constructDOMHTMLMarqueeElementTrueSpeed -- VVV Prop "vspace" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLMarqueeElementVspace :: (MonadIO m, DOMHTMLMarqueeElementK o) => o -> m Word64 getDOMHTMLMarqueeElementVspace obj = liftIO $ getObjectPropertyUInt64 obj "vspace" setDOMHTMLMarqueeElementVspace :: (MonadIO m, DOMHTMLMarqueeElementK o) => o -> Word64 -> m () setDOMHTMLMarqueeElementVspace obj val = liftIO $ setObjectPropertyUInt64 obj "vspace" val constructDOMHTMLMarqueeElementVspace :: Word64 -> IO ([Char], GValue) constructDOMHTMLMarqueeElementVspace val = constructObjectPropertyUInt64 "vspace" val data DOMHTMLMarqueeElementVspacePropertyInfo instance AttrInfo DOMHTMLMarqueeElementVspacePropertyInfo where type AttrAllowedOps DOMHTMLMarqueeElementVspacePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLMarqueeElementVspacePropertyInfo = (~) Word64 type AttrBaseTypeConstraint DOMHTMLMarqueeElementVspacePropertyInfo = DOMHTMLMarqueeElementK type AttrGetType DOMHTMLMarqueeElementVspacePropertyInfo = Word64 type AttrLabel DOMHTMLMarqueeElementVspacePropertyInfo = "DOMHTMLMarqueeElement::vspace" attrGet _ = getDOMHTMLMarqueeElementVspace attrSet _ = setDOMHTMLMarqueeElementVspace attrConstruct _ = constructDOMHTMLMarqueeElementVspace -- VVV Prop "width" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLMarqueeElementWidth :: (MonadIO m, DOMHTMLMarqueeElementK o) => o -> m T.Text getDOMHTMLMarqueeElementWidth obj = liftIO $ getObjectPropertyString obj "width" setDOMHTMLMarqueeElementWidth :: (MonadIO m, DOMHTMLMarqueeElementK o) => o -> T.Text -> m () setDOMHTMLMarqueeElementWidth obj val = liftIO $ setObjectPropertyString obj "width" val constructDOMHTMLMarqueeElementWidth :: T.Text -> IO ([Char], GValue) constructDOMHTMLMarqueeElementWidth val = constructObjectPropertyString "width" val data DOMHTMLMarqueeElementWidthPropertyInfo instance AttrInfo DOMHTMLMarqueeElementWidthPropertyInfo where type AttrAllowedOps DOMHTMLMarqueeElementWidthPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLMarqueeElementWidthPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLMarqueeElementWidthPropertyInfo = DOMHTMLMarqueeElementK type AttrGetType DOMHTMLMarqueeElementWidthPropertyInfo = T.Text type AttrLabel DOMHTMLMarqueeElementWidthPropertyInfo = "DOMHTMLMarqueeElement::width" attrGet _ = getDOMHTMLMarqueeElementWidth attrSet _ = setDOMHTMLMarqueeElementWidth attrConstruct _ = constructDOMHTMLMarqueeElementWidth type instance AttributeList DOMHTMLMarqueeElement = '[ '("access-key", DOMHTMLElementAccessKeyPropertyInfo), '("attributes", DOMElementAttributesPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("behavior", DOMHTMLMarqueeElementBehaviorPropertyInfo), '("bg-color", DOMHTMLMarqueeElementBgColorPropertyInfo), '("child-element-count", DOMElementChildElementCountPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("children", DOMHTMLElementChildrenPropertyInfo), '("class-list", DOMElementClassListPropertyInfo), '("class-name", DOMElementClassNamePropertyInfo), '("client-height", DOMElementClientHeightPropertyInfo), '("client-left", DOMElementClientLeftPropertyInfo), '("client-top", DOMElementClientTopPropertyInfo), '("client-width", DOMElementClientWidthPropertyInfo), '("content-editable", DOMHTMLElementContentEditablePropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("dir", DOMHTMLElementDirPropertyInfo), '("direction", DOMHTMLMarqueeElementDirectionPropertyInfo), '("draggable", DOMHTMLElementDraggablePropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("first-element-child", DOMElementFirstElementChildPropertyInfo), '("height", DOMHTMLMarqueeElementHeightPropertyInfo), '("hidden", DOMHTMLElementHiddenPropertyInfo), '("hspace", DOMHTMLMarqueeElementHspacePropertyInfo), '("id", DOMElementIdPropertyInfo), '("inner-html", DOMHTMLElementInnerHtmlPropertyInfo), '("inner-text", DOMHTMLElementInnerTextPropertyInfo), '("is-content-editable", DOMHTMLElementIsContentEditablePropertyInfo), '("lang", DOMHTMLElementLangPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-element-child", DOMElementLastElementChildPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("loop", DOMHTMLMarqueeElementLoopPropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-element-sibling", DOMElementNextElementSiblingPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("offset-height", DOMElementOffsetHeightPropertyInfo), '("offset-left", DOMElementOffsetLeftPropertyInfo), '("offset-parent", DOMElementOffsetParentPropertyInfo), '("offset-top", DOMElementOffsetTopPropertyInfo), '("offset-width", DOMElementOffsetWidthPropertyInfo), '("outer-html", DOMHTMLElementOuterHtmlPropertyInfo), '("outer-text", DOMHTMLElementOuterTextPropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-element-sibling", DOMElementPreviousElementSiblingPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("scroll-amount", DOMHTMLMarqueeElementScrollAmountPropertyInfo), '("scroll-delay", DOMHTMLMarqueeElementScrollDelayPropertyInfo), '("scroll-height", DOMElementScrollHeightPropertyInfo), '("scroll-left", DOMElementScrollLeftPropertyInfo), '("scroll-top", DOMElementScrollTopPropertyInfo), '("scroll-width", DOMElementScrollWidthPropertyInfo), '("spellcheck", DOMHTMLElementSpellcheckPropertyInfo), '("style", DOMElementStylePropertyInfo), '("tab-index", DOMHTMLElementTabIndexPropertyInfo), '("tag-name", DOMElementTagNamePropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("title", DOMHTMLElementTitlePropertyInfo), '("translate", DOMHTMLElementTranslatePropertyInfo), '("true-speed", DOMHTMLMarqueeElementTrueSpeedPropertyInfo), '("vspace", DOMHTMLMarqueeElementVspacePropertyInfo), '("webkit-region-overset", DOMElementWebkitRegionOversetPropertyInfo), '("webkitdropzone", DOMHTMLElementWebkitdropzonePropertyInfo), '("width", DOMHTMLMarqueeElementWidthPropertyInfo)] -- VVV Prop "audio-tracks" -- Type: TInterface "WebKit" "DOMAudioTrackList" -- Flags: [PropertyReadable] getDOMHTMLMediaElementAudioTracks :: (MonadIO m, DOMHTMLMediaElementK o) => o -> m DOMAudioTrackList getDOMHTMLMediaElementAudioTracks obj = liftIO $ getObjectPropertyObject obj "audio-tracks" DOMAudioTrackList data DOMHTMLMediaElementAudioTracksPropertyInfo instance AttrInfo DOMHTMLMediaElementAudioTracksPropertyInfo where type AttrAllowedOps DOMHTMLMediaElementAudioTracksPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLMediaElementAudioTracksPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLMediaElementAudioTracksPropertyInfo = DOMHTMLMediaElementK type AttrGetType DOMHTMLMediaElementAudioTracksPropertyInfo = DOMAudioTrackList type AttrLabel DOMHTMLMediaElementAudioTracksPropertyInfo = "DOMHTMLMediaElement::audio-tracks" attrGet _ = getDOMHTMLMediaElementAudioTracks attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "autoplay" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLMediaElementAutoplay :: (MonadIO m, DOMHTMLMediaElementK o) => o -> m Bool getDOMHTMLMediaElementAutoplay obj = liftIO $ getObjectPropertyBool obj "autoplay" setDOMHTMLMediaElementAutoplay :: (MonadIO m, DOMHTMLMediaElementK o) => o -> Bool -> m () setDOMHTMLMediaElementAutoplay obj val = liftIO $ setObjectPropertyBool obj "autoplay" val constructDOMHTMLMediaElementAutoplay :: Bool -> IO ([Char], GValue) constructDOMHTMLMediaElementAutoplay val = constructObjectPropertyBool "autoplay" val data DOMHTMLMediaElementAutoplayPropertyInfo instance AttrInfo DOMHTMLMediaElementAutoplayPropertyInfo where type AttrAllowedOps DOMHTMLMediaElementAutoplayPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLMediaElementAutoplayPropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLMediaElementAutoplayPropertyInfo = DOMHTMLMediaElementK type AttrGetType DOMHTMLMediaElementAutoplayPropertyInfo = Bool type AttrLabel DOMHTMLMediaElementAutoplayPropertyInfo = "DOMHTMLMediaElement::autoplay" attrGet _ = getDOMHTMLMediaElementAutoplay attrSet _ = setDOMHTMLMediaElementAutoplay attrConstruct _ = constructDOMHTMLMediaElementAutoplay -- VVV Prop "buffered" -- Type: TInterface "WebKit" "DOMTimeRanges" -- Flags: [PropertyReadable] getDOMHTMLMediaElementBuffered :: (MonadIO m, DOMHTMLMediaElementK o) => o -> m DOMTimeRanges getDOMHTMLMediaElementBuffered obj = liftIO $ getObjectPropertyObject obj "buffered" DOMTimeRanges data DOMHTMLMediaElementBufferedPropertyInfo instance AttrInfo DOMHTMLMediaElementBufferedPropertyInfo where type AttrAllowedOps DOMHTMLMediaElementBufferedPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLMediaElementBufferedPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLMediaElementBufferedPropertyInfo = DOMHTMLMediaElementK type AttrGetType DOMHTMLMediaElementBufferedPropertyInfo = DOMTimeRanges type AttrLabel DOMHTMLMediaElementBufferedPropertyInfo = "DOMHTMLMediaElement::buffered" attrGet _ = getDOMHTMLMediaElementBuffered attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "controller" -- Type: TInterface "WebKit" "DOMMediaController" -- Flags: [PropertyReadable] getDOMHTMLMediaElementController :: (MonadIO m, DOMHTMLMediaElementK o) => o -> m DOMMediaController getDOMHTMLMediaElementController obj = liftIO $ getObjectPropertyObject obj "controller" DOMMediaController data DOMHTMLMediaElementControllerPropertyInfo instance AttrInfo DOMHTMLMediaElementControllerPropertyInfo where type AttrAllowedOps DOMHTMLMediaElementControllerPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLMediaElementControllerPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLMediaElementControllerPropertyInfo = DOMHTMLMediaElementK type AttrGetType DOMHTMLMediaElementControllerPropertyInfo = DOMMediaController type AttrLabel DOMHTMLMediaElementControllerPropertyInfo = "DOMHTMLMediaElement::controller" attrGet _ = getDOMHTMLMediaElementController attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "controls" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLMediaElementControls :: (MonadIO m, DOMHTMLMediaElementK o) => o -> m Bool getDOMHTMLMediaElementControls obj = liftIO $ getObjectPropertyBool obj "controls" setDOMHTMLMediaElementControls :: (MonadIO m, DOMHTMLMediaElementK o) => o -> Bool -> m () setDOMHTMLMediaElementControls obj val = liftIO $ setObjectPropertyBool obj "controls" val constructDOMHTMLMediaElementControls :: Bool -> IO ([Char], GValue) constructDOMHTMLMediaElementControls val = constructObjectPropertyBool "controls" val data DOMHTMLMediaElementControlsPropertyInfo instance AttrInfo DOMHTMLMediaElementControlsPropertyInfo where type AttrAllowedOps DOMHTMLMediaElementControlsPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLMediaElementControlsPropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLMediaElementControlsPropertyInfo = DOMHTMLMediaElementK type AttrGetType DOMHTMLMediaElementControlsPropertyInfo = Bool type AttrLabel DOMHTMLMediaElementControlsPropertyInfo = "DOMHTMLMediaElement::controls" attrGet _ = getDOMHTMLMediaElementControls attrSet _ = setDOMHTMLMediaElementControls attrConstruct _ = constructDOMHTMLMediaElementControls -- VVV Prop "current-src" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMHTMLMediaElementCurrentSrc :: (MonadIO m, DOMHTMLMediaElementK o) => o -> m T.Text getDOMHTMLMediaElementCurrentSrc obj = liftIO $ getObjectPropertyString obj "current-src" data DOMHTMLMediaElementCurrentSrcPropertyInfo instance AttrInfo DOMHTMLMediaElementCurrentSrcPropertyInfo where type AttrAllowedOps DOMHTMLMediaElementCurrentSrcPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLMediaElementCurrentSrcPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLMediaElementCurrentSrcPropertyInfo = DOMHTMLMediaElementK type AttrGetType DOMHTMLMediaElementCurrentSrcPropertyInfo = T.Text type AttrLabel DOMHTMLMediaElementCurrentSrcPropertyInfo = "DOMHTMLMediaElement::current-src" attrGet _ = getDOMHTMLMediaElementCurrentSrc attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "current-time" -- Type: TBasicType TDouble -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLMediaElementCurrentTime :: (MonadIO m, DOMHTMLMediaElementK o) => o -> m Double getDOMHTMLMediaElementCurrentTime obj = liftIO $ getObjectPropertyDouble obj "current-time" setDOMHTMLMediaElementCurrentTime :: (MonadIO m, DOMHTMLMediaElementK o) => o -> Double -> m () setDOMHTMLMediaElementCurrentTime obj val = liftIO $ setObjectPropertyDouble obj "current-time" val constructDOMHTMLMediaElementCurrentTime :: Double -> IO ([Char], GValue) constructDOMHTMLMediaElementCurrentTime val = constructObjectPropertyDouble "current-time" val data DOMHTMLMediaElementCurrentTimePropertyInfo instance AttrInfo DOMHTMLMediaElementCurrentTimePropertyInfo where type AttrAllowedOps DOMHTMLMediaElementCurrentTimePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLMediaElementCurrentTimePropertyInfo = (~) Double type AttrBaseTypeConstraint DOMHTMLMediaElementCurrentTimePropertyInfo = DOMHTMLMediaElementK type AttrGetType DOMHTMLMediaElementCurrentTimePropertyInfo = Double type AttrLabel DOMHTMLMediaElementCurrentTimePropertyInfo = "DOMHTMLMediaElement::current-time" attrGet _ = getDOMHTMLMediaElementCurrentTime attrSet _ = setDOMHTMLMediaElementCurrentTime attrConstruct _ = constructDOMHTMLMediaElementCurrentTime -- VVV Prop "default-muted" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLMediaElementDefaultMuted :: (MonadIO m, DOMHTMLMediaElementK o) => o -> m Bool getDOMHTMLMediaElementDefaultMuted obj = liftIO $ getObjectPropertyBool obj "default-muted" setDOMHTMLMediaElementDefaultMuted :: (MonadIO m, DOMHTMLMediaElementK o) => o -> Bool -> m () setDOMHTMLMediaElementDefaultMuted obj val = liftIO $ setObjectPropertyBool obj "default-muted" val constructDOMHTMLMediaElementDefaultMuted :: Bool -> IO ([Char], GValue) constructDOMHTMLMediaElementDefaultMuted val = constructObjectPropertyBool "default-muted" val data DOMHTMLMediaElementDefaultMutedPropertyInfo instance AttrInfo DOMHTMLMediaElementDefaultMutedPropertyInfo where type AttrAllowedOps DOMHTMLMediaElementDefaultMutedPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLMediaElementDefaultMutedPropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLMediaElementDefaultMutedPropertyInfo = DOMHTMLMediaElementK type AttrGetType DOMHTMLMediaElementDefaultMutedPropertyInfo = Bool type AttrLabel DOMHTMLMediaElementDefaultMutedPropertyInfo = "DOMHTMLMediaElement::default-muted" attrGet _ = getDOMHTMLMediaElementDefaultMuted attrSet _ = setDOMHTMLMediaElementDefaultMuted attrConstruct _ = constructDOMHTMLMediaElementDefaultMuted -- VVV Prop "default-playback-rate" -- Type: TBasicType TDouble -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLMediaElementDefaultPlaybackRate :: (MonadIO m, DOMHTMLMediaElementK o) => o -> m Double getDOMHTMLMediaElementDefaultPlaybackRate obj = liftIO $ getObjectPropertyDouble obj "default-playback-rate" setDOMHTMLMediaElementDefaultPlaybackRate :: (MonadIO m, DOMHTMLMediaElementK o) => o -> Double -> m () setDOMHTMLMediaElementDefaultPlaybackRate obj val = liftIO $ setObjectPropertyDouble obj "default-playback-rate" val constructDOMHTMLMediaElementDefaultPlaybackRate :: Double -> IO ([Char], GValue) constructDOMHTMLMediaElementDefaultPlaybackRate val = constructObjectPropertyDouble "default-playback-rate" val data DOMHTMLMediaElementDefaultPlaybackRatePropertyInfo instance AttrInfo DOMHTMLMediaElementDefaultPlaybackRatePropertyInfo where type AttrAllowedOps DOMHTMLMediaElementDefaultPlaybackRatePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLMediaElementDefaultPlaybackRatePropertyInfo = (~) Double type AttrBaseTypeConstraint DOMHTMLMediaElementDefaultPlaybackRatePropertyInfo = DOMHTMLMediaElementK type AttrGetType DOMHTMLMediaElementDefaultPlaybackRatePropertyInfo = Double type AttrLabel DOMHTMLMediaElementDefaultPlaybackRatePropertyInfo = "DOMHTMLMediaElement::default-playback-rate" attrGet _ = getDOMHTMLMediaElementDefaultPlaybackRate attrSet _ = setDOMHTMLMediaElementDefaultPlaybackRate attrConstruct _ = constructDOMHTMLMediaElementDefaultPlaybackRate -- VVV Prop "duration" -- Type: TBasicType TDouble -- Flags: [PropertyReadable] getDOMHTMLMediaElementDuration :: (MonadIO m, DOMHTMLMediaElementK o) => o -> m Double getDOMHTMLMediaElementDuration obj = liftIO $ getObjectPropertyDouble obj "duration" data DOMHTMLMediaElementDurationPropertyInfo instance AttrInfo DOMHTMLMediaElementDurationPropertyInfo where type AttrAllowedOps DOMHTMLMediaElementDurationPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLMediaElementDurationPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLMediaElementDurationPropertyInfo = DOMHTMLMediaElementK type AttrGetType DOMHTMLMediaElementDurationPropertyInfo = Double type AttrLabel DOMHTMLMediaElementDurationPropertyInfo = "DOMHTMLMediaElement::duration" attrGet _ = getDOMHTMLMediaElementDuration attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "ended" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMHTMLMediaElementEnded :: (MonadIO m, DOMHTMLMediaElementK o) => o -> m Bool getDOMHTMLMediaElementEnded obj = liftIO $ getObjectPropertyBool obj "ended" data DOMHTMLMediaElementEndedPropertyInfo instance AttrInfo DOMHTMLMediaElementEndedPropertyInfo where type AttrAllowedOps DOMHTMLMediaElementEndedPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLMediaElementEndedPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLMediaElementEndedPropertyInfo = DOMHTMLMediaElementK type AttrGetType DOMHTMLMediaElementEndedPropertyInfo = Bool type AttrLabel DOMHTMLMediaElementEndedPropertyInfo = "DOMHTMLMediaElement::ended" attrGet _ = getDOMHTMLMediaElementEnded attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "error" -- Type: TInterface "WebKit" "DOMMediaError" -- Flags: [PropertyReadable] getDOMHTMLMediaElementError :: (MonadIO m, DOMHTMLMediaElementK o) => o -> m DOMMediaError getDOMHTMLMediaElementError obj = liftIO $ getObjectPropertyObject obj "error" DOMMediaError data DOMHTMLMediaElementErrorPropertyInfo instance AttrInfo DOMHTMLMediaElementErrorPropertyInfo where type AttrAllowedOps DOMHTMLMediaElementErrorPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLMediaElementErrorPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLMediaElementErrorPropertyInfo = DOMHTMLMediaElementK type AttrGetType DOMHTMLMediaElementErrorPropertyInfo = DOMMediaError type AttrLabel DOMHTMLMediaElementErrorPropertyInfo = "DOMHTMLMediaElement::error" attrGet _ = getDOMHTMLMediaElementError attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "loop" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLMediaElementLoop :: (MonadIO m, DOMHTMLMediaElementK o) => o -> m Bool getDOMHTMLMediaElementLoop obj = liftIO $ getObjectPropertyBool obj "loop" setDOMHTMLMediaElementLoop :: (MonadIO m, DOMHTMLMediaElementK o) => o -> Bool -> m () setDOMHTMLMediaElementLoop obj val = liftIO $ setObjectPropertyBool obj "loop" val constructDOMHTMLMediaElementLoop :: Bool -> IO ([Char], GValue) constructDOMHTMLMediaElementLoop val = constructObjectPropertyBool "loop" val data DOMHTMLMediaElementLoopPropertyInfo instance AttrInfo DOMHTMLMediaElementLoopPropertyInfo where type AttrAllowedOps DOMHTMLMediaElementLoopPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLMediaElementLoopPropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLMediaElementLoopPropertyInfo = DOMHTMLMediaElementK type AttrGetType DOMHTMLMediaElementLoopPropertyInfo = Bool type AttrLabel DOMHTMLMediaElementLoopPropertyInfo = "DOMHTMLMediaElement::loop" attrGet _ = getDOMHTMLMediaElementLoop attrSet _ = setDOMHTMLMediaElementLoop attrConstruct _ = constructDOMHTMLMediaElementLoop -- VVV Prop "media-group" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLMediaElementMediaGroup :: (MonadIO m, DOMHTMLMediaElementK o) => o -> m T.Text getDOMHTMLMediaElementMediaGroup obj = liftIO $ getObjectPropertyString obj "media-group" setDOMHTMLMediaElementMediaGroup :: (MonadIO m, DOMHTMLMediaElementK o) => o -> T.Text -> m () setDOMHTMLMediaElementMediaGroup obj val = liftIO $ setObjectPropertyString obj "media-group" val constructDOMHTMLMediaElementMediaGroup :: T.Text -> IO ([Char], GValue) constructDOMHTMLMediaElementMediaGroup val = constructObjectPropertyString "media-group" val data DOMHTMLMediaElementMediaGroupPropertyInfo instance AttrInfo DOMHTMLMediaElementMediaGroupPropertyInfo where type AttrAllowedOps DOMHTMLMediaElementMediaGroupPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLMediaElementMediaGroupPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLMediaElementMediaGroupPropertyInfo = DOMHTMLMediaElementK type AttrGetType DOMHTMLMediaElementMediaGroupPropertyInfo = T.Text type AttrLabel DOMHTMLMediaElementMediaGroupPropertyInfo = "DOMHTMLMediaElement::media-group" attrGet _ = getDOMHTMLMediaElementMediaGroup attrSet _ = setDOMHTMLMediaElementMediaGroup attrConstruct _ = constructDOMHTMLMediaElementMediaGroup -- VVV Prop "muted" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLMediaElementMuted :: (MonadIO m, DOMHTMLMediaElementK o) => o -> m Bool getDOMHTMLMediaElementMuted obj = liftIO $ getObjectPropertyBool obj "muted" setDOMHTMLMediaElementMuted :: (MonadIO m, DOMHTMLMediaElementK o) => o -> Bool -> m () setDOMHTMLMediaElementMuted obj val = liftIO $ setObjectPropertyBool obj "muted" val constructDOMHTMLMediaElementMuted :: Bool -> IO ([Char], GValue) constructDOMHTMLMediaElementMuted val = constructObjectPropertyBool "muted" val data DOMHTMLMediaElementMutedPropertyInfo instance AttrInfo DOMHTMLMediaElementMutedPropertyInfo where type AttrAllowedOps DOMHTMLMediaElementMutedPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLMediaElementMutedPropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLMediaElementMutedPropertyInfo = DOMHTMLMediaElementK type AttrGetType DOMHTMLMediaElementMutedPropertyInfo = Bool type AttrLabel DOMHTMLMediaElementMutedPropertyInfo = "DOMHTMLMediaElement::muted" attrGet _ = getDOMHTMLMediaElementMuted attrSet _ = setDOMHTMLMediaElementMuted attrConstruct _ = constructDOMHTMLMediaElementMuted -- VVV Prop "network-state" -- Type: TBasicType TUInt32 -- Flags: [PropertyReadable] getDOMHTMLMediaElementNetworkState :: (MonadIO m, DOMHTMLMediaElementK o) => o -> m Word32 getDOMHTMLMediaElementNetworkState obj = liftIO $ getObjectPropertyCUInt obj "network-state" data DOMHTMLMediaElementNetworkStatePropertyInfo instance AttrInfo DOMHTMLMediaElementNetworkStatePropertyInfo where type AttrAllowedOps DOMHTMLMediaElementNetworkStatePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLMediaElementNetworkStatePropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLMediaElementNetworkStatePropertyInfo = DOMHTMLMediaElementK type AttrGetType DOMHTMLMediaElementNetworkStatePropertyInfo = Word32 type AttrLabel DOMHTMLMediaElementNetworkStatePropertyInfo = "DOMHTMLMediaElement::network-state" attrGet _ = getDOMHTMLMediaElementNetworkState attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "paused" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMHTMLMediaElementPaused :: (MonadIO m, DOMHTMLMediaElementK o) => o -> m Bool getDOMHTMLMediaElementPaused obj = liftIO $ getObjectPropertyBool obj "paused" data DOMHTMLMediaElementPausedPropertyInfo instance AttrInfo DOMHTMLMediaElementPausedPropertyInfo where type AttrAllowedOps DOMHTMLMediaElementPausedPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLMediaElementPausedPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLMediaElementPausedPropertyInfo = DOMHTMLMediaElementK type AttrGetType DOMHTMLMediaElementPausedPropertyInfo = Bool type AttrLabel DOMHTMLMediaElementPausedPropertyInfo = "DOMHTMLMediaElement::paused" attrGet _ = getDOMHTMLMediaElementPaused attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "playback-rate" -- Type: TBasicType TDouble -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLMediaElementPlaybackRate :: (MonadIO m, DOMHTMLMediaElementK o) => o -> m Double getDOMHTMLMediaElementPlaybackRate obj = liftIO $ getObjectPropertyDouble obj "playback-rate" setDOMHTMLMediaElementPlaybackRate :: (MonadIO m, DOMHTMLMediaElementK o) => o -> Double -> m () setDOMHTMLMediaElementPlaybackRate obj val = liftIO $ setObjectPropertyDouble obj "playback-rate" val constructDOMHTMLMediaElementPlaybackRate :: Double -> IO ([Char], GValue) constructDOMHTMLMediaElementPlaybackRate val = constructObjectPropertyDouble "playback-rate" val data DOMHTMLMediaElementPlaybackRatePropertyInfo instance AttrInfo DOMHTMLMediaElementPlaybackRatePropertyInfo where type AttrAllowedOps DOMHTMLMediaElementPlaybackRatePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLMediaElementPlaybackRatePropertyInfo = (~) Double type AttrBaseTypeConstraint DOMHTMLMediaElementPlaybackRatePropertyInfo = DOMHTMLMediaElementK type AttrGetType DOMHTMLMediaElementPlaybackRatePropertyInfo = Double type AttrLabel DOMHTMLMediaElementPlaybackRatePropertyInfo = "DOMHTMLMediaElement::playback-rate" attrGet _ = getDOMHTMLMediaElementPlaybackRate attrSet _ = setDOMHTMLMediaElementPlaybackRate attrConstruct _ = constructDOMHTMLMediaElementPlaybackRate -- VVV Prop "played" -- Type: TInterface "WebKit" "DOMTimeRanges" -- Flags: [PropertyReadable] getDOMHTMLMediaElementPlayed :: (MonadIO m, DOMHTMLMediaElementK o) => o -> m DOMTimeRanges getDOMHTMLMediaElementPlayed obj = liftIO $ getObjectPropertyObject obj "played" DOMTimeRanges data DOMHTMLMediaElementPlayedPropertyInfo instance AttrInfo DOMHTMLMediaElementPlayedPropertyInfo where type AttrAllowedOps DOMHTMLMediaElementPlayedPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLMediaElementPlayedPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLMediaElementPlayedPropertyInfo = DOMHTMLMediaElementK type AttrGetType DOMHTMLMediaElementPlayedPropertyInfo = DOMTimeRanges type AttrLabel DOMHTMLMediaElementPlayedPropertyInfo = "DOMHTMLMediaElement::played" attrGet _ = getDOMHTMLMediaElementPlayed attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "preload" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLMediaElementPreload :: (MonadIO m, DOMHTMLMediaElementK o) => o -> m T.Text getDOMHTMLMediaElementPreload obj = liftIO $ getObjectPropertyString obj "preload" setDOMHTMLMediaElementPreload :: (MonadIO m, DOMHTMLMediaElementK o) => o -> T.Text -> m () setDOMHTMLMediaElementPreload obj val = liftIO $ setObjectPropertyString obj "preload" val constructDOMHTMLMediaElementPreload :: T.Text -> IO ([Char], GValue) constructDOMHTMLMediaElementPreload val = constructObjectPropertyString "preload" val data DOMHTMLMediaElementPreloadPropertyInfo instance AttrInfo DOMHTMLMediaElementPreloadPropertyInfo where type AttrAllowedOps DOMHTMLMediaElementPreloadPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLMediaElementPreloadPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLMediaElementPreloadPropertyInfo = DOMHTMLMediaElementK type AttrGetType DOMHTMLMediaElementPreloadPropertyInfo = T.Text type AttrLabel DOMHTMLMediaElementPreloadPropertyInfo = "DOMHTMLMediaElement::preload" attrGet _ = getDOMHTMLMediaElementPreload attrSet _ = setDOMHTMLMediaElementPreload attrConstruct _ = constructDOMHTMLMediaElementPreload -- VVV Prop "ready-state" -- Type: TBasicType TUInt32 -- Flags: [PropertyReadable] getDOMHTMLMediaElementReadyState :: (MonadIO m, DOMHTMLMediaElementK o) => o -> m Word32 getDOMHTMLMediaElementReadyState obj = liftIO $ getObjectPropertyCUInt obj "ready-state" data DOMHTMLMediaElementReadyStatePropertyInfo instance AttrInfo DOMHTMLMediaElementReadyStatePropertyInfo where type AttrAllowedOps DOMHTMLMediaElementReadyStatePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLMediaElementReadyStatePropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLMediaElementReadyStatePropertyInfo = DOMHTMLMediaElementK type AttrGetType DOMHTMLMediaElementReadyStatePropertyInfo = Word32 type AttrLabel DOMHTMLMediaElementReadyStatePropertyInfo = "DOMHTMLMediaElement::ready-state" attrGet _ = getDOMHTMLMediaElementReadyState attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "seekable" -- Type: TInterface "WebKit" "DOMTimeRanges" -- Flags: [PropertyReadable] getDOMHTMLMediaElementSeekable :: (MonadIO m, DOMHTMLMediaElementK o) => o -> m DOMTimeRanges getDOMHTMLMediaElementSeekable obj = liftIO $ getObjectPropertyObject obj "seekable" DOMTimeRanges data DOMHTMLMediaElementSeekablePropertyInfo instance AttrInfo DOMHTMLMediaElementSeekablePropertyInfo where type AttrAllowedOps DOMHTMLMediaElementSeekablePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLMediaElementSeekablePropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLMediaElementSeekablePropertyInfo = DOMHTMLMediaElementK type AttrGetType DOMHTMLMediaElementSeekablePropertyInfo = DOMTimeRanges type AttrLabel DOMHTMLMediaElementSeekablePropertyInfo = "DOMHTMLMediaElement::seekable" attrGet _ = getDOMHTMLMediaElementSeekable attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "seeking" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMHTMLMediaElementSeeking :: (MonadIO m, DOMHTMLMediaElementK o) => o -> m Bool getDOMHTMLMediaElementSeeking obj = liftIO $ getObjectPropertyBool obj "seeking" data DOMHTMLMediaElementSeekingPropertyInfo instance AttrInfo DOMHTMLMediaElementSeekingPropertyInfo where type AttrAllowedOps DOMHTMLMediaElementSeekingPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLMediaElementSeekingPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLMediaElementSeekingPropertyInfo = DOMHTMLMediaElementK type AttrGetType DOMHTMLMediaElementSeekingPropertyInfo = Bool type AttrLabel DOMHTMLMediaElementSeekingPropertyInfo = "DOMHTMLMediaElement::seeking" attrGet _ = getDOMHTMLMediaElementSeeking attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "src" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLMediaElementSrc :: (MonadIO m, DOMHTMLMediaElementK o) => o -> m T.Text getDOMHTMLMediaElementSrc obj = liftIO $ getObjectPropertyString obj "src" setDOMHTMLMediaElementSrc :: (MonadIO m, DOMHTMLMediaElementK o) => o -> T.Text -> m () setDOMHTMLMediaElementSrc obj val = liftIO $ setObjectPropertyString obj "src" val constructDOMHTMLMediaElementSrc :: T.Text -> IO ([Char], GValue) constructDOMHTMLMediaElementSrc val = constructObjectPropertyString "src" val data DOMHTMLMediaElementSrcPropertyInfo instance AttrInfo DOMHTMLMediaElementSrcPropertyInfo where type AttrAllowedOps DOMHTMLMediaElementSrcPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLMediaElementSrcPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLMediaElementSrcPropertyInfo = DOMHTMLMediaElementK type AttrGetType DOMHTMLMediaElementSrcPropertyInfo = T.Text type AttrLabel DOMHTMLMediaElementSrcPropertyInfo = "DOMHTMLMediaElement::src" attrGet _ = getDOMHTMLMediaElementSrc attrSet _ = setDOMHTMLMediaElementSrc attrConstruct _ = constructDOMHTMLMediaElementSrc -- VVV Prop "text-tracks" -- Type: TInterface "WebKit" "DOMTextTrackList" -- Flags: [PropertyReadable] getDOMHTMLMediaElementTextTracks :: (MonadIO m, DOMHTMLMediaElementK o) => o -> m DOMTextTrackList getDOMHTMLMediaElementTextTracks obj = liftIO $ getObjectPropertyObject obj "text-tracks" DOMTextTrackList data DOMHTMLMediaElementTextTracksPropertyInfo instance AttrInfo DOMHTMLMediaElementTextTracksPropertyInfo where type AttrAllowedOps DOMHTMLMediaElementTextTracksPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLMediaElementTextTracksPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLMediaElementTextTracksPropertyInfo = DOMHTMLMediaElementK type AttrGetType DOMHTMLMediaElementTextTracksPropertyInfo = DOMTextTrackList type AttrLabel DOMHTMLMediaElementTextTracksPropertyInfo = "DOMHTMLMediaElement::text-tracks" attrGet _ = getDOMHTMLMediaElementTextTracks attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "video-tracks" -- Type: TInterface "WebKit" "DOMVideoTrackList" -- Flags: [PropertyReadable] getDOMHTMLMediaElementVideoTracks :: (MonadIO m, DOMHTMLMediaElementK o) => o -> m DOMVideoTrackList getDOMHTMLMediaElementVideoTracks obj = liftIO $ getObjectPropertyObject obj "video-tracks" DOMVideoTrackList data DOMHTMLMediaElementVideoTracksPropertyInfo instance AttrInfo DOMHTMLMediaElementVideoTracksPropertyInfo where type AttrAllowedOps DOMHTMLMediaElementVideoTracksPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLMediaElementVideoTracksPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLMediaElementVideoTracksPropertyInfo = DOMHTMLMediaElementK type AttrGetType DOMHTMLMediaElementVideoTracksPropertyInfo = DOMVideoTrackList type AttrLabel DOMHTMLMediaElementVideoTracksPropertyInfo = "DOMHTMLMediaElement::video-tracks" attrGet _ = getDOMHTMLMediaElementVideoTracks attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "volume" -- Type: TBasicType TDouble -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLMediaElementVolume :: (MonadIO m, DOMHTMLMediaElementK o) => o -> m Double getDOMHTMLMediaElementVolume obj = liftIO $ getObjectPropertyDouble obj "volume" setDOMHTMLMediaElementVolume :: (MonadIO m, DOMHTMLMediaElementK o) => o -> Double -> m () setDOMHTMLMediaElementVolume obj val = liftIO $ setObjectPropertyDouble obj "volume" val constructDOMHTMLMediaElementVolume :: Double -> IO ([Char], GValue) constructDOMHTMLMediaElementVolume val = constructObjectPropertyDouble "volume" val data DOMHTMLMediaElementVolumePropertyInfo instance AttrInfo DOMHTMLMediaElementVolumePropertyInfo where type AttrAllowedOps DOMHTMLMediaElementVolumePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLMediaElementVolumePropertyInfo = (~) Double type AttrBaseTypeConstraint DOMHTMLMediaElementVolumePropertyInfo = DOMHTMLMediaElementK type AttrGetType DOMHTMLMediaElementVolumePropertyInfo = Double type AttrLabel DOMHTMLMediaElementVolumePropertyInfo = "DOMHTMLMediaElement::volume" attrGet _ = getDOMHTMLMediaElementVolume attrSet _ = setDOMHTMLMediaElementVolume attrConstruct _ = constructDOMHTMLMediaElementVolume -- VVV Prop "webkit-audio-decoded-byte-count" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMHTMLMediaElementWebkitAudioDecodedByteCount :: (MonadIO m, DOMHTMLMediaElementK o) => o -> m Word64 getDOMHTMLMediaElementWebkitAudioDecodedByteCount obj = liftIO $ getObjectPropertyUInt64 obj "webkit-audio-decoded-byte-count" data DOMHTMLMediaElementWebkitAudioDecodedByteCountPropertyInfo instance AttrInfo DOMHTMLMediaElementWebkitAudioDecodedByteCountPropertyInfo where type AttrAllowedOps DOMHTMLMediaElementWebkitAudioDecodedByteCountPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLMediaElementWebkitAudioDecodedByteCountPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLMediaElementWebkitAudioDecodedByteCountPropertyInfo = DOMHTMLMediaElementK type AttrGetType DOMHTMLMediaElementWebkitAudioDecodedByteCountPropertyInfo = Word64 type AttrLabel DOMHTMLMediaElementWebkitAudioDecodedByteCountPropertyInfo = "DOMHTMLMediaElement::webkit-audio-decoded-byte-count" attrGet _ = getDOMHTMLMediaElementWebkitAudioDecodedByteCount attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "webkit-closed-captions-visible" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLMediaElementWebkitClosedCaptionsVisible :: (MonadIO m, DOMHTMLMediaElementK o) => o -> m Bool getDOMHTMLMediaElementWebkitClosedCaptionsVisible obj = liftIO $ getObjectPropertyBool obj "webkit-closed-captions-visible" setDOMHTMLMediaElementWebkitClosedCaptionsVisible :: (MonadIO m, DOMHTMLMediaElementK o) => o -> Bool -> m () setDOMHTMLMediaElementWebkitClosedCaptionsVisible obj val = liftIO $ setObjectPropertyBool obj "webkit-closed-captions-visible" val constructDOMHTMLMediaElementWebkitClosedCaptionsVisible :: Bool -> IO ([Char], GValue) constructDOMHTMLMediaElementWebkitClosedCaptionsVisible val = constructObjectPropertyBool "webkit-closed-captions-visible" val data DOMHTMLMediaElementWebkitClosedCaptionsVisiblePropertyInfo instance AttrInfo DOMHTMLMediaElementWebkitClosedCaptionsVisiblePropertyInfo where type AttrAllowedOps DOMHTMLMediaElementWebkitClosedCaptionsVisiblePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLMediaElementWebkitClosedCaptionsVisiblePropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLMediaElementWebkitClosedCaptionsVisiblePropertyInfo = DOMHTMLMediaElementK type AttrGetType DOMHTMLMediaElementWebkitClosedCaptionsVisiblePropertyInfo = Bool type AttrLabel DOMHTMLMediaElementWebkitClosedCaptionsVisiblePropertyInfo = "DOMHTMLMediaElement::webkit-closed-captions-visible" attrGet _ = getDOMHTMLMediaElementWebkitClosedCaptionsVisible attrSet _ = setDOMHTMLMediaElementWebkitClosedCaptionsVisible attrConstruct _ = constructDOMHTMLMediaElementWebkitClosedCaptionsVisible -- VVV Prop "webkit-current-playback-target-is-wireless" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMHTMLMediaElementWebkitCurrentPlaybackTargetIsWireless :: (MonadIO m, DOMHTMLMediaElementK o) => o -> m Bool getDOMHTMLMediaElementWebkitCurrentPlaybackTargetIsWireless obj = liftIO $ getObjectPropertyBool obj "webkit-current-playback-target-is-wireless" data DOMHTMLMediaElementWebkitCurrentPlaybackTargetIsWirelessPropertyInfo instance AttrInfo DOMHTMLMediaElementWebkitCurrentPlaybackTargetIsWirelessPropertyInfo where type AttrAllowedOps DOMHTMLMediaElementWebkitCurrentPlaybackTargetIsWirelessPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLMediaElementWebkitCurrentPlaybackTargetIsWirelessPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLMediaElementWebkitCurrentPlaybackTargetIsWirelessPropertyInfo = DOMHTMLMediaElementK type AttrGetType DOMHTMLMediaElementWebkitCurrentPlaybackTargetIsWirelessPropertyInfo = Bool type AttrLabel DOMHTMLMediaElementWebkitCurrentPlaybackTargetIsWirelessPropertyInfo = "DOMHTMLMediaElement::webkit-current-playback-target-is-wireless" attrGet _ = getDOMHTMLMediaElementWebkitCurrentPlaybackTargetIsWireless attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "webkit-has-closed-captions" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMHTMLMediaElementWebkitHasClosedCaptions :: (MonadIO m, DOMHTMLMediaElementK o) => o -> m Bool getDOMHTMLMediaElementWebkitHasClosedCaptions obj = liftIO $ getObjectPropertyBool obj "webkit-has-closed-captions" data DOMHTMLMediaElementWebkitHasClosedCaptionsPropertyInfo instance AttrInfo DOMHTMLMediaElementWebkitHasClosedCaptionsPropertyInfo where type AttrAllowedOps DOMHTMLMediaElementWebkitHasClosedCaptionsPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLMediaElementWebkitHasClosedCaptionsPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLMediaElementWebkitHasClosedCaptionsPropertyInfo = DOMHTMLMediaElementK type AttrGetType DOMHTMLMediaElementWebkitHasClosedCaptionsPropertyInfo = Bool type AttrLabel DOMHTMLMediaElementWebkitHasClosedCaptionsPropertyInfo = "DOMHTMLMediaElement::webkit-has-closed-captions" attrGet _ = getDOMHTMLMediaElementWebkitHasClosedCaptions attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "webkit-preserves-pitch" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLMediaElementWebkitPreservesPitch :: (MonadIO m, DOMHTMLMediaElementK o) => o -> m Bool getDOMHTMLMediaElementWebkitPreservesPitch obj = liftIO $ getObjectPropertyBool obj "webkit-preserves-pitch" setDOMHTMLMediaElementWebkitPreservesPitch :: (MonadIO m, DOMHTMLMediaElementK o) => o -> Bool -> m () setDOMHTMLMediaElementWebkitPreservesPitch obj val = liftIO $ setObjectPropertyBool obj "webkit-preserves-pitch" val constructDOMHTMLMediaElementWebkitPreservesPitch :: Bool -> IO ([Char], GValue) constructDOMHTMLMediaElementWebkitPreservesPitch val = constructObjectPropertyBool "webkit-preserves-pitch" val data DOMHTMLMediaElementWebkitPreservesPitchPropertyInfo instance AttrInfo DOMHTMLMediaElementWebkitPreservesPitchPropertyInfo where type AttrAllowedOps DOMHTMLMediaElementWebkitPreservesPitchPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLMediaElementWebkitPreservesPitchPropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLMediaElementWebkitPreservesPitchPropertyInfo = DOMHTMLMediaElementK type AttrGetType DOMHTMLMediaElementWebkitPreservesPitchPropertyInfo = Bool type AttrLabel DOMHTMLMediaElementWebkitPreservesPitchPropertyInfo = "DOMHTMLMediaElement::webkit-preserves-pitch" attrGet _ = getDOMHTMLMediaElementWebkitPreservesPitch attrSet _ = setDOMHTMLMediaElementWebkitPreservesPitch attrConstruct _ = constructDOMHTMLMediaElementWebkitPreservesPitch -- VVV Prop "webkit-video-decoded-byte-count" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMHTMLMediaElementWebkitVideoDecodedByteCount :: (MonadIO m, DOMHTMLMediaElementK o) => o -> m Word64 getDOMHTMLMediaElementWebkitVideoDecodedByteCount obj = liftIO $ getObjectPropertyUInt64 obj "webkit-video-decoded-byte-count" data DOMHTMLMediaElementWebkitVideoDecodedByteCountPropertyInfo instance AttrInfo DOMHTMLMediaElementWebkitVideoDecodedByteCountPropertyInfo where type AttrAllowedOps DOMHTMLMediaElementWebkitVideoDecodedByteCountPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLMediaElementWebkitVideoDecodedByteCountPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLMediaElementWebkitVideoDecodedByteCountPropertyInfo = DOMHTMLMediaElementK type AttrGetType DOMHTMLMediaElementWebkitVideoDecodedByteCountPropertyInfo = Word64 type AttrLabel DOMHTMLMediaElementWebkitVideoDecodedByteCountPropertyInfo = "DOMHTMLMediaElement::webkit-video-decoded-byte-count" attrGet _ = getDOMHTMLMediaElementWebkitVideoDecodedByteCount attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMHTMLMediaElement = '[ '("access-key", DOMHTMLElementAccessKeyPropertyInfo), '("attributes", DOMElementAttributesPropertyInfo), '("audio-tracks", DOMHTMLMediaElementAudioTracksPropertyInfo), '("autoplay", DOMHTMLMediaElementAutoplayPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("buffered", DOMHTMLMediaElementBufferedPropertyInfo), '("child-element-count", DOMElementChildElementCountPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("children", DOMHTMLElementChildrenPropertyInfo), '("class-list", DOMElementClassListPropertyInfo), '("class-name", DOMElementClassNamePropertyInfo), '("client-height", DOMElementClientHeightPropertyInfo), '("client-left", DOMElementClientLeftPropertyInfo), '("client-top", DOMElementClientTopPropertyInfo), '("client-width", DOMElementClientWidthPropertyInfo), '("content-editable", DOMHTMLElementContentEditablePropertyInfo), '("controller", DOMHTMLMediaElementControllerPropertyInfo), '("controls", DOMHTMLMediaElementControlsPropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("current-src", DOMHTMLMediaElementCurrentSrcPropertyInfo), '("current-time", DOMHTMLMediaElementCurrentTimePropertyInfo), '("default-muted", DOMHTMLMediaElementDefaultMutedPropertyInfo), '("default-playback-rate", DOMHTMLMediaElementDefaultPlaybackRatePropertyInfo), '("dir", DOMHTMLElementDirPropertyInfo), '("draggable", DOMHTMLElementDraggablePropertyInfo), '("duration", DOMHTMLMediaElementDurationPropertyInfo), '("ended", DOMHTMLMediaElementEndedPropertyInfo), '("error", DOMHTMLMediaElementErrorPropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("first-element-child", DOMElementFirstElementChildPropertyInfo), '("hidden", DOMHTMLElementHiddenPropertyInfo), '("id", DOMElementIdPropertyInfo), '("inner-html", DOMHTMLElementInnerHtmlPropertyInfo), '("inner-text", DOMHTMLElementInnerTextPropertyInfo), '("is-content-editable", DOMHTMLElementIsContentEditablePropertyInfo), '("lang", DOMHTMLElementLangPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-element-child", DOMElementLastElementChildPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("loop", DOMHTMLMediaElementLoopPropertyInfo), '("media-group", DOMHTMLMediaElementMediaGroupPropertyInfo), '("muted", DOMHTMLMediaElementMutedPropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("network-state", DOMHTMLMediaElementNetworkStatePropertyInfo), '("next-element-sibling", DOMElementNextElementSiblingPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("offset-height", DOMElementOffsetHeightPropertyInfo), '("offset-left", DOMElementOffsetLeftPropertyInfo), '("offset-parent", DOMElementOffsetParentPropertyInfo), '("offset-top", DOMElementOffsetTopPropertyInfo), '("offset-width", DOMElementOffsetWidthPropertyInfo), '("outer-html", DOMHTMLElementOuterHtmlPropertyInfo), '("outer-text", DOMHTMLElementOuterTextPropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("paused", DOMHTMLMediaElementPausedPropertyInfo), '("playback-rate", DOMHTMLMediaElementPlaybackRatePropertyInfo), '("played", DOMHTMLMediaElementPlayedPropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("preload", DOMHTMLMediaElementPreloadPropertyInfo), '("previous-element-sibling", DOMElementPreviousElementSiblingPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("ready-state", DOMHTMLMediaElementReadyStatePropertyInfo), '("scroll-height", DOMElementScrollHeightPropertyInfo), '("scroll-left", DOMElementScrollLeftPropertyInfo), '("scroll-top", DOMElementScrollTopPropertyInfo), '("scroll-width", DOMElementScrollWidthPropertyInfo), '("seekable", DOMHTMLMediaElementSeekablePropertyInfo), '("seeking", DOMHTMLMediaElementSeekingPropertyInfo), '("spellcheck", DOMHTMLElementSpellcheckPropertyInfo), '("src", DOMHTMLMediaElementSrcPropertyInfo), '("style", DOMElementStylePropertyInfo), '("tab-index", DOMHTMLElementTabIndexPropertyInfo), '("tag-name", DOMElementTagNamePropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("text-tracks", DOMHTMLMediaElementTextTracksPropertyInfo), '("title", DOMHTMLElementTitlePropertyInfo), '("translate", DOMHTMLElementTranslatePropertyInfo), '("video-tracks", DOMHTMLMediaElementVideoTracksPropertyInfo), '("volume", DOMHTMLMediaElementVolumePropertyInfo), '("webkit-audio-decoded-byte-count", DOMHTMLMediaElementWebkitAudioDecodedByteCountPropertyInfo), '("webkit-closed-captions-visible", DOMHTMLMediaElementWebkitClosedCaptionsVisiblePropertyInfo), '("webkit-current-playback-target-is-wireless", DOMHTMLMediaElementWebkitCurrentPlaybackTargetIsWirelessPropertyInfo), '("webkit-has-closed-captions", DOMHTMLMediaElementWebkitHasClosedCaptionsPropertyInfo), '("webkit-preserves-pitch", DOMHTMLMediaElementWebkitPreservesPitchPropertyInfo), '("webkit-region-overset", DOMElementWebkitRegionOversetPropertyInfo), '("webkit-video-decoded-byte-count", DOMHTMLMediaElementWebkitVideoDecodedByteCountPropertyInfo), '("webkitdropzone", DOMHTMLElementWebkitdropzonePropertyInfo)] -- VVV Prop "compact" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLMenuElementCompact :: (MonadIO m, DOMHTMLMenuElementK o) => o -> m Bool getDOMHTMLMenuElementCompact obj = liftIO $ getObjectPropertyBool obj "compact" setDOMHTMLMenuElementCompact :: (MonadIO m, DOMHTMLMenuElementK o) => o -> Bool -> m () setDOMHTMLMenuElementCompact obj val = liftIO $ setObjectPropertyBool obj "compact" val constructDOMHTMLMenuElementCompact :: Bool -> IO ([Char], GValue) constructDOMHTMLMenuElementCompact val = constructObjectPropertyBool "compact" val data DOMHTMLMenuElementCompactPropertyInfo instance AttrInfo DOMHTMLMenuElementCompactPropertyInfo where type AttrAllowedOps DOMHTMLMenuElementCompactPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLMenuElementCompactPropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLMenuElementCompactPropertyInfo = DOMHTMLMenuElementK type AttrGetType DOMHTMLMenuElementCompactPropertyInfo = Bool type AttrLabel DOMHTMLMenuElementCompactPropertyInfo = "DOMHTMLMenuElement::compact" attrGet _ = getDOMHTMLMenuElementCompact attrSet _ = setDOMHTMLMenuElementCompact attrConstruct _ = constructDOMHTMLMenuElementCompact type instance AttributeList DOMHTMLMenuElement = '[ '("access-key", DOMHTMLElementAccessKeyPropertyInfo), '("attributes", DOMElementAttributesPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("child-element-count", DOMElementChildElementCountPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("children", DOMHTMLElementChildrenPropertyInfo), '("class-list", DOMElementClassListPropertyInfo), '("class-name", DOMElementClassNamePropertyInfo), '("client-height", DOMElementClientHeightPropertyInfo), '("client-left", DOMElementClientLeftPropertyInfo), '("client-top", DOMElementClientTopPropertyInfo), '("client-width", DOMElementClientWidthPropertyInfo), '("compact", DOMHTMLMenuElementCompactPropertyInfo), '("content-editable", DOMHTMLElementContentEditablePropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("dir", DOMHTMLElementDirPropertyInfo), '("draggable", DOMHTMLElementDraggablePropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("first-element-child", DOMElementFirstElementChildPropertyInfo), '("hidden", DOMHTMLElementHiddenPropertyInfo), '("id", DOMElementIdPropertyInfo), '("inner-html", DOMHTMLElementInnerHtmlPropertyInfo), '("inner-text", DOMHTMLElementInnerTextPropertyInfo), '("is-content-editable", DOMHTMLElementIsContentEditablePropertyInfo), '("lang", DOMHTMLElementLangPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-element-child", DOMElementLastElementChildPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-element-sibling", DOMElementNextElementSiblingPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("offset-height", DOMElementOffsetHeightPropertyInfo), '("offset-left", DOMElementOffsetLeftPropertyInfo), '("offset-parent", DOMElementOffsetParentPropertyInfo), '("offset-top", DOMElementOffsetTopPropertyInfo), '("offset-width", DOMElementOffsetWidthPropertyInfo), '("outer-html", DOMHTMLElementOuterHtmlPropertyInfo), '("outer-text", DOMHTMLElementOuterTextPropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-element-sibling", DOMElementPreviousElementSiblingPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("scroll-height", DOMElementScrollHeightPropertyInfo), '("scroll-left", DOMElementScrollLeftPropertyInfo), '("scroll-top", DOMElementScrollTopPropertyInfo), '("scroll-width", DOMElementScrollWidthPropertyInfo), '("spellcheck", DOMHTMLElementSpellcheckPropertyInfo), '("style", DOMElementStylePropertyInfo), '("tab-index", DOMHTMLElementTabIndexPropertyInfo), '("tag-name", DOMElementTagNamePropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("title", DOMHTMLElementTitlePropertyInfo), '("translate", DOMHTMLElementTranslatePropertyInfo), '("webkit-region-overset", DOMElementWebkitRegionOversetPropertyInfo), '("webkitdropzone", DOMHTMLElementWebkitdropzonePropertyInfo)] -- VVV Prop "content" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLMetaElementContent :: (MonadIO m, DOMHTMLMetaElementK o) => o -> m T.Text getDOMHTMLMetaElementContent obj = liftIO $ getObjectPropertyString obj "content" setDOMHTMLMetaElementContent :: (MonadIO m, DOMHTMLMetaElementK o) => o -> T.Text -> m () setDOMHTMLMetaElementContent obj val = liftIO $ setObjectPropertyString obj "content" val constructDOMHTMLMetaElementContent :: T.Text -> IO ([Char], GValue) constructDOMHTMLMetaElementContent val = constructObjectPropertyString "content" val data DOMHTMLMetaElementContentPropertyInfo instance AttrInfo DOMHTMLMetaElementContentPropertyInfo where type AttrAllowedOps DOMHTMLMetaElementContentPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLMetaElementContentPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLMetaElementContentPropertyInfo = DOMHTMLMetaElementK type AttrGetType DOMHTMLMetaElementContentPropertyInfo = T.Text type AttrLabel DOMHTMLMetaElementContentPropertyInfo = "DOMHTMLMetaElement::content" attrGet _ = getDOMHTMLMetaElementContent attrSet _ = setDOMHTMLMetaElementContent attrConstruct _ = constructDOMHTMLMetaElementContent -- VVV Prop "http-equiv" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLMetaElementHttpEquiv :: (MonadIO m, DOMHTMLMetaElementK o) => o -> m T.Text getDOMHTMLMetaElementHttpEquiv obj = liftIO $ getObjectPropertyString obj "http-equiv" setDOMHTMLMetaElementHttpEquiv :: (MonadIO m, DOMHTMLMetaElementK o) => o -> T.Text -> m () setDOMHTMLMetaElementHttpEquiv obj val = liftIO $ setObjectPropertyString obj "http-equiv" val constructDOMHTMLMetaElementHttpEquiv :: T.Text -> IO ([Char], GValue) constructDOMHTMLMetaElementHttpEquiv val = constructObjectPropertyString "http-equiv" val data DOMHTMLMetaElementHttpEquivPropertyInfo instance AttrInfo DOMHTMLMetaElementHttpEquivPropertyInfo where type AttrAllowedOps DOMHTMLMetaElementHttpEquivPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLMetaElementHttpEquivPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLMetaElementHttpEquivPropertyInfo = DOMHTMLMetaElementK type AttrGetType DOMHTMLMetaElementHttpEquivPropertyInfo = T.Text type AttrLabel DOMHTMLMetaElementHttpEquivPropertyInfo = "DOMHTMLMetaElement::http-equiv" attrGet _ = getDOMHTMLMetaElementHttpEquiv attrSet _ = setDOMHTMLMetaElementHttpEquiv attrConstruct _ = constructDOMHTMLMetaElementHttpEquiv -- VVV Prop "name" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLMetaElementName :: (MonadIO m, DOMHTMLMetaElementK o) => o -> m T.Text getDOMHTMLMetaElementName obj = liftIO $ getObjectPropertyString obj "name" setDOMHTMLMetaElementName :: (MonadIO m, DOMHTMLMetaElementK o) => o -> T.Text -> m () setDOMHTMLMetaElementName obj val = liftIO $ setObjectPropertyString obj "name" val constructDOMHTMLMetaElementName :: T.Text -> IO ([Char], GValue) constructDOMHTMLMetaElementName val = constructObjectPropertyString "name" val data DOMHTMLMetaElementNamePropertyInfo instance AttrInfo DOMHTMLMetaElementNamePropertyInfo where type AttrAllowedOps DOMHTMLMetaElementNamePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLMetaElementNamePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLMetaElementNamePropertyInfo = DOMHTMLMetaElementK type AttrGetType DOMHTMLMetaElementNamePropertyInfo = T.Text type AttrLabel DOMHTMLMetaElementNamePropertyInfo = "DOMHTMLMetaElement::name" attrGet _ = getDOMHTMLMetaElementName attrSet _ = setDOMHTMLMetaElementName attrConstruct _ = constructDOMHTMLMetaElementName -- VVV Prop "scheme" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLMetaElementScheme :: (MonadIO m, DOMHTMLMetaElementK o) => o -> m T.Text getDOMHTMLMetaElementScheme obj = liftIO $ getObjectPropertyString obj "scheme" setDOMHTMLMetaElementScheme :: (MonadIO m, DOMHTMLMetaElementK o) => o -> T.Text -> m () setDOMHTMLMetaElementScheme obj val = liftIO $ setObjectPropertyString obj "scheme" val constructDOMHTMLMetaElementScheme :: T.Text -> IO ([Char], GValue) constructDOMHTMLMetaElementScheme val = constructObjectPropertyString "scheme" val data DOMHTMLMetaElementSchemePropertyInfo instance AttrInfo DOMHTMLMetaElementSchemePropertyInfo where type AttrAllowedOps DOMHTMLMetaElementSchemePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLMetaElementSchemePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLMetaElementSchemePropertyInfo = DOMHTMLMetaElementK type AttrGetType DOMHTMLMetaElementSchemePropertyInfo = T.Text type AttrLabel DOMHTMLMetaElementSchemePropertyInfo = "DOMHTMLMetaElement::scheme" attrGet _ = getDOMHTMLMetaElementScheme attrSet _ = setDOMHTMLMetaElementScheme attrConstruct _ = constructDOMHTMLMetaElementScheme type instance AttributeList DOMHTMLMetaElement = '[ '("access-key", DOMHTMLElementAccessKeyPropertyInfo), '("attributes", DOMElementAttributesPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("child-element-count", DOMElementChildElementCountPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("children", DOMHTMLElementChildrenPropertyInfo), '("class-list", DOMElementClassListPropertyInfo), '("class-name", DOMElementClassNamePropertyInfo), '("client-height", DOMElementClientHeightPropertyInfo), '("client-left", DOMElementClientLeftPropertyInfo), '("client-top", DOMElementClientTopPropertyInfo), '("client-width", DOMElementClientWidthPropertyInfo), '("content", DOMHTMLMetaElementContentPropertyInfo), '("content-editable", DOMHTMLElementContentEditablePropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("dir", DOMHTMLElementDirPropertyInfo), '("draggable", DOMHTMLElementDraggablePropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("first-element-child", DOMElementFirstElementChildPropertyInfo), '("hidden", DOMHTMLElementHiddenPropertyInfo), '("http-equiv", DOMHTMLMetaElementHttpEquivPropertyInfo), '("id", DOMElementIdPropertyInfo), '("inner-html", DOMHTMLElementInnerHtmlPropertyInfo), '("inner-text", DOMHTMLElementInnerTextPropertyInfo), '("is-content-editable", DOMHTMLElementIsContentEditablePropertyInfo), '("lang", DOMHTMLElementLangPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-element-child", DOMElementLastElementChildPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("name", DOMHTMLMetaElementNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-element-sibling", DOMElementNextElementSiblingPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("offset-height", DOMElementOffsetHeightPropertyInfo), '("offset-left", DOMElementOffsetLeftPropertyInfo), '("offset-parent", DOMElementOffsetParentPropertyInfo), '("offset-top", DOMElementOffsetTopPropertyInfo), '("offset-width", DOMElementOffsetWidthPropertyInfo), '("outer-html", DOMHTMLElementOuterHtmlPropertyInfo), '("outer-text", DOMHTMLElementOuterTextPropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-element-sibling", DOMElementPreviousElementSiblingPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("scheme", DOMHTMLMetaElementSchemePropertyInfo), '("scroll-height", DOMElementScrollHeightPropertyInfo), '("scroll-left", DOMElementScrollLeftPropertyInfo), '("scroll-top", DOMElementScrollTopPropertyInfo), '("scroll-width", DOMElementScrollWidthPropertyInfo), '("spellcheck", DOMHTMLElementSpellcheckPropertyInfo), '("style", DOMElementStylePropertyInfo), '("tab-index", DOMHTMLElementTabIndexPropertyInfo), '("tag-name", DOMElementTagNamePropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("title", DOMHTMLElementTitlePropertyInfo), '("translate", DOMHTMLElementTranslatePropertyInfo), '("webkit-region-overset", DOMElementWebkitRegionOversetPropertyInfo), '("webkitdropzone", DOMHTMLElementWebkitdropzonePropertyInfo)] -- VVV Prop "cite" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLModElementCite :: (MonadIO m, DOMHTMLModElementK o) => o -> m T.Text getDOMHTMLModElementCite obj = liftIO $ getObjectPropertyString obj "cite" setDOMHTMLModElementCite :: (MonadIO m, DOMHTMLModElementK o) => o -> T.Text -> m () setDOMHTMLModElementCite obj val = liftIO $ setObjectPropertyString obj "cite" val constructDOMHTMLModElementCite :: T.Text -> IO ([Char], GValue) constructDOMHTMLModElementCite val = constructObjectPropertyString "cite" val data DOMHTMLModElementCitePropertyInfo instance AttrInfo DOMHTMLModElementCitePropertyInfo where type AttrAllowedOps DOMHTMLModElementCitePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLModElementCitePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLModElementCitePropertyInfo = DOMHTMLModElementK type AttrGetType DOMHTMLModElementCitePropertyInfo = T.Text type AttrLabel DOMHTMLModElementCitePropertyInfo = "DOMHTMLModElement::cite" attrGet _ = getDOMHTMLModElementCite attrSet _ = setDOMHTMLModElementCite attrConstruct _ = constructDOMHTMLModElementCite -- VVV Prop "date-time" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLModElementDateTime :: (MonadIO m, DOMHTMLModElementK o) => o -> m T.Text getDOMHTMLModElementDateTime obj = liftIO $ getObjectPropertyString obj "date-time" setDOMHTMLModElementDateTime :: (MonadIO m, DOMHTMLModElementK o) => o -> T.Text -> m () setDOMHTMLModElementDateTime obj val = liftIO $ setObjectPropertyString obj "date-time" val constructDOMHTMLModElementDateTime :: T.Text -> IO ([Char], GValue) constructDOMHTMLModElementDateTime val = constructObjectPropertyString "date-time" val data DOMHTMLModElementDateTimePropertyInfo instance AttrInfo DOMHTMLModElementDateTimePropertyInfo where type AttrAllowedOps DOMHTMLModElementDateTimePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLModElementDateTimePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLModElementDateTimePropertyInfo = DOMHTMLModElementK type AttrGetType DOMHTMLModElementDateTimePropertyInfo = T.Text type AttrLabel DOMHTMLModElementDateTimePropertyInfo = "DOMHTMLModElement::date-time" attrGet _ = getDOMHTMLModElementDateTime attrSet _ = setDOMHTMLModElementDateTime attrConstruct _ = constructDOMHTMLModElementDateTime type instance AttributeList DOMHTMLModElement = '[ '("access-key", DOMHTMLElementAccessKeyPropertyInfo), '("attributes", DOMElementAttributesPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("child-element-count", DOMElementChildElementCountPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("children", DOMHTMLElementChildrenPropertyInfo), '("cite", DOMHTMLModElementCitePropertyInfo), '("class-list", DOMElementClassListPropertyInfo), '("class-name", DOMElementClassNamePropertyInfo), '("client-height", DOMElementClientHeightPropertyInfo), '("client-left", DOMElementClientLeftPropertyInfo), '("client-top", DOMElementClientTopPropertyInfo), '("client-width", DOMElementClientWidthPropertyInfo), '("content-editable", DOMHTMLElementContentEditablePropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("date-time", DOMHTMLModElementDateTimePropertyInfo), '("dir", DOMHTMLElementDirPropertyInfo), '("draggable", DOMHTMLElementDraggablePropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("first-element-child", DOMElementFirstElementChildPropertyInfo), '("hidden", DOMHTMLElementHiddenPropertyInfo), '("id", DOMElementIdPropertyInfo), '("inner-html", DOMHTMLElementInnerHtmlPropertyInfo), '("inner-text", DOMHTMLElementInnerTextPropertyInfo), '("is-content-editable", DOMHTMLElementIsContentEditablePropertyInfo), '("lang", DOMHTMLElementLangPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-element-child", DOMElementLastElementChildPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-element-sibling", DOMElementNextElementSiblingPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("offset-height", DOMElementOffsetHeightPropertyInfo), '("offset-left", DOMElementOffsetLeftPropertyInfo), '("offset-parent", DOMElementOffsetParentPropertyInfo), '("offset-top", DOMElementOffsetTopPropertyInfo), '("offset-width", DOMElementOffsetWidthPropertyInfo), '("outer-html", DOMHTMLElementOuterHtmlPropertyInfo), '("outer-text", DOMHTMLElementOuterTextPropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-element-sibling", DOMElementPreviousElementSiblingPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("scroll-height", DOMElementScrollHeightPropertyInfo), '("scroll-left", DOMElementScrollLeftPropertyInfo), '("scroll-top", DOMElementScrollTopPropertyInfo), '("scroll-width", DOMElementScrollWidthPropertyInfo), '("spellcheck", DOMHTMLElementSpellcheckPropertyInfo), '("style", DOMElementStylePropertyInfo), '("tab-index", DOMHTMLElementTabIndexPropertyInfo), '("tag-name", DOMElementTagNamePropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("title", DOMHTMLElementTitlePropertyInfo), '("translate", DOMHTMLElementTranslatePropertyInfo), '("webkit-region-overset", DOMElementWebkitRegionOversetPropertyInfo), '("webkitdropzone", DOMHTMLElementWebkitdropzonePropertyInfo)] -- VVV Prop "compact" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLOListElementCompact :: (MonadIO m, DOMHTMLOListElementK o) => o -> m Bool getDOMHTMLOListElementCompact obj = liftIO $ getObjectPropertyBool obj "compact" setDOMHTMLOListElementCompact :: (MonadIO m, DOMHTMLOListElementK o) => o -> Bool -> m () setDOMHTMLOListElementCompact obj val = liftIO $ setObjectPropertyBool obj "compact" val constructDOMHTMLOListElementCompact :: Bool -> IO ([Char], GValue) constructDOMHTMLOListElementCompact val = constructObjectPropertyBool "compact" val data DOMHTMLOListElementCompactPropertyInfo instance AttrInfo DOMHTMLOListElementCompactPropertyInfo where type AttrAllowedOps DOMHTMLOListElementCompactPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLOListElementCompactPropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLOListElementCompactPropertyInfo = DOMHTMLOListElementK type AttrGetType DOMHTMLOListElementCompactPropertyInfo = Bool type AttrLabel DOMHTMLOListElementCompactPropertyInfo = "DOMHTMLOListElement::compact" attrGet _ = getDOMHTMLOListElementCompact attrSet _ = setDOMHTMLOListElementCompact attrConstruct _ = constructDOMHTMLOListElementCompact -- VVV Prop "reversed" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLOListElementReversed :: (MonadIO m, DOMHTMLOListElementK o) => o -> m Bool getDOMHTMLOListElementReversed obj = liftIO $ getObjectPropertyBool obj "reversed" setDOMHTMLOListElementReversed :: (MonadIO m, DOMHTMLOListElementK o) => o -> Bool -> m () setDOMHTMLOListElementReversed obj val = liftIO $ setObjectPropertyBool obj "reversed" val constructDOMHTMLOListElementReversed :: Bool -> IO ([Char], GValue) constructDOMHTMLOListElementReversed val = constructObjectPropertyBool "reversed" val data DOMHTMLOListElementReversedPropertyInfo instance AttrInfo DOMHTMLOListElementReversedPropertyInfo where type AttrAllowedOps DOMHTMLOListElementReversedPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLOListElementReversedPropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLOListElementReversedPropertyInfo = DOMHTMLOListElementK type AttrGetType DOMHTMLOListElementReversedPropertyInfo = Bool type AttrLabel DOMHTMLOListElementReversedPropertyInfo = "DOMHTMLOListElement::reversed" attrGet _ = getDOMHTMLOListElementReversed attrSet _ = setDOMHTMLOListElementReversed attrConstruct _ = constructDOMHTMLOListElementReversed -- VVV Prop "start" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLOListElementStart :: (MonadIO m, DOMHTMLOListElementK o) => o -> m Int64 getDOMHTMLOListElementStart obj = liftIO $ getObjectPropertyInt64 obj "start" setDOMHTMLOListElementStart :: (MonadIO m, DOMHTMLOListElementK o) => o -> Int64 -> m () setDOMHTMLOListElementStart obj val = liftIO $ setObjectPropertyInt64 obj "start" val constructDOMHTMLOListElementStart :: Int64 -> IO ([Char], GValue) constructDOMHTMLOListElementStart val = constructObjectPropertyInt64 "start" val data DOMHTMLOListElementStartPropertyInfo instance AttrInfo DOMHTMLOListElementStartPropertyInfo where type AttrAllowedOps DOMHTMLOListElementStartPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLOListElementStartPropertyInfo = (~) Int64 type AttrBaseTypeConstraint DOMHTMLOListElementStartPropertyInfo = DOMHTMLOListElementK type AttrGetType DOMHTMLOListElementStartPropertyInfo = Int64 type AttrLabel DOMHTMLOListElementStartPropertyInfo = "DOMHTMLOListElement::start" attrGet _ = getDOMHTMLOListElementStart attrSet _ = setDOMHTMLOListElementStart attrConstruct _ = constructDOMHTMLOListElementStart -- VVV Prop "type" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLOListElementType :: (MonadIO m, DOMHTMLOListElementK o) => o -> m T.Text getDOMHTMLOListElementType obj = liftIO $ getObjectPropertyString obj "type" setDOMHTMLOListElementType :: (MonadIO m, DOMHTMLOListElementK o) => o -> T.Text -> m () setDOMHTMLOListElementType obj val = liftIO $ setObjectPropertyString obj "type" val constructDOMHTMLOListElementType :: T.Text -> IO ([Char], GValue) constructDOMHTMLOListElementType val = constructObjectPropertyString "type" val data DOMHTMLOListElementTypePropertyInfo instance AttrInfo DOMHTMLOListElementTypePropertyInfo where type AttrAllowedOps DOMHTMLOListElementTypePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLOListElementTypePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLOListElementTypePropertyInfo = DOMHTMLOListElementK type AttrGetType DOMHTMLOListElementTypePropertyInfo = T.Text type AttrLabel DOMHTMLOListElementTypePropertyInfo = "DOMHTMLOListElement::type" attrGet _ = getDOMHTMLOListElementType attrSet _ = setDOMHTMLOListElementType attrConstruct _ = constructDOMHTMLOListElementType type instance AttributeList DOMHTMLOListElement = '[ '("access-key", DOMHTMLElementAccessKeyPropertyInfo), '("attributes", DOMElementAttributesPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("child-element-count", DOMElementChildElementCountPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("children", DOMHTMLElementChildrenPropertyInfo), '("class-list", DOMElementClassListPropertyInfo), '("class-name", DOMElementClassNamePropertyInfo), '("client-height", DOMElementClientHeightPropertyInfo), '("client-left", DOMElementClientLeftPropertyInfo), '("client-top", DOMElementClientTopPropertyInfo), '("client-width", DOMElementClientWidthPropertyInfo), '("compact", DOMHTMLOListElementCompactPropertyInfo), '("content-editable", DOMHTMLElementContentEditablePropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("dir", DOMHTMLElementDirPropertyInfo), '("draggable", DOMHTMLElementDraggablePropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("first-element-child", DOMElementFirstElementChildPropertyInfo), '("hidden", DOMHTMLElementHiddenPropertyInfo), '("id", DOMElementIdPropertyInfo), '("inner-html", DOMHTMLElementInnerHtmlPropertyInfo), '("inner-text", DOMHTMLElementInnerTextPropertyInfo), '("is-content-editable", DOMHTMLElementIsContentEditablePropertyInfo), '("lang", DOMHTMLElementLangPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-element-child", DOMElementLastElementChildPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-element-sibling", DOMElementNextElementSiblingPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("offset-height", DOMElementOffsetHeightPropertyInfo), '("offset-left", DOMElementOffsetLeftPropertyInfo), '("offset-parent", DOMElementOffsetParentPropertyInfo), '("offset-top", DOMElementOffsetTopPropertyInfo), '("offset-width", DOMElementOffsetWidthPropertyInfo), '("outer-html", DOMHTMLElementOuterHtmlPropertyInfo), '("outer-text", DOMHTMLElementOuterTextPropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-element-sibling", DOMElementPreviousElementSiblingPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("reversed", DOMHTMLOListElementReversedPropertyInfo), '("scroll-height", DOMElementScrollHeightPropertyInfo), '("scroll-left", DOMElementScrollLeftPropertyInfo), '("scroll-top", DOMElementScrollTopPropertyInfo), '("scroll-width", DOMElementScrollWidthPropertyInfo), '("spellcheck", DOMHTMLElementSpellcheckPropertyInfo), '("start", DOMHTMLOListElementStartPropertyInfo), '("style", DOMElementStylePropertyInfo), '("tab-index", DOMHTMLElementTabIndexPropertyInfo), '("tag-name", DOMElementTagNamePropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("title", DOMHTMLElementTitlePropertyInfo), '("translate", DOMHTMLElementTranslatePropertyInfo), '("type", DOMHTMLOListElementTypePropertyInfo), '("webkit-region-overset", DOMElementWebkitRegionOversetPropertyInfo), '("webkitdropzone", DOMHTMLElementWebkitdropzonePropertyInfo)] -- VVV Prop "align" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLObjectElementAlign :: (MonadIO m, DOMHTMLObjectElementK o) => o -> m T.Text getDOMHTMLObjectElementAlign obj = liftIO $ getObjectPropertyString obj "align" setDOMHTMLObjectElementAlign :: (MonadIO m, DOMHTMLObjectElementK o) => o -> T.Text -> m () setDOMHTMLObjectElementAlign obj val = liftIO $ setObjectPropertyString obj "align" val constructDOMHTMLObjectElementAlign :: T.Text -> IO ([Char], GValue) constructDOMHTMLObjectElementAlign val = constructObjectPropertyString "align" val data DOMHTMLObjectElementAlignPropertyInfo instance AttrInfo DOMHTMLObjectElementAlignPropertyInfo where type AttrAllowedOps DOMHTMLObjectElementAlignPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLObjectElementAlignPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLObjectElementAlignPropertyInfo = DOMHTMLObjectElementK type AttrGetType DOMHTMLObjectElementAlignPropertyInfo = T.Text type AttrLabel DOMHTMLObjectElementAlignPropertyInfo = "DOMHTMLObjectElement::align" attrGet _ = getDOMHTMLObjectElementAlign attrSet _ = setDOMHTMLObjectElementAlign attrConstruct _ = constructDOMHTMLObjectElementAlign -- VVV Prop "archive" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLObjectElementArchive :: (MonadIO m, DOMHTMLObjectElementK o) => o -> m T.Text getDOMHTMLObjectElementArchive obj = liftIO $ getObjectPropertyString obj "archive" setDOMHTMLObjectElementArchive :: (MonadIO m, DOMHTMLObjectElementK o) => o -> T.Text -> m () setDOMHTMLObjectElementArchive obj val = liftIO $ setObjectPropertyString obj "archive" val constructDOMHTMLObjectElementArchive :: T.Text -> IO ([Char], GValue) constructDOMHTMLObjectElementArchive val = constructObjectPropertyString "archive" val data DOMHTMLObjectElementArchivePropertyInfo instance AttrInfo DOMHTMLObjectElementArchivePropertyInfo where type AttrAllowedOps DOMHTMLObjectElementArchivePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLObjectElementArchivePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLObjectElementArchivePropertyInfo = DOMHTMLObjectElementK type AttrGetType DOMHTMLObjectElementArchivePropertyInfo = T.Text type AttrLabel DOMHTMLObjectElementArchivePropertyInfo = "DOMHTMLObjectElement::archive" attrGet _ = getDOMHTMLObjectElementArchive attrSet _ = setDOMHTMLObjectElementArchive attrConstruct _ = constructDOMHTMLObjectElementArchive -- VVV Prop "border" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLObjectElementBorder :: (MonadIO m, DOMHTMLObjectElementK o) => o -> m T.Text getDOMHTMLObjectElementBorder obj = liftIO $ getObjectPropertyString obj "border" setDOMHTMLObjectElementBorder :: (MonadIO m, DOMHTMLObjectElementK o) => o -> T.Text -> m () setDOMHTMLObjectElementBorder obj val = liftIO $ setObjectPropertyString obj "border" val constructDOMHTMLObjectElementBorder :: T.Text -> IO ([Char], GValue) constructDOMHTMLObjectElementBorder val = constructObjectPropertyString "border" val data DOMHTMLObjectElementBorderPropertyInfo instance AttrInfo DOMHTMLObjectElementBorderPropertyInfo where type AttrAllowedOps DOMHTMLObjectElementBorderPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLObjectElementBorderPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLObjectElementBorderPropertyInfo = DOMHTMLObjectElementK type AttrGetType DOMHTMLObjectElementBorderPropertyInfo = T.Text type AttrLabel DOMHTMLObjectElementBorderPropertyInfo = "DOMHTMLObjectElement::border" attrGet _ = getDOMHTMLObjectElementBorder attrSet _ = setDOMHTMLObjectElementBorder attrConstruct _ = constructDOMHTMLObjectElementBorder -- VVV Prop "code" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLObjectElementCode :: (MonadIO m, DOMHTMLObjectElementK o) => o -> m T.Text getDOMHTMLObjectElementCode obj = liftIO $ getObjectPropertyString obj "code" setDOMHTMLObjectElementCode :: (MonadIO m, DOMHTMLObjectElementK o) => o -> T.Text -> m () setDOMHTMLObjectElementCode obj val = liftIO $ setObjectPropertyString obj "code" val constructDOMHTMLObjectElementCode :: T.Text -> IO ([Char], GValue) constructDOMHTMLObjectElementCode val = constructObjectPropertyString "code" val data DOMHTMLObjectElementCodePropertyInfo instance AttrInfo DOMHTMLObjectElementCodePropertyInfo where type AttrAllowedOps DOMHTMLObjectElementCodePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLObjectElementCodePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLObjectElementCodePropertyInfo = DOMHTMLObjectElementK type AttrGetType DOMHTMLObjectElementCodePropertyInfo = T.Text type AttrLabel DOMHTMLObjectElementCodePropertyInfo = "DOMHTMLObjectElement::code" attrGet _ = getDOMHTMLObjectElementCode attrSet _ = setDOMHTMLObjectElementCode attrConstruct _ = constructDOMHTMLObjectElementCode -- VVV Prop "code-base" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLObjectElementCodeBase :: (MonadIO m, DOMHTMLObjectElementK o) => o -> m T.Text getDOMHTMLObjectElementCodeBase obj = liftIO $ getObjectPropertyString obj "code-base" setDOMHTMLObjectElementCodeBase :: (MonadIO m, DOMHTMLObjectElementK o) => o -> T.Text -> m () setDOMHTMLObjectElementCodeBase obj val = liftIO $ setObjectPropertyString obj "code-base" val constructDOMHTMLObjectElementCodeBase :: T.Text -> IO ([Char], GValue) constructDOMHTMLObjectElementCodeBase val = constructObjectPropertyString "code-base" val data DOMHTMLObjectElementCodeBasePropertyInfo instance AttrInfo DOMHTMLObjectElementCodeBasePropertyInfo where type AttrAllowedOps DOMHTMLObjectElementCodeBasePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLObjectElementCodeBasePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLObjectElementCodeBasePropertyInfo = DOMHTMLObjectElementK type AttrGetType DOMHTMLObjectElementCodeBasePropertyInfo = T.Text type AttrLabel DOMHTMLObjectElementCodeBasePropertyInfo = "DOMHTMLObjectElement::code-base" attrGet _ = getDOMHTMLObjectElementCodeBase attrSet _ = setDOMHTMLObjectElementCodeBase attrConstruct _ = constructDOMHTMLObjectElementCodeBase -- VVV Prop "code-type" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLObjectElementCodeType :: (MonadIO m, DOMHTMLObjectElementK o) => o -> m T.Text getDOMHTMLObjectElementCodeType obj = liftIO $ getObjectPropertyString obj "code-type" setDOMHTMLObjectElementCodeType :: (MonadIO m, DOMHTMLObjectElementK o) => o -> T.Text -> m () setDOMHTMLObjectElementCodeType obj val = liftIO $ setObjectPropertyString obj "code-type" val constructDOMHTMLObjectElementCodeType :: T.Text -> IO ([Char], GValue) constructDOMHTMLObjectElementCodeType val = constructObjectPropertyString "code-type" val data DOMHTMLObjectElementCodeTypePropertyInfo instance AttrInfo DOMHTMLObjectElementCodeTypePropertyInfo where type AttrAllowedOps DOMHTMLObjectElementCodeTypePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLObjectElementCodeTypePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLObjectElementCodeTypePropertyInfo = DOMHTMLObjectElementK type AttrGetType DOMHTMLObjectElementCodeTypePropertyInfo = T.Text type AttrLabel DOMHTMLObjectElementCodeTypePropertyInfo = "DOMHTMLObjectElement::code-type" attrGet _ = getDOMHTMLObjectElementCodeType attrSet _ = setDOMHTMLObjectElementCodeType attrConstruct _ = constructDOMHTMLObjectElementCodeType -- VVV Prop "content-document" -- Type: TInterface "WebKit" "DOMDocument" -- Flags: [PropertyReadable] getDOMHTMLObjectElementContentDocument :: (MonadIO m, DOMHTMLObjectElementK o) => o -> m DOMDocument getDOMHTMLObjectElementContentDocument obj = liftIO $ getObjectPropertyObject obj "content-document" DOMDocument data DOMHTMLObjectElementContentDocumentPropertyInfo instance AttrInfo DOMHTMLObjectElementContentDocumentPropertyInfo where type AttrAllowedOps DOMHTMLObjectElementContentDocumentPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLObjectElementContentDocumentPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLObjectElementContentDocumentPropertyInfo = DOMHTMLObjectElementK type AttrGetType DOMHTMLObjectElementContentDocumentPropertyInfo = DOMDocument type AttrLabel DOMHTMLObjectElementContentDocumentPropertyInfo = "DOMHTMLObjectElement::content-document" attrGet _ = getDOMHTMLObjectElementContentDocument attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "data" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLObjectElementData :: (MonadIO m, DOMHTMLObjectElementK o) => o -> m T.Text getDOMHTMLObjectElementData obj = liftIO $ getObjectPropertyString obj "data" setDOMHTMLObjectElementData :: (MonadIO m, DOMHTMLObjectElementK o) => o -> T.Text -> m () setDOMHTMLObjectElementData obj val = liftIO $ setObjectPropertyString obj "data" val constructDOMHTMLObjectElementData :: T.Text -> IO ([Char], GValue) constructDOMHTMLObjectElementData val = constructObjectPropertyString "data" val data DOMHTMLObjectElementDataPropertyInfo instance AttrInfo DOMHTMLObjectElementDataPropertyInfo where type AttrAllowedOps DOMHTMLObjectElementDataPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLObjectElementDataPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLObjectElementDataPropertyInfo = DOMHTMLObjectElementK type AttrGetType DOMHTMLObjectElementDataPropertyInfo = T.Text type AttrLabel DOMHTMLObjectElementDataPropertyInfo = "DOMHTMLObjectElement::data" attrGet _ = getDOMHTMLObjectElementData attrSet _ = setDOMHTMLObjectElementData attrConstruct _ = constructDOMHTMLObjectElementData -- VVV Prop "declare" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLObjectElementDeclare :: (MonadIO m, DOMHTMLObjectElementK o) => o -> m Bool getDOMHTMLObjectElementDeclare obj = liftIO $ getObjectPropertyBool obj "declare" setDOMHTMLObjectElementDeclare :: (MonadIO m, DOMHTMLObjectElementK o) => o -> Bool -> m () setDOMHTMLObjectElementDeclare obj val = liftIO $ setObjectPropertyBool obj "declare" val constructDOMHTMLObjectElementDeclare :: Bool -> IO ([Char], GValue) constructDOMHTMLObjectElementDeclare val = constructObjectPropertyBool "declare" val data DOMHTMLObjectElementDeclarePropertyInfo instance AttrInfo DOMHTMLObjectElementDeclarePropertyInfo where type AttrAllowedOps DOMHTMLObjectElementDeclarePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLObjectElementDeclarePropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLObjectElementDeclarePropertyInfo = DOMHTMLObjectElementK type AttrGetType DOMHTMLObjectElementDeclarePropertyInfo = Bool type AttrLabel DOMHTMLObjectElementDeclarePropertyInfo = "DOMHTMLObjectElement::declare" attrGet _ = getDOMHTMLObjectElementDeclare attrSet _ = setDOMHTMLObjectElementDeclare attrConstruct _ = constructDOMHTMLObjectElementDeclare -- VVV Prop "form" -- Type: TInterface "WebKit" "DOMHTMLFormElement" -- Flags: [PropertyReadable] getDOMHTMLObjectElementForm :: (MonadIO m, DOMHTMLObjectElementK o) => o -> m DOMHTMLFormElement getDOMHTMLObjectElementForm obj = liftIO $ getObjectPropertyObject obj "form" DOMHTMLFormElement data DOMHTMLObjectElementFormPropertyInfo instance AttrInfo DOMHTMLObjectElementFormPropertyInfo where type AttrAllowedOps DOMHTMLObjectElementFormPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLObjectElementFormPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLObjectElementFormPropertyInfo = DOMHTMLObjectElementK type AttrGetType DOMHTMLObjectElementFormPropertyInfo = DOMHTMLFormElement type AttrLabel DOMHTMLObjectElementFormPropertyInfo = "DOMHTMLObjectElement::form" attrGet _ = getDOMHTMLObjectElementForm attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "height" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLObjectElementHeight :: (MonadIO m, DOMHTMLObjectElementK o) => o -> m T.Text getDOMHTMLObjectElementHeight obj = liftIO $ getObjectPropertyString obj "height" setDOMHTMLObjectElementHeight :: (MonadIO m, DOMHTMLObjectElementK o) => o -> T.Text -> m () setDOMHTMLObjectElementHeight obj val = liftIO $ setObjectPropertyString obj "height" val constructDOMHTMLObjectElementHeight :: T.Text -> IO ([Char], GValue) constructDOMHTMLObjectElementHeight val = constructObjectPropertyString "height" val data DOMHTMLObjectElementHeightPropertyInfo instance AttrInfo DOMHTMLObjectElementHeightPropertyInfo where type AttrAllowedOps DOMHTMLObjectElementHeightPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLObjectElementHeightPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLObjectElementHeightPropertyInfo = DOMHTMLObjectElementK type AttrGetType DOMHTMLObjectElementHeightPropertyInfo = T.Text type AttrLabel DOMHTMLObjectElementHeightPropertyInfo = "DOMHTMLObjectElement::height" attrGet _ = getDOMHTMLObjectElementHeight attrSet _ = setDOMHTMLObjectElementHeight attrConstruct _ = constructDOMHTMLObjectElementHeight -- VVV Prop "hspace" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLObjectElementHspace :: (MonadIO m, DOMHTMLObjectElementK o) => o -> m Int64 getDOMHTMLObjectElementHspace obj = liftIO $ getObjectPropertyInt64 obj "hspace" setDOMHTMLObjectElementHspace :: (MonadIO m, DOMHTMLObjectElementK o) => o -> Int64 -> m () setDOMHTMLObjectElementHspace obj val = liftIO $ setObjectPropertyInt64 obj "hspace" val constructDOMHTMLObjectElementHspace :: Int64 -> IO ([Char], GValue) constructDOMHTMLObjectElementHspace val = constructObjectPropertyInt64 "hspace" val data DOMHTMLObjectElementHspacePropertyInfo instance AttrInfo DOMHTMLObjectElementHspacePropertyInfo where type AttrAllowedOps DOMHTMLObjectElementHspacePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLObjectElementHspacePropertyInfo = (~) Int64 type AttrBaseTypeConstraint DOMHTMLObjectElementHspacePropertyInfo = DOMHTMLObjectElementK type AttrGetType DOMHTMLObjectElementHspacePropertyInfo = Int64 type AttrLabel DOMHTMLObjectElementHspacePropertyInfo = "DOMHTMLObjectElement::hspace" attrGet _ = getDOMHTMLObjectElementHspace attrSet _ = setDOMHTMLObjectElementHspace attrConstruct _ = constructDOMHTMLObjectElementHspace -- VVV Prop "name" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLObjectElementName :: (MonadIO m, DOMHTMLObjectElementK o) => o -> m T.Text getDOMHTMLObjectElementName obj = liftIO $ getObjectPropertyString obj "name" setDOMHTMLObjectElementName :: (MonadIO m, DOMHTMLObjectElementK o) => o -> T.Text -> m () setDOMHTMLObjectElementName obj val = liftIO $ setObjectPropertyString obj "name" val constructDOMHTMLObjectElementName :: T.Text -> IO ([Char], GValue) constructDOMHTMLObjectElementName val = constructObjectPropertyString "name" val data DOMHTMLObjectElementNamePropertyInfo instance AttrInfo DOMHTMLObjectElementNamePropertyInfo where type AttrAllowedOps DOMHTMLObjectElementNamePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLObjectElementNamePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLObjectElementNamePropertyInfo = DOMHTMLObjectElementK type AttrGetType DOMHTMLObjectElementNamePropertyInfo = T.Text type AttrLabel DOMHTMLObjectElementNamePropertyInfo = "DOMHTMLObjectElement::name" attrGet _ = getDOMHTMLObjectElementName attrSet _ = setDOMHTMLObjectElementName attrConstruct _ = constructDOMHTMLObjectElementName -- VVV Prop "standby" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLObjectElementStandby :: (MonadIO m, DOMHTMLObjectElementK o) => o -> m T.Text getDOMHTMLObjectElementStandby obj = liftIO $ getObjectPropertyString obj "standby" setDOMHTMLObjectElementStandby :: (MonadIO m, DOMHTMLObjectElementK o) => o -> T.Text -> m () setDOMHTMLObjectElementStandby obj val = liftIO $ setObjectPropertyString obj "standby" val constructDOMHTMLObjectElementStandby :: T.Text -> IO ([Char], GValue) constructDOMHTMLObjectElementStandby val = constructObjectPropertyString "standby" val data DOMHTMLObjectElementStandbyPropertyInfo instance AttrInfo DOMHTMLObjectElementStandbyPropertyInfo where type AttrAllowedOps DOMHTMLObjectElementStandbyPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLObjectElementStandbyPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLObjectElementStandbyPropertyInfo = DOMHTMLObjectElementK type AttrGetType DOMHTMLObjectElementStandbyPropertyInfo = T.Text type AttrLabel DOMHTMLObjectElementStandbyPropertyInfo = "DOMHTMLObjectElement::standby" attrGet _ = getDOMHTMLObjectElementStandby attrSet _ = setDOMHTMLObjectElementStandby attrConstruct _ = constructDOMHTMLObjectElementStandby -- VVV Prop "type" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLObjectElementType :: (MonadIO m, DOMHTMLObjectElementK o) => o -> m T.Text getDOMHTMLObjectElementType obj = liftIO $ getObjectPropertyString obj "type" setDOMHTMLObjectElementType :: (MonadIO m, DOMHTMLObjectElementK o) => o -> T.Text -> m () setDOMHTMLObjectElementType obj val = liftIO $ setObjectPropertyString obj "type" val constructDOMHTMLObjectElementType :: T.Text -> IO ([Char], GValue) constructDOMHTMLObjectElementType val = constructObjectPropertyString "type" val data DOMHTMLObjectElementTypePropertyInfo instance AttrInfo DOMHTMLObjectElementTypePropertyInfo where type AttrAllowedOps DOMHTMLObjectElementTypePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLObjectElementTypePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLObjectElementTypePropertyInfo = DOMHTMLObjectElementK type AttrGetType DOMHTMLObjectElementTypePropertyInfo = T.Text type AttrLabel DOMHTMLObjectElementTypePropertyInfo = "DOMHTMLObjectElement::type" attrGet _ = getDOMHTMLObjectElementType attrSet _ = setDOMHTMLObjectElementType attrConstruct _ = constructDOMHTMLObjectElementType -- VVV Prop "use-map" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLObjectElementUseMap :: (MonadIO m, DOMHTMLObjectElementK o) => o -> m T.Text getDOMHTMLObjectElementUseMap obj = liftIO $ getObjectPropertyString obj "use-map" setDOMHTMLObjectElementUseMap :: (MonadIO m, DOMHTMLObjectElementK o) => o -> T.Text -> m () setDOMHTMLObjectElementUseMap obj val = liftIO $ setObjectPropertyString obj "use-map" val constructDOMHTMLObjectElementUseMap :: T.Text -> IO ([Char], GValue) constructDOMHTMLObjectElementUseMap val = constructObjectPropertyString "use-map" val data DOMHTMLObjectElementUseMapPropertyInfo instance AttrInfo DOMHTMLObjectElementUseMapPropertyInfo where type AttrAllowedOps DOMHTMLObjectElementUseMapPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLObjectElementUseMapPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLObjectElementUseMapPropertyInfo = DOMHTMLObjectElementK type AttrGetType DOMHTMLObjectElementUseMapPropertyInfo = T.Text type AttrLabel DOMHTMLObjectElementUseMapPropertyInfo = "DOMHTMLObjectElement::use-map" attrGet _ = getDOMHTMLObjectElementUseMap attrSet _ = setDOMHTMLObjectElementUseMap attrConstruct _ = constructDOMHTMLObjectElementUseMap -- VVV Prop "validation-message" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMHTMLObjectElementValidationMessage :: (MonadIO m, DOMHTMLObjectElementK o) => o -> m T.Text getDOMHTMLObjectElementValidationMessage obj = liftIO $ getObjectPropertyString obj "validation-message" data DOMHTMLObjectElementValidationMessagePropertyInfo instance AttrInfo DOMHTMLObjectElementValidationMessagePropertyInfo where type AttrAllowedOps DOMHTMLObjectElementValidationMessagePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLObjectElementValidationMessagePropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLObjectElementValidationMessagePropertyInfo = DOMHTMLObjectElementK type AttrGetType DOMHTMLObjectElementValidationMessagePropertyInfo = T.Text type AttrLabel DOMHTMLObjectElementValidationMessagePropertyInfo = "DOMHTMLObjectElement::validation-message" attrGet _ = getDOMHTMLObjectElementValidationMessage attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "validity" -- Type: TInterface "WebKit" "DOMValidityState" -- Flags: [PropertyReadable] getDOMHTMLObjectElementValidity :: (MonadIO m, DOMHTMLObjectElementK o) => o -> m DOMValidityState getDOMHTMLObjectElementValidity obj = liftIO $ getObjectPropertyObject obj "validity" DOMValidityState data DOMHTMLObjectElementValidityPropertyInfo instance AttrInfo DOMHTMLObjectElementValidityPropertyInfo where type AttrAllowedOps DOMHTMLObjectElementValidityPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLObjectElementValidityPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLObjectElementValidityPropertyInfo = DOMHTMLObjectElementK type AttrGetType DOMHTMLObjectElementValidityPropertyInfo = DOMValidityState type AttrLabel DOMHTMLObjectElementValidityPropertyInfo = "DOMHTMLObjectElement::validity" attrGet _ = getDOMHTMLObjectElementValidity attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "vspace" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLObjectElementVspace :: (MonadIO m, DOMHTMLObjectElementK o) => o -> m Int64 getDOMHTMLObjectElementVspace obj = liftIO $ getObjectPropertyInt64 obj "vspace" setDOMHTMLObjectElementVspace :: (MonadIO m, DOMHTMLObjectElementK o) => o -> Int64 -> m () setDOMHTMLObjectElementVspace obj val = liftIO $ setObjectPropertyInt64 obj "vspace" val constructDOMHTMLObjectElementVspace :: Int64 -> IO ([Char], GValue) constructDOMHTMLObjectElementVspace val = constructObjectPropertyInt64 "vspace" val data DOMHTMLObjectElementVspacePropertyInfo instance AttrInfo DOMHTMLObjectElementVspacePropertyInfo where type AttrAllowedOps DOMHTMLObjectElementVspacePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLObjectElementVspacePropertyInfo = (~) Int64 type AttrBaseTypeConstraint DOMHTMLObjectElementVspacePropertyInfo = DOMHTMLObjectElementK type AttrGetType DOMHTMLObjectElementVspacePropertyInfo = Int64 type AttrLabel DOMHTMLObjectElementVspacePropertyInfo = "DOMHTMLObjectElement::vspace" attrGet _ = getDOMHTMLObjectElementVspace attrSet _ = setDOMHTMLObjectElementVspace attrConstruct _ = constructDOMHTMLObjectElementVspace -- VVV Prop "width" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLObjectElementWidth :: (MonadIO m, DOMHTMLObjectElementK o) => o -> m T.Text getDOMHTMLObjectElementWidth obj = liftIO $ getObjectPropertyString obj "width" setDOMHTMLObjectElementWidth :: (MonadIO m, DOMHTMLObjectElementK o) => o -> T.Text -> m () setDOMHTMLObjectElementWidth obj val = liftIO $ setObjectPropertyString obj "width" val constructDOMHTMLObjectElementWidth :: T.Text -> IO ([Char], GValue) constructDOMHTMLObjectElementWidth val = constructObjectPropertyString "width" val data DOMHTMLObjectElementWidthPropertyInfo instance AttrInfo DOMHTMLObjectElementWidthPropertyInfo where type AttrAllowedOps DOMHTMLObjectElementWidthPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLObjectElementWidthPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLObjectElementWidthPropertyInfo = DOMHTMLObjectElementK type AttrGetType DOMHTMLObjectElementWidthPropertyInfo = T.Text type AttrLabel DOMHTMLObjectElementWidthPropertyInfo = "DOMHTMLObjectElement::width" attrGet _ = getDOMHTMLObjectElementWidth attrSet _ = setDOMHTMLObjectElementWidth attrConstruct _ = constructDOMHTMLObjectElementWidth -- VVV Prop "will-validate" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMHTMLObjectElementWillValidate :: (MonadIO m, DOMHTMLObjectElementK o) => o -> m Bool getDOMHTMLObjectElementWillValidate obj = liftIO $ getObjectPropertyBool obj "will-validate" data DOMHTMLObjectElementWillValidatePropertyInfo instance AttrInfo DOMHTMLObjectElementWillValidatePropertyInfo where type AttrAllowedOps DOMHTMLObjectElementWillValidatePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLObjectElementWillValidatePropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLObjectElementWillValidatePropertyInfo = DOMHTMLObjectElementK type AttrGetType DOMHTMLObjectElementWillValidatePropertyInfo = Bool type AttrLabel DOMHTMLObjectElementWillValidatePropertyInfo = "DOMHTMLObjectElement::will-validate" attrGet _ = getDOMHTMLObjectElementWillValidate attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMHTMLObjectElement = '[ '("access-key", DOMHTMLElementAccessKeyPropertyInfo), '("align", DOMHTMLObjectElementAlignPropertyInfo), '("archive", DOMHTMLObjectElementArchivePropertyInfo), '("attributes", DOMElementAttributesPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("border", DOMHTMLObjectElementBorderPropertyInfo), '("child-element-count", DOMElementChildElementCountPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("children", DOMHTMLElementChildrenPropertyInfo), '("class-list", DOMElementClassListPropertyInfo), '("class-name", DOMElementClassNamePropertyInfo), '("client-height", DOMElementClientHeightPropertyInfo), '("client-left", DOMElementClientLeftPropertyInfo), '("client-top", DOMElementClientTopPropertyInfo), '("client-width", DOMElementClientWidthPropertyInfo), '("code", DOMHTMLObjectElementCodePropertyInfo), '("code-base", DOMHTMLObjectElementCodeBasePropertyInfo), '("code-type", DOMHTMLObjectElementCodeTypePropertyInfo), '("content-document", DOMHTMLObjectElementContentDocumentPropertyInfo), '("content-editable", DOMHTMLElementContentEditablePropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("data", DOMHTMLObjectElementDataPropertyInfo), '("declare", DOMHTMLObjectElementDeclarePropertyInfo), '("dir", DOMHTMLElementDirPropertyInfo), '("draggable", DOMHTMLElementDraggablePropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("first-element-child", DOMElementFirstElementChildPropertyInfo), '("form", DOMHTMLObjectElementFormPropertyInfo), '("height", DOMHTMLObjectElementHeightPropertyInfo), '("hidden", DOMHTMLElementHiddenPropertyInfo), '("hspace", DOMHTMLObjectElementHspacePropertyInfo), '("id", DOMElementIdPropertyInfo), '("inner-html", DOMHTMLElementInnerHtmlPropertyInfo), '("inner-text", DOMHTMLElementInnerTextPropertyInfo), '("is-content-editable", DOMHTMLElementIsContentEditablePropertyInfo), '("lang", DOMHTMLElementLangPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-element-child", DOMElementLastElementChildPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("name", DOMHTMLObjectElementNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-element-sibling", DOMElementNextElementSiblingPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("offset-height", DOMElementOffsetHeightPropertyInfo), '("offset-left", DOMElementOffsetLeftPropertyInfo), '("offset-parent", DOMElementOffsetParentPropertyInfo), '("offset-top", DOMElementOffsetTopPropertyInfo), '("offset-width", DOMElementOffsetWidthPropertyInfo), '("outer-html", DOMHTMLElementOuterHtmlPropertyInfo), '("outer-text", DOMHTMLElementOuterTextPropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-element-sibling", DOMElementPreviousElementSiblingPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("scroll-height", DOMElementScrollHeightPropertyInfo), '("scroll-left", DOMElementScrollLeftPropertyInfo), '("scroll-top", DOMElementScrollTopPropertyInfo), '("scroll-width", DOMElementScrollWidthPropertyInfo), '("spellcheck", DOMHTMLElementSpellcheckPropertyInfo), '("standby", DOMHTMLObjectElementStandbyPropertyInfo), '("style", DOMElementStylePropertyInfo), '("tab-index", DOMHTMLElementTabIndexPropertyInfo), '("tag-name", DOMElementTagNamePropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("title", DOMHTMLElementTitlePropertyInfo), '("translate", DOMHTMLElementTranslatePropertyInfo), '("type", DOMHTMLObjectElementTypePropertyInfo), '("use-map", DOMHTMLObjectElementUseMapPropertyInfo), '("validation-message", DOMHTMLObjectElementValidationMessagePropertyInfo), '("validity", DOMHTMLObjectElementValidityPropertyInfo), '("vspace", DOMHTMLObjectElementVspacePropertyInfo), '("webkit-region-overset", DOMElementWebkitRegionOversetPropertyInfo), '("webkitdropzone", DOMHTMLElementWebkitdropzonePropertyInfo), '("width", DOMHTMLObjectElementWidthPropertyInfo), '("will-validate", DOMHTMLObjectElementWillValidatePropertyInfo)] -- VVV Prop "disabled" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLOptGroupElementDisabled :: (MonadIO m, DOMHTMLOptGroupElementK o) => o -> m Bool getDOMHTMLOptGroupElementDisabled obj = liftIO $ getObjectPropertyBool obj "disabled" setDOMHTMLOptGroupElementDisabled :: (MonadIO m, DOMHTMLOptGroupElementK o) => o -> Bool -> m () setDOMHTMLOptGroupElementDisabled obj val = liftIO $ setObjectPropertyBool obj "disabled" val constructDOMHTMLOptGroupElementDisabled :: Bool -> IO ([Char], GValue) constructDOMHTMLOptGroupElementDisabled val = constructObjectPropertyBool "disabled" val data DOMHTMLOptGroupElementDisabledPropertyInfo instance AttrInfo DOMHTMLOptGroupElementDisabledPropertyInfo where type AttrAllowedOps DOMHTMLOptGroupElementDisabledPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLOptGroupElementDisabledPropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLOptGroupElementDisabledPropertyInfo = DOMHTMLOptGroupElementK type AttrGetType DOMHTMLOptGroupElementDisabledPropertyInfo = Bool type AttrLabel DOMHTMLOptGroupElementDisabledPropertyInfo = "DOMHTMLOptGroupElement::disabled" attrGet _ = getDOMHTMLOptGroupElementDisabled attrSet _ = setDOMHTMLOptGroupElementDisabled attrConstruct _ = constructDOMHTMLOptGroupElementDisabled -- VVV Prop "label" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLOptGroupElementLabel :: (MonadIO m, DOMHTMLOptGroupElementK o) => o -> m T.Text getDOMHTMLOptGroupElementLabel obj = liftIO $ getObjectPropertyString obj "label" setDOMHTMLOptGroupElementLabel :: (MonadIO m, DOMHTMLOptGroupElementK o) => o -> T.Text -> m () setDOMHTMLOptGroupElementLabel obj val = liftIO $ setObjectPropertyString obj "label" val constructDOMHTMLOptGroupElementLabel :: T.Text -> IO ([Char], GValue) constructDOMHTMLOptGroupElementLabel val = constructObjectPropertyString "label" val data DOMHTMLOptGroupElementLabelPropertyInfo instance AttrInfo DOMHTMLOptGroupElementLabelPropertyInfo where type AttrAllowedOps DOMHTMLOptGroupElementLabelPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLOptGroupElementLabelPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLOptGroupElementLabelPropertyInfo = DOMHTMLOptGroupElementK type AttrGetType DOMHTMLOptGroupElementLabelPropertyInfo = T.Text type AttrLabel DOMHTMLOptGroupElementLabelPropertyInfo = "DOMHTMLOptGroupElement::label" attrGet _ = getDOMHTMLOptGroupElementLabel attrSet _ = setDOMHTMLOptGroupElementLabel attrConstruct _ = constructDOMHTMLOptGroupElementLabel type instance AttributeList DOMHTMLOptGroupElement = '[ '("access-key", DOMHTMLElementAccessKeyPropertyInfo), '("attributes", DOMElementAttributesPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("child-element-count", DOMElementChildElementCountPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("children", DOMHTMLElementChildrenPropertyInfo), '("class-list", DOMElementClassListPropertyInfo), '("class-name", DOMElementClassNamePropertyInfo), '("client-height", DOMElementClientHeightPropertyInfo), '("client-left", DOMElementClientLeftPropertyInfo), '("client-top", DOMElementClientTopPropertyInfo), '("client-width", DOMElementClientWidthPropertyInfo), '("content-editable", DOMHTMLElementContentEditablePropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("dir", DOMHTMLElementDirPropertyInfo), '("disabled", DOMHTMLOptGroupElementDisabledPropertyInfo), '("draggable", DOMHTMLElementDraggablePropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("first-element-child", DOMElementFirstElementChildPropertyInfo), '("hidden", DOMHTMLElementHiddenPropertyInfo), '("id", DOMElementIdPropertyInfo), '("inner-html", DOMHTMLElementInnerHtmlPropertyInfo), '("inner-text", DOMHTMLElementInnerTextPropertyInfo), '("is-content-editable", DOMHTMLElementIsContentEditablePropertyInfo), '("label", DOMHTMLOptGroupElementLabelPropertyInfo), '("lang", DOMHTMLElementLangPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-element-child", DOMElementLastElementChildPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-element-sibling", DOMElementNextElementSiblingPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("offset-height", DOMElementOffsetHeightPropertyInfo), '("offset-left", DOMElementOffsetLeftPropertyInfo), '("offset-parent", DOMElementOffsetParentPropertyInfo), '("offset-top", DOMElementOffsetTopPropertyInfo), '("offset-width", DOMElementOffsetWidthPropertyInfo), '("outer-html", DOMHTMLElementOuterHtmlPropertyInfo), '("outer-text", DOMHTMLElementOuterTextPropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-element-sibling", DOMElementPreviousElementSiblingPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("scroll-height", DOMElementScrollHeightPropertyInfo), '("scroll-left", DOMElementScrollLeftPropertyInfo), '("scroll-top", DOMElementScrollTopPropertyInfo), '("scroll-width", DOMElementScrollWidthPropertyInfo), '("spellcheck", DOMHTMLElementSpellcheckPropertyInfo), '("style", DOMElementStylePropertyInfo), '("tab-index", DOMHTMLElementTabIndexPropertyInfo), '("tag-name", DOMElementTagNamePropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("title", DOMHTMLElementTitlePropertyInfo), '("translate", DOMHTMLElementTranslatePropertyInfo), '("webkit-region-overset", DOMElementWebkitRegionOversetPropertyInfo), '("webkitdropzone", DOMHTMLElementWebkitdropzonePropertyInfo)] -- VVV Prop "default-selected" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLOptionElementDefaultSelected :: (MonadIO m, DOMHTMLOptionElementK o) => o -> m Bool getDOMHTMLOptionElementDefaultSelected obj = liftIO $ getObjectPropertyBool obj "default-selected" setDOMHTMLOptionElementDefaultSelected :: (MonadIO m, DOMHTMLOptionElementK o) => o -> Bool -> m () setDOMHTMLOptionElementDefaultSelected obj val = liftIO $ setObjectPropertyBool obj "default-selected" val constructDOMHTMLOptionElementDefaultSelected :: Bool -> IO ([Char], GValue) constructDOMHTMLOptionElementDefaultSelected val = constructObjectPropertyBool "default-selected" val data DOMHTMLOptionElementDefaultSelectedPropertyInfo instance AttrInfo DOMHTMLOptionElementDefaultSelectedPropertyInfo where type AttrAllowedOps DOMHTMLOptionElementDefaultSelectedPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLOptionElementDefaultSelectedPropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLOptionElementDefaultSelectedPropertyInfo = DOMHTMLOptionElementK type AttrGetType DOMHTMLOptionElementDefaultSelectedPropertyInfo = Bool type AttrLabel DOMHTMLOptionElementDefaultSelectedPropertyInfo = "DOMHTMLOptionElement::default-selected" attrGet _ = getDOMHTMLOptionElementDefaultSelected attrSet _ = setDOMHTMLOptionElementDefaultSelected attrConstruct _ = constructDOMHTMLOptionElementDefaultSelected -- VVV Prop "disabled" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLOptionElementDisabled :: (MonadIO m, DOMHTMLOptionElementK o) => o -> m Bool getDOMHTMLOptionElementDisabled obj = liftIO $ getObjectPropertyBool obj "disabled" setDOMHTMLOptionElementDisabled :: (MonadIO m, DOMHTMLOptionElementK o) => o -> Bool -> m () setDOMHTMLOptionElementDisabled obj val = liftIO $ setObjectPropertyBool obj "disabled" val constructDOMHTMLOptionElementDisabled :: Bool -> IO ([Char], GValue) constructDOMHTMLOptionElementDisabled val = constructObjectPropertyBool "disabled" val data DOMHTMLOptionElementDisabledPropertyInfo instance AttrInfo DOMHTMLOptionElementDisabledPropertyInfo where type AttrAllowedOps DOMHTMLOptionElementDisabledPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLOptionElementDisabledPropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLOptionElementDisabledPropertyInfo = DOMHTMLOptionElementK type AttrGetType DOMHTMLOptionElementDisabledPropertyInfo = Bool type AttrLabel DOMHTMLOptionElementDisabledPropertyInfo = "DOMHTMLOptionElement::disabled" attrGet _ = getDOMHTMLOptionElementDisabled attrSet _ = setDOMHTMLOptionElementDisabled attrConstruct _ = constructDOMHTMLOptionElementDisabled -- VVV Prop "form" -- Type: TInterface "WebKit" "DOMHTMLFormElement" -- Flags: [PropertyReadable] getDOMHTMLOptionElementForm :: (MonadIO m, DOMHTMLOptionElementK o) => o -> m DOMHTMLFormElement getDOMHTMLOptionElementForm obj = liftIO $ getObjectPropertyObject obj "form" DOMHTMLFormElement data DOMHTMLOptionElementFormPropertyInfo instance AttrInfo DOMHTMLOptionElementFormPropertyInfo where type AttrAllowedOps DOMHTMLOptionElementFormPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLOptionElementFormPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLOptionElementFormPropertyInfo = DOMHTMLOptionElementK type AttrGetType DOMHTMLOptionElementFormPropertyInfo = DOMHTMLFormElement type AttrLabel DOMHTMLOptionElementFormPropertyInfo = "DOMHTMLOptionElement::form" attrGet _ = getDOMHTMLOptionElementForm attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "index" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMHTMLOptionElementIndex :: (MonadIO m, DOMHTMLOptionElementK o) => o -> m Int64 getDOMHTMLOptionElementIndex obj = liftIO $ getObjectPropertyInt64 obj "index" data DOMHTMLOptionElementIndexPropertyInfo instance AttrInfo DOMHTMLOptionElementIndexPropertyInfo where type AttrAllowedOps DOMHTMLOptionElementIndexPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLOptionElementIndexPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLOptionElementIndexPropertyInfo = DOMHTMLOptionElementK type AttrGetType DOMHTMLOptionElementIndexPropertyInfo = Int64 type AttrLabel DOMHTMLOptionElementIndexPropertyInfo = "DOMHTMLOptionElement::index" attrGet _ = getDOMHTMLOptionElementIndex attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "label" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLOptionElementLabel :: (MonadIO m, DOMHTMLOptionElementK o) => o -> m T.Text getDOMHTMLOptionElementLabel obj = liftIO $ getObjectPropertyString obj "label" setDOMHTMLOptionElementLabel :: (MonadIO m, DOMHTMLOptionElementK o) => o -> T.Text -> m () setDOMHTMLOptionElementLabel obj val = liftIO $ setObjectPropertyString obj "label" val constructDOMHTMLOptionElementLabel :: T.Text -> IO ([Char], GValue) constructDOMHTMLOptionElementLabel val = constructObjectPropertyString "label" val data DOMHTMLOptionElementLabelPropertyInfo instance AttrInfo DOMHTMLOptionElementLabelPropertyInfo where type AttrAllowedOps DOMHTMLOptionElementLabelPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLOptionElementLabelPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLOptionElementLabelPropertyInfo = DOMHTMLOptionElementK type AttrGetType DOMHTMLOptionElementLabelPropertyInfo = T.Text type AttrLabel DOMHTMLOptionElementLabelPropertyInfo = "DOMHTMLOptionElement::label" attrGet _ = getDOMHTMLOptionElementLabel attrSet _ = setDOMHTMLOptionElementLabel attrConstruct _ = constructDOMHTMLOptionElementLabel -- VVV Prop "selected" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLOptionElementSelected :: (MonadIO m, DOMHTMLOptionElementK o) => o -> m Bool getDOMHTMLOptionElementSelected obj = liftIO $ getObjectPropertyBool obj "selected" setDOMHTMLOptionElementSelected :: (MonadIO m, DOMHTMLOptionElementK o) => o -> Bool -> m () setDOMHTMLOptionElementSelected obj val = liftIO $ setObjectPropertyBool obj "selected" val constructDOMHTMLOptionElementSelected :: Bool -> IO ([Char], GValue) constructDOMHTMLOptionElementSelected val = constructObjectPropertyBool "selected" val data DOMHTMLOptionElementSelectedPropertyInfo instance AttrInfo DOMHTMLOptionElementSelectedPropertyInfo where type AttrAllowedOps DOMHTMLOptionElementSelectedPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLOptionElementSelectedPropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLOptionElementSelectedPropertyInfo = DOMHTMLOptionElementK type AttrGetType DOMHTMLOptionElementSelectedPropertyInfo = Bool type AttrLabel DOMHTMLOptionElementSelectedPropertyInfo = "DOMHTMLOptionElement::selected" attrGet _ = getDOMHTMLOptionElementSelected attrSet _ = setDOMHTMLOptionElementSelected attrConstruct _ = constructDOMHTMLOptionElementSelected -- VVV Prop "text" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMHTMLOptionElementText :: (MonadIO m, DOMHTMLOptionElementK o) => o -> m T.Text getDOMHTMLOptionElementText obj = liftIO $ getObjectPropertyString obj "text" data DOMHTMLOptionElementTextPropertyInfo instance AttrInfo DOMHTMLOptionElementTextPropertyInfo where type AttrAllowedOps DOMHTMLOptionElementTextPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLOptionElementTextPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLOptionElementTextPropertyInfo = DOMHTMLOptionElementK type AttrGetType DOMHTMLOptionElementTextPropertyInfo = T.Text type AttrLabel DOMHTMLOptionElementTextPropertyInfo = "DOMHTMLOptionElement::text" attrGet _ = getDOMHTMLOptionElementText attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "value" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLOptionElementValue :: (MonadIO m, DOMHTMLOptionElementK o) => o -> m T.Text getDOMHTMLOptionElementValue obj = liftIO $ getObjectPropertyString obj "value" setDOMHTMLOptionElementValue :: (MonadIO m, DOMHTMLOptionElementK o) => o -> T.Text -> m () setDOMHTMLOptionElementValue obj val = liftIO $ setObjectPropertyString obj "value" val constructDOMHTMLOptionElementValue :: T.Text -> IO ([Char], GValue) constructDOMHTMLOptionElementValue val = constructObjectPropertyString "value" val data DOMHTMLOptionElementValuePropertyInfo instance AttrInfo DOMHTMLOptionElementValuePropertyInfo where type AttrAllowedOps DOMHTMLOptionElementValuePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLOptionElementValuePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLOptionElementValuePropertyInfo = DOMHTMLOptionElementK type AttrGetType DOMHTMLOptionElementValuePropertyInfo = T.Text type AttrLabel DOMHTMLOptionElementValuePropertyInfo = "DOMHTMLOptionElement::value" attrGet _ = getDOMHTMLOptionElementValue attrSet _ = setDOMHTMLOptionElementValue attrConstruct _ = constructDOMHTMLOptionElementValue type instance AttributeList DOMHTMLOptionElement = '[ '("access-key", DOMHTMLElementAccessKeyPropertyInfo), '("attributes", DOMElementAttributesPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("child-element-count", DOMElementChildElementCountPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("children", DOMHTMLElementChildrenPropertyInfo), '("class-list", DOMElementClassListPropertyInfo), '("class-name", DOMElementClassNamePropertyInfo), '("client-height", DOMElementClientHeightPropertyInfo), '("client-left", DOMElementClientLeftPropertyInfo), '("client-top", DOMElementClientTopPropertyInfo), '("client-width", DOMElementClientWidthPropertyInfo), '("content-editable", DOMHTMLElementContentEditablePropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("default-selected", DOMHTMLOptionElementDefaultSelectedPropertyInfo), '("dir", DOMHTMLElementDirPropertyInfo), '("disabled", DOMHTMLOptionElementDisabledPropertyInfo), '("draggable", DOMHTMLElementDraggablePropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("first-element-child", DOMElementFirstElementChildPropertyInfo), '("form", DOMHTMLOptionElementFormPropertyInfo), '("hidden", DOMHTMLElementHiddenPropertyInfo), '("id", DOMElementIdPropertyInfo), '("index", DOMHTMLOptionElementIndexPropertyInfo), '("inner-html", DOMHTMLElementInnerHtmlPropertyInfo), '("inner-text", DOMHTMLElementInnerTextPropertyInfo), '("is-content-editable", DOMHTMLElementIsContentEditablePropertyInfo), '("label", DOMHTMLOptionElementLabelPropertyInfo), '("lang", DOMHTMLElementLangPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-element-child", DOMElementLastElementChildPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-element-sibling", DOMElementNextElementSiblingPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("offset-height", DOMElementOffsetHeightPropertyInfo), '("offset-left", DOMElementOffsetLeftPropertyInfo), '("offset-parent", DOMElementOffsetParentPropertyInfo), '("offset-top", DOMElementOffsetTopPropertyInfo), '("offset-width", DOMElementOffsetWidthPropertyInfo), '("outer-html", DOMHTMLElementOuterHtmlPropertyInfo), '("outer-text", DOMHTMLElementOuterTextPropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-element-sibling", DOMElementPreviousElementSiblingPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("scroll-height", DOMElementScrollHeightPropertyInfo), '("scroll-left", DOMElementScrollLeftPropertyInfo), '("scroll-top", DOMElementScrollTopPropertyInfo), '("scroll-width", DOMElementScrollWidthPropertyInfo), '("selected", DOMHTMLOptionElementSelectedPropertyInfo), '("spellcheck", DOMHTMLElementSpellcheckPropertyInfo), '("style", DOMElementStylePropertyInfo), '("tab-index", DOMHTMLElementTabIndexPropertyInfo), '("tag-name", DOMElementTagNamePropertyInfo), '("text", DOMHTMLOptionElementTextPropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("title", DOMHTMLElementTitlePropertyInfo), '("translate", DOMHTMLElementTranslatePropertyInfo), '("value", DOMHTMLOptionElementValuePropertyInfo), '("webkit-region-overset", DOMElementWebkitRegionOversetPropertyInfo), '("webkitdropzone", DOMHTMLElementWebkitdropzonePropertyInfo)] -- VVV Prop "length" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMHTMLOptionsCollectionLength :: (MonadIO m, DOMHTMLOptionsCollectionK o) => o -> m Word64 getDOMHTMLOptionsCollectionLength obj = liftIO $ getObjectPropertyUInt64 obj "length" data DOMHTMLOptionsCollectionLengthPropertyInfo instance AttrInfo DOMHTMLOptionsCollectionLengthPropertyInfo where type AttrAllowedOps DOMHTMLOptionsCollectionLengthPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLOptionsCollectionLengthPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLOptionsCollectionLengthPropertyInfo = DOMHTMLOptionsCollectionK type AttrGetType DOMHTMLOptionsCollectionLengthPropertyInfo = Word64 type AttrLabel DOMHTMLOptionsCollectionLengthPropertyInfo = "DOMHTMLOptionsCollection::length" attrGet _ = getDOMHTMLOptionsCollectionLength attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "selected-index" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLOptionsCollectionSelectedIndex :: (MonadIO m, DOMHTMLOptionsCollectionK o) => o -> m Int64 getDOMHTMLOptionsCollectionSelectedIndex obj = liftIO $ getObjectPropertyInt64 obj "selected-index" setDOMHTMLOptionsCollectionSelectedIndex :: (MonadIO m, DOMHTMLOptionsCollectionK o) => o -> Int64 -> m () setDOMHTMLOptionsCollectionSelectedIndex obj val = liftIO $ setObjectPropertyInt64 obj "selected-index" val constructDOMHTMLOptionsCollectionSelectedIndex :: Int64 -> IO ([Char], GValue) constructDOMHTMLOptionsCollectionSelectedIndex val = constructObjectPropertyInt64 "selected-index" val data DOMHTMLOptionsCollectionSelectedIndexPropertyInfo instance AttrInfo DOMHTMLOptionsCollectionSelectedIndexPropertyInfo where type AttrAllowedOps DOMHTMLOptionsCollectionSelectedIndexPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLOptionsCollectionSelectedIndexPropertyInfo = (~) Int64 type AttrBaseTypeConstraint DOMHTMLOptionsCollectionSelectedIndexPropertyInfo = DOMHTMLOptionsCollectionK type AttrGetType DOMHTMLOptionsCollectionSelectedIndexPropertyInfo = Int64 type AttrLabel DOMHTMLOptionsCollectionSelectedIndexPropertyInfo = "DOMHTMLOptionsCollection::selected-index" attrGet _ = getDOMHTMLOptionsCollectionSelectedIndex attrSet _ = setDOMHTMLOptionsCollectionSelectedIndex attrConstruct _ = constructDOMHTMLOptionsCollectionSelectedIndex type instance AttributeList DOMHTMLOptionsCollection = '[ '("core-object", DOMObjectCoreObjectPropertyInfo), '("length", DOMHTMLOptionsCollectionLengthPropertyInfo), '("selected-index", DOMHTMLOptionsCollectionSelectedIndexPropertyInfo)] -- VVV Prop "align" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLParagraphElementAlign :: (MonadIO m, DOMHTMLParagraphElementK o) => o -> m T.Text getDOMHTMLParagraphElementAlign obj = liftIO $ getObjectPropertyString obj "align" setDOMHTMLParagraphElementAlign :: (MonadIO m, DOMHTMLParagraphElementK o) => o -> T.Text -> m () setDOMHTMLParagraphElementAlign obj val = liftIO $ setObjectPropertyString obj "align" val constructDOMHTMLParagraphElementAlign :: T.Text -> IO ([Char], GValue) constructDOMHTMLParagraphElementAlign val = constructObjectPropertyString "align" val data DOMHTMLParagraphElementAlignPropertyInfo instance AttrInfo DOMHTMLParagraphElementAlignPropertyInfo where type AttrAllowedOps DOMHTMLParagraphElementAlignPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLParagraphElementAlignPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLParagraphElementAlignPropertyInfo = DOMHTMLParagraphElementK type AttrGetType DOMHTMLParagraphElementAlignPropertyInfo = T.Text type AttrLabel DOMHTMLParagraphElementAlignPropertyInfo = "DOMHTMLParagraphElement::align" attrGet _ = getDOMHTMLParagraphElementAlign attrSet _ = setDOMHTMLParagraphElementAlign attrConstruct _ = constructDOMHTMLParagraphElementAlign type instance AttributeList DOMHTMLParagraphElement = '[ '("access-key", DOMHTMLElementAccessKeyPropertyInfo), '("align", DOMHTMLParagraphElementAlignPropertyInfo), '("attributes", DOMElementAttributesPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("child-element-count", DOMElementChildElementCountPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("children", DOMHTMLElementChildrenPropertyInfo), '("class-list", DOMElementClassListPropertyInfo), '("class-name", DOMElementClassNamePropertyInfo), '("client-height", DOMElementClientHeightPropertyInfo), '("client-left", DOMElementClientLeftPropertyInfo), '("client-top", DOMElementClientTopPropertyInfo), '("client-width", DOMElementClientWidthPropertyInfo), '("content-editable", DOMHTMLElementContentEditablePropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("dir", DOMHTMLElementDirPropertyInfo), '("draggable", DOMHTMLElementDraggablePropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("first-element-child", DOMElementFirstElementChildPropertyInfo), '("hidden", DOMHTMLElementHiddenPropertyInfo), '("id", DOMElementIdPropertyInfo), '("inner-html", DOMHTMLElementInnerHtmlPropertyInfo), '("inner-text", DOMHTMLElementInnerTextPropertyInfo), '("is-content-editable", DOMHTMLElementIsContentEditablePropertyInfo), '("lang", DOMHTMLElementLangPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-element-child", DOMElementLastElementChildPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-element-sibling", DOMElementNextElementSiblingPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("offset-height", DOMElementOffsetHeightPropertyInfo), '("offset-left", DOMElementOffsetLeftPropertyInfo), '("offset-parent", DOMElementOffsetParentPropertyInfo), '("offset-top", DOMElementOffsetTopPropertyInfo), '("offset-width", DOMElementOffsetWidthPropertyInfo), '("outer-html", DOMHTMLElementOuterHtmlPropertyInfo), '("outer-text", DOMHTMLElementOuterTextPropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-element-sibling", DOMElementPreviousElementSiblingPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("scroll-height", DOMElementScrollHeightPropertyInfo), '("scroll-left", DOMElementScrollLeftPropertyInfo), '("scroll-top", DOMElementScrollTopPropertyInfo), '("scroll-width", DOMElementScrollWidthPropertyInfo), '("spellcheck", DOMHTMLElementSpellcheckPropertyInfo), '("style", DOMElementStylePropertyInfo), '("tab-index", DOMHTMLElementTabIndexPropertyInfo), '("tag-name", DOMElementTagNamePropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("title", DOMHTMLElementTitlePropertyInfo), '("translate", DOMHTMLElementTranslatePropertyInfo), '("webkit-region-overset", DOMElementWebkitRegionOversetPropertyInfo), '("webkitdropzone", DOMHTMLElementWebkitdropzonePropertyInfo)] -- VVV Prop "name" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLParamElementName :: (MonadIO m, DOMHTMLParamElementK o) => o -> m T.Text getDOMHTMLParamElementName obj = liftIO $ getObjectPropertyString obj "name" setDOMHTMLParamElementName :: (MonadIO m, DOMHTMLParamElementK o) => o -> T.Text -> m () setDOMHTMLParamElementName obj val = liftIO $ setObjectPropertyString obj "name" val constructDOMHTMLParamElementName :: T.Text -> IO ([Char], GValue) constructDOMHTMLParamElementName val = constructObjectPropertyString "name" val data DOMHTMLParamElementNamePropertyInfo instance AttrInfo DOMHTMLParamElementNamePropertyInfo where type AttrAllowedOps DOMHTMLParamElementNamePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLParamElementNamePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLParamElementNamePropertyInfo = DOMHTMLParamElementK type AttrGetType DOMHTMLParamElementNamePropertyInfo = T.Text type AttrLabel DOMHTMLParamElementNamePropertyInfo = "DOMHTMLParamElement::name" attrGet _ = getDOMHTMLParamElementName attrSet _ = setDOMHTMLParamElementName attrConstruct _ = constructDOMHTMLParamElementName -- VVV Prop "type" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLParamElementType :: (MonadIO m, DOMHTMLParamElementK o) => o -> m T.Text getDOMHTMLParamElementType obj = liftIO $ getObjectPropertyString obj "type" setDOMHTMLParamElementType :: (MonadIO m, DOMHTMLParamElementK o) => o -> T.Text -> m () setDOMHTMLParamElementType obj val = liftIO $ setObjectPropertyString obj "type" val constructDOMHTMLParamElementType :: T.Text -> IO ([Char], GValue) constructDOMHTMLParamElementType val = constructObjectPropertyString "type" val data DOMHTMLParamElementTypePropertyInfo instance AttrInfo DOMHTMLParamElementTypePropertyInfo where type AttrAllowedOps DOMHTMLParamElementTypePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLParamElementTypePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLParamElementTypePropertyInfo = DOMHTMLParamElementK type AttrGetType DOMHTMLParamElementTypePropertyInfo = T.Text type AttrLabel DOMHTMLParamElementTypePropertyInfo = "DOMHTMLParamElement::type" attrGet _ = getDOMHTMLParamElementType attrSet _ = setDOMHTMLParamElementType attrConstruct _ = constructDOMHTMLParamElementType -- VVV Prop "value" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLParamElementValue :: (MonadIO m, DOMHTMLParamElementK o) => o -> m T.Text getDOMHTMLParamElementValue obj = liftIO $ getObjectPropertyString obj "value" setDOMHTMLParamElementValue :: (MonadIO m, DOMHTMLParamElementK o) => o -> T.Text -> m () setDOMHTMLParamElementValue obj val = liftIO $ setObjectPropertyString obj "value" val constructDOMHTMLParamElementValue :: T.Text -> IO ([Char], GValue) constructDOMHTMLParamElementValue val = constructObjectPropertyString "value" val data DOMHTMLParamElementValuePropertyInfo instance AttrInfo DOMHTMLParamElementValuePropertyInfo where type AttrAllowedOps DOMHTMLParamElementValuePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLParamElementValuePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLParamElementValuePropertyInfo = DOMHTMLParamElementK type AttrGetType DOMHTMLParamElementValuePropertyInfo = T.Text type AttrLabel DOMHTMLParamElementValuePropertyInfo = "DOMHTMLParamElement::value" attrGet _ = getDOMHTMLParamElementValue attrSet _ = setDOMHTMLParamElementValue attrConstruct _ = constructDOMHTMLParamElementValue -- VVV Prop "value-type" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLParamElementValueType :: (MonadIO m, DOMHTMLParamElementK o) => o -> m T.Text getDOMHTMLParamElementValueType obj = liftIO $ getObjectPropertyString obj "value-type" setDOMHTMLParamElementValueType :: (MonadIO m, DOMHTMLParamElementK o) => o -> T.Text -> m () setDOMHTMLParamElementValueType obj val = liftIO $ setObjectPropertyString obj "value-type" val constructDOMHTMLParamElementValueType :: T.Text -> IO ([Char], GValue) constructDOMHTMLParamElementValueType val = constructObjectPropertyString "value-type" val data DOMHTMLParamElementValueTypePropertyInfo instance AttrInfo DOMHTMLParamElementValueTypePropertyInfo where type AttrAllowedOps DOMHTMLParamElementValueTypePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLParamElementValueTypePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLParamElementValueTypePropertyInfo = DOMHTMLParamElementK type AttrGetType DOMHTMLParamElementValueTypePropertyInfo = T.Text type AttrLabel DOMHTMLParamElementValueTypePropertyInfo = "DOMHTMLParamElement::value-type" attrGet _ = getDOMHTMLParamElementValueType attrSet _ = setDOMHTMLParamElementValueType attrConstruct _ = constructDOMHTMLParamElementValueType type instance AttributeList DOMHTMLParamElement = '[ '("access-key", DOMHTMLElementAccessKeyPropertyInfo), '("attributes", DOMElementAttributesPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("child-element-count", DOMElementChildElementCountPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("children", DOMHTMLElementChildrenPropertyInfo), '("class-list", DOMElementClassListPropertyInfo), '("class-name", DOMElementClassNamePropertyInfo), '("client-height", DOMElementClientHeightPropertyInfo), '("client-left", DOMElementClientLeftPropertyInfo), '("client-top", DOMElementClientTopPropertyInfo), '("client-width", DOMElementClientWidthPropertyInfo), '("content-editable", DOMHTMLElementContentEditablePropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("dir", DOMHTMLElementDirPropertyInfo), '("draggable", DOMHTMLElementDraggablePropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("first-element-child", DOMElementFirstElementChildPropertyInfo), '("hidden", DOMHTMLElementHiddenPropertyInfo), '("id", DOMElementIdPropertyInfo), '("inner-html", DOMHTMLElementInnerHtmlPropertyInfo), '("inner-text", DOMHTMLElementInnerTextPropertyInfo), '("is-content-editable", DOMHTMLElementIsContentEditablePropertyInfo), '("lang", DOMHTMLElementLangPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-element-child", DOMElementLastElementChildPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("name", DOMHTMLParamElementNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-element-sibling", DOMElementNextElementSiblingPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("offset-height", DOMElementOffsetHeightPropertyInfo), '("offset-left", DOMElementOffsetLeftPropertyInfo), '("offset-parent", DOMElementOffsetParentPropertyInfo), '("offset-top", DOMElementOffsetTopPropertyInfo), '("offset-width", DOMElementOffsetWidthPropertyInfo), '("outer-html", DOMHTMLElementOuterHtmlPropertyInfo), '("outer-text", DOMHTMLElementOuterTextPropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-element-sibling", DOMElementPreviousElementSiblingPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("scroll-height", DOMElementScrollHeightPropertyInfo), '("scroll-left", DOMElementScrollLeftPropertyInfo), '("scroll-top", DOMElementScrollTopPropertyInfo), '("scroll-width", DOMElementScrollWidthPropertyInfo), '("spellcheck", DOMHTMLElementSpellcheckPropertyInfo), '("style", DOMElementStylePropertyInfo), '("tab-index", DOMHTMLElementTabIndexPropertyInfo), '("tag-name", DOMElementTagNamePropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("title", DOMHTMLElementTitlePropertyInfo), '("translate", DOMHTMLElementTranslatePropertyInfo), '("type", DOMHTMLParamElementTypePropertyInfo), '("value", DOMHTMLParamElementValuePropertyInfo), '("value-type", DOMHTMLParamElementValueTypePropertyInfo), '("webkit-region-overset", DOMElementWebkitRegionOversetPropertyInfo), '("webkitdropzone", DOMHTMLElementWebkitdropzonePropertyInfo)] -- VVV Prop "width" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLPreElementWidth :: (MonadIO m, DOMHTMLPreElementK o) => o -> m Int64 getDOMHTMLPreElementWidth obj = liftIO $ getObjectPropertyInt64 obj "width" setDOMHTMLPreElementWidth :: (MonadIO m, DOMHTMLPreElementK o) => o -> Int64 -> m () setDOMHTMLPreElementWidth obj val = liftIO $ setObjectPropertyInt64 obj "width" val constructDOMHTMLPreElementWidth :: Int64 -> IO ([Char], GValue) constructDOMHTMLPreElementWidth val = constructObjectPropertyInt64 "width" val data DOMHTMLPreElementWidthPropertyInfo instance AttrInfo DOMHTMLPreElementWidthPropertyInfo where type AttrAllowedOps DOMHTMLPreElementWidthPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLPreElementWidthPropertyInfo = (~) Int64 type AttrBaseTypeConstraint DOMHTMLPreElementWidthPropertyInfo = DOMHTMLPreElementK type AttrGetType DOMHTMLPreElementWidthPropertyInfo = Int64 type AttrLabel DOMHTMLPreElementWidthPropertyInfo = "DOMHTMLPreElement::width" attrGet _ = getDOMHTMLPreElementWidth attrSet _ = setDOMHTMLPreElementWidth attrConstruct _ = constructDOMHTMLPreElementWidth -- VVV Prop "wrap" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLPreElementWrap :: (MonadIO m, DOMHTMLPreElementK o) => o -> m Bool getDOMHTMLPreElementWrap obj = liftIO $ getObjectPropertyBool obj "wrap" setDOMHTMLPreElementWrap :: (MonadIO m, DOMHTMLPreElementK o) => o -> Bool -> m () setDOMHTMLPreElementWrap obj val = liftIO $ setObjectPropertyBool obj "wrap" val constructDOMHTMLPreElementWrap :: Bool -> IO ([Char], GValue) constructDOMHTMLPreElementWrap val = constructObjectPropertyBool "wrap" val data DOMHTMLPreElementWrapPropertyInfo instance AttrInfo DOMHTMLPreElementWrapPropertyInfo where type AttrAllowedOps DOMHTMLPreElementWrapPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLPreElementWrapPropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLPreElementWrapPropertyInfo = DOMHTMLPreElementK type AttrGetType DOMHTMLPreElementWrapPropertyInfo = Bool type AttrLabel DOMHTMLPreElementWrapPropertyInfo = "DOMHTMLPreElement::wrap" attrGet _ = getDOMHTMLPreElementWrap attrSet _ = setDOMHTMLPreElementWrap attrConstruct _ = constructDOMHTMLPreElementWrap type instance AttributeList DOMHTMLPreElement = '[ '("access-key", DOMHTMLElementAccessKeyPropertyInfo), '("attributes", DOMElementAttributesPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("child-element-count", DOMElementChildElementCountPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("children", DOMHTMLElementChildrenPropertyInfo), '("class-list", DOMElementClassListPropertyInfo), '("class-name", DOMElementClassNamePropertyInfo), '("client-height", DOMElementClientHeightPropertyInfo), '("client-left", DOMElementClientLeftPropertyInfo), '("client-top", DOMElementClientTopPropertyInfo), '("client-width", DOMElementClientWidthPropertyInfo), '("content-editable", DOMHTMLElementContentEditablePropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("dir", DOMHTMLElementDirPropertyInfo), '("draggable", DOMHTMLElementDraggablePropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("first-element-child", DOMElementFirstElementChildPropertyInfo), '("hidden", DOMHTMLElementHiddenPropertyInfo), '("id", DOMElementIdPropertyInfo), '("inner-html", DOMHTMLElementInnerHtmlPropertyInfo), '("inner-text", DOMHTMLElementInnerTextPropertyInfo), '("is-content-editable", DOMHTMLElementIsContentEditablePropertyInfo), '("lang", DOMHTMLElementLangPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-element-child", DOMElementLastElementChildPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-element-sibling", DOMElementNextElementSiblingPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("offset-height", DOMElementOffsetHeightPropertyInfo), '("offset-left", DOMElementOffsetLeftPropertyInfo), '("offset-parent", DOMElementOffsetParentPropertyInfo), '("offset-top", DOMElementOffsetTopPropertyInfo), '("offset-width", DOMElementOffsetWidthPropertyInfo), '("outer-html", DOMHTMLElementOuterHtmlPropertyInfo), '("outer-text", DOMHTMLElementOuterTextPropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-element-sibling", DOMElementPreviousElementSiblingPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("scroll-height", DOMElementScrollHeightPropertyInfo), '("scroll-left", DOMElementScrollLeftPropertyInfo), '("scroll-top", DOMElementScrollTopPropertyInfo), '("scroll-width", DOMElementScrollWidthPropertyInfo), '("spellcheck", DOMHTMLElementSpellcheckPropertyInfo), '("style", DOMElementStylePropertyInfo), '("tab-index", DOMHTMLElementTabIndexPropertyInfo), '("tag-name", DOMElementTagNamePropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("title", DOMHTMLElementTitlePropertyInfo), '("translate", DOMHTMLElementTranslatePropertyInfo), '("webkit-region-overset", DOMElementWebkitRegionOversetPropertyInfo), '("webkitdropzone", DOMHTMLElementWebkitdropzonePropertyInfo), '("width", DOMHTMLPreElementWidthPropertyInfo), '("wrap", DOMHTMLPreElementWrapPropertyInfo)] -- VVV Prop "length" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMHTMLPropertiesCollectionLength :: (MonadIO m, DOMHTMLPropertiesCollectionK o) => o -> m Word64 getDOMHTMLPropertiesCollectionLength obj = liftIO $ getObjectPropertyUInt64 obj "length" data DOMHTMLPropertiesCollectionLengthPropertyInfo instance AttrInfo DOMHTMLPropertiesCollectionLengthPropertyInfo where type AttrAllowedOps DOMHTMLPropertiesCollectionLengthPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLPropertiesCollectionLengthPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLPropertiesCollectionLengthPropertyInfo = DOMHTMLPropertiesCollectionK type AttrGetType DOMHTMLPropertiesCollectionLengthPropertyInfo = Word64 type AttrLabel DOMHTMLPropertiesCollectionLengthPropertyInfo = "DOMHTMLPropertiesCollection::length" attrGet _ = getDOMHTMLPropertiesCollectionLength attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "names" -- Type: TInterface "WebKit" "DOMDOMStringList" -- Flags: [PropertyReadable] getDOMHTMLPropertiesCollectionNames :: (MonadIO m, DOMHTMLPropertiesCollectionK o) => o -> m DOMDOMStringList getDOMHTMLPropertiesCollectionNames obj = liftIO $ getObjectPropertyObject obj "names" DOMDOMStringList data DOMHTMLPropertiesCollectionNamesPropertyInfo instance AttrInfo DOMHTMLPropertiesCollectionNamesPropertyInfo where type AttrAllowedOps DOMHTMLPropertiesCollectionNamesPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLPropertiesCollectionNamesPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLPropertiesCollectionNamesPropertyInfo = DOMHTMLPropertiesCollectionK type AttrGetType DOMHTMLPropertiesCollectionNamesPropertyInfo = DOMDOMStringList type AttrLabel DOMHTMLPropertiesCollectionNamesPropertyInfo = "DOMHTMLPropertiesCollection::names" attrGet _ = getDOMHTMLPropertiesCollectionNames attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMHTMLPropertiesCollection = '[ '("core-object", DOMObjectCoreObjectPropertyInfo), '("length", DOMHTMLPropertiesCollectionLengthPropertyInfo), '("names", DOMHTMLPropertiesCollectionNamesPropertyInfo)] -- VVV Prop "cite" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLQuoteElementCite :: (MonadIO m, DOMHTMLQuoteElementK o) => o -> m T.Text getDOMHTMLQuoteElementCite obj = liftIO $ getObjectPropertyString obj "cite" setDOMHTMLQuoteElementCite :: (MonadIO m, DOMHTMLQuoteElementK o) => o -> T.Text -> m () setDOMHTMLQuoteElementCite obj val = liftIO $ setObjectPropertyString obj "cite" val constructDOMHTMLQuoteElementCite :: T.Text -> IO ([Char], GValue) constructDOMHTMLQuoteElementCite val = constructObjectPropertyString "cite" val data DOMHTMLQuoteElementCitePropertyInfo instance AttrInfo DOMHTMLQuoteElementCitePropertyInfo where type AttrAllowedOps DOMHTMLQuoteElementCitePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLQuoteElementCitePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLQuoteElementCitePropertyInfo = DOMHTMLQuoteElementK type AttrGetType DOMHTMLQuoteElementCitePropertyInfo = T.Text type AttrLabel DOMHTMLQuoteElementCitePropertyInfo = "DOMHTMLQuoteElement::cite" attrGet _ = getDOMHTMLQuoteElementCite attrSet _ = setDOMHTMLQuoteElementCite attrConstruct _ = constructDOMHTMLQuoteElementCite type instance AttributeList DOMHTMLQuoteElement = '[ '("access-key", DOMHTMLElementAccessKeyPropertyInfo), '("attributes", DOMElementAttributesPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("child-element-count", DOMElementChildElementCountPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("children", DOMHTMLElementChildrenPropertyInfo), '("cite", DOMHTMLQuoteElementCitePropertyInfo), '("class-list", DOMElementClassListPropertyInfo), '("class-name", DOMElementClassNamePropertyInfo), '("client-height", DOMElementClientHeightPropertyInfo), '("client-left", DOMElementClientLeftPropertyInfo), '("client-top", DOMElementClientTopPropertyInfo), '("client-width", DOMElementClientWidthPropertyInfo), '("content-editable", DOMHTMLElementContentEditablePropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("dir", DOMHTMLElementDirPropertyInfo), '("draggable", DOMHTMLElementDraggablePropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("first-element-child", DOMElementFirstElementChildPropertyInfo), '("hidden", DOMHTMLElementHiddenPropertyInfo), '("id", DOMElementIdPropertyInfo), '("inner-html", DOMHTMLElementInnerHtmlPropertyInfo), '("inner-text", DOMHTMLElementInnerTextPropertyInfo), '("is-content-editable", DOMHTMLElementIsContentEditablePropertyInfo), '("lang", DOMHTMLElementLangPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-element-child", DOMElementLastElementChildPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-element-sibling", DOMElementNextElementSiblingPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("offset-height", DOMElementOffsetHeightPropertyInfo), '("offset-left", DOMElementOffsetLeftPropertyInfo), '("offset-parent", DOMElementOffsetParentPropertyInfo), '("offset-top", DOMElementOffsetTopPropertyInfo), '("offset-width", DOMElementOffsetWidthPropertyInfo), '("outer-html", DOMHTMLElementOuterHtmlPropertyInfo), '("outer-text", DOMHTMLElementOuterTextPropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-element-sibling", DOMElementPreviousElementSiblingPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("scroll-height", DOMElementScrollHeightPropertyInfo), '("scroll-left", DOMElementScrollLeftPropertyInfo), '("scroll-top", DOMElementScrollTopPropertyInfo), '("scroll-width", DOMElementScrollWidthPropertyInfo), '("spellcheck", DOMHTMLElementSpellcheckPropertyInfo), '("style", DOMElementStylePropertyInfo), '("tab-index", DOMHTMLElementTabIndexPropertyInfo), '("tag-name", DOMElementTagNamePropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("title", DOMHTMLElementTitlePropertyInfo), '("translate", DOMHTMLElementTranslatePropertyInfo), '("webkit-region-overset", DOMElementWebkitRegionOversetPropertyInfo), '("webkitdropzone", DOMHTMLElementWebkitdropzonePropertyInfo)] -- VVV Prop "async" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLScriptElementAsync :: (MonadIO m, DOMHTMLScriptElementK o) => o -> m Bool getDOMHTMLScriptElementAsync obj = liftIO $ getObjectPropertyBool obj "async" setDOMHTMLScriptElementAsync :: (MonadIO m, DOMHTMLScriptElementK o) => o -> Bool -> m () setDOMHTMLScriptElementAsync obj val = liftIO $ setObjectPropertyBool obj "async" val constructDOMHTMLScriptElementAsync :: Bool -> IO ([Char], GValue) constructDOMHTMLScriptElementAsync val = constructObjectPropertyBool "async" val data DOMHTMLScriptElementAsyncPropertyInfo instance AttrInfo DOMHTMLScriptElementAsyncPropertyInfo where type AttrAllowedOps DOMHTMLScriptElementAsyncPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLScriptElementAsyncPropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLScriptElementAsyncPropertyInfo = DOMHTMLScriptElementK type AttrGetType DOMHTMLScriptElementAsyncPropertyInfo = Bool type AttrLabel DOMHTMLScriptElementAsyncPropertyInfo = "DOMHTMLScriptElement::async" attrGet _ = getDOMHTMLScriptElementAsync attrSet _ = setDOMHTMLScriptElementAsync attrConstruct _ = constructDOMHTMLScriptElementAsync -- VVV Prop "charset" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLScriptElementCharset :: (MonadIO m, DOMHTMLScriptElementK o) => o -> m T.Text getDOMHTMLScriptElementCharset obj = liftIO $ getObjectPropertyString obj "charset" setDOMHTMLScriptElementCharset :: (MonadIO m, DOMHTMLScriptElementK o) => o -> T.Text -> m () setDOMHTMLScriptElementCharset obj val = liftIO $ setObjectPropertyString obj "charset" val constructDOMHTMLScriptElementCharset :: T.Text -> IO ([Char], GValue) constructDOMHTMLScriptElementCharset val = constructObjectPropertyString "charset" val data DOMHTMLScriptElementCharsetPropertyInfo instance AttrInfo DOMHTMLScriptElementCharsetPropertyInfo where type AttrAllowedOps DOMHTMLScriptElementCharsetPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLScriptElementCharsetPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLScriptElementCharsetPropertyInfo = DOMHTMLScriptElementK type AttrGetType DOMHTMLScriptElementCharsetPropertyInfo = T.Text type AttrLabel DOMHTMLScriptElementCharsetPropertyInfo = "DOMHTMLScriptElement::charset" attrGet _ = getDOMHTMLScriptElementCharset attrSet _ = setDOMHTMLScriptElementCharset attrConstruct _ = constructDOMHTMLScriptElementCharset -- VVV Prop "cross-origin" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLScriptElementCrossOrigin :: (MonadIO m, DOMHTMLScriptElementK o) => o -> m T.Text getDOMHTMLScriptElementCrossOrigin obj = liftIO $ getObjectPropertyString obj "cross-origin" setDOMHTMLScriptElementCrossOrigin :: (MonadIO m, DOMHTMLScriptElementK o) => o -> T.Text -> m () setDOMHTMLScriptElementCrossOrigin obj val = liftIO $ setObjectPropertyString obj "cross-origin" val constructDOMHTMLScriptElementCrossOrigin :: T.Text -> IO ([Char], GValue) constructDOMHTMLScriptElementCrossOrigin val = constructObjectPropertyString "cross-origin" val data DOMHTMLScriptElementCrossOriginPropertyInfo instance AttrInfo DOMHTMLScriptElementCrossOriginPropertyInfo where type AttrAllowedOps DOMHTMLScriptElementCrossOriginPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLScriptElementCrossOriginPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLScriptElementCrossOriginPropertyInfo = DOMHTMLScriptElementK type AttrGetType DOMHTMLScriptElementCrossOriginPropertyInfo = T.Text type AttrLabel DOMHTMLScriptElementCrossOriginPropertyInfo = "DOMHTMLScriptElement::cross-origin" attrGet _ = getDOMHTMLScriptElementCrossOrigin attrSet _ = setDOMHTMLScriptElementCrossOrigin attrConstruct _ = constructDOMHTMLScriptElementCrossOrigin -- VVV Prop "defer" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLScriptElementDefer :: (MonadIO m, DOMHTMLScriptElementK o) => o -> m Bool getDOMHTMLScriptElementDefer obj = liftIO $ getObjectPropertyBool obj "defer" setDOMHTMLScriptElementDefer :: (MonadIO m, DOMHTMLScriptElementK o) => o -> Bool -> m () setDOMHTMLScriptElementDefer obj val = liftIO $ setObjectPropertyBool obj "defer" val constructDOMHTMLScriptElementDefer :: Bool -> IO ([Char], GValue) constructDOMHTMLScriptElementDefer val = constructObjectPropertyBool "defer" val data DOMHTMLScriptElementDeferPropertyInfo instance AttrInfo DOMHTMLScriptElementDeferPropertyInfo where type AttrAllowedOps DOMHTMLScriptElementDeferPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLScriptElementDeferPropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLScriptElementDeferPropertyInfo = DOMHTMLScriptElementK type AttrGetType DOMHTMLScriptElementDeferPropertyInfo = Bool type AttrLabel DOMHTMLScriptElementDeferPropertyInfo = "DOMHTMLScriptElement::defer" attrGet _ = getDOMHTMLScriptElementDefer attrSet _ = setDOMHTMLScriptElementDefer attrConstruct _ = constructDOMHTMLScriptElementDefer -- VVV Prop "event" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLScriptElementEvent :: (MonadIO m, DOMHTMLScriptElementK o) => o -> m T.Text getDOMHTMLScriptElementEvent obj = liftIO $ getObjectPropertyString obj "event" setDOMHTMLScriptElementEvent :: (MonadIO m, DOMHTMLScriptElementK o) => o -> T.Text -> m () setDOMHTMLScriptElementEvent obj val = liftIO $ setObjectPropertyString obj "event" val constructDOMHTMLScriptElementEvent :: T.Text -> IO ([Char], GValue) constructDOMHTMLScriptElementEvent val = constructObjectPropertyString "event" val data DOMHTMLScriptElementEventPropertyInfo instance AttrInfo DOMHTMLScriptElementEventPropertyInfo where type AttrAllowedOps DOMHTMLScriptElementEventPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLScriptElementEventPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLScriptElementEventPropertyInfo = DOMHTMLScriptElementK type AttrGetType DOMHTMLScriptElementEventPropertyInfo = T.Text type AttrLabel DOMHTMLScriptElementEventPropertyInfo = "DOMHTMLScriptElement::event" attrGet _ = getDOMHTMLScriptElementEvent attrSet _ = setDOMHTMLScriptElementEvent attrConstruct _ = constructDOMHTMLScriptElementEvent -- VVV Prop "html-for" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLScriptElementHtmlFor :: (MonadIO m, DOMHTMLScriptElementK o) => o -> m T.Text getDOMHTMLScriptElementHtmlFor obj = liftIO $ getObjectPropertyString obj "html-for" setDOMHTMLScriptElementHtmlFor :: (MonadIO m, DOMHTMLScriptElementK o) => o -> T.Text -> m () setDOMHTMLScriptElementHtmlFor obj val = liftIO $ setObjectPropertyString obj "html-for" val constructDOMHTMLScriptElementHtmlFor :: T.Text -> IO ([Char], GValue) constructDOMHTMLScriptElementHtmlFor val = constructObjectPropertyString "html-for" val data DOMHTMLScriptElementHtmlForPropertyInfo instance AttrInfo DOMHTMLScriptElementHtmlForPropertyInfo where type AttrAllowedOps DOMHTMLScriptElementHtmlForPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLScriptElementHtmlForPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLScriptElementHtmlForPropertyInfo = DOMHTMLScriptElementK type AttrGetType DOMHTMLScriptElementHtmlForPropertyInfo = T.Text type AttrLabel DOMHTMLScriptElementHtmlForPropertyInfo = "DOMHTMLScriptElement::html-for" attrGet _ = getDOMHTMLScriptElementHtmlFor attrSet _ = setDOMHTMLScriptElementHtmlFor attrConstruct _ = constructDOMHTMLScriptElementHtmlFor -- VVV Prop "nonce" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLScriptElementNonce :: (MonadIO m, DOMHTMLScriptElementK o) => o -> m T.Text getDOMHTMLScriptElementNonce obj = liftIO $ getObjectPropertyString obj "nonce" setDOMHTMLScriptElementNonce :: (MonadIO m, DOMHTMLScriptElementK o) => o -> T.Text -> m () setDOMHTMLScriptElementNonce obj val = liftIO $ setObjectPropertyString obj "nonce" val constructDOMHTMLScriptElementNonce :: T.Text -> IO ([Char], GValue) constructDOMHTMLScriptElementNonce val = constructObjectPropertyString "nonce" val data DOMHTMLScriptElementNoncePropertyInfo instance AttrInfo DOMHTMLScriptElementNoncePropertyInfo where type AttrAllowedOps DOMHTMLScriptElementNoncePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLScriptElementNoncePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLScriptElementNoncePropertyInfo = DOMHTMLScriptElementK type AttrGetType DOMHTMLScriptElementNoncePropertyInfo = T.Text type AttrLabel DOMHTMLScriptElementNoncePropertyInfo = "DOMHTMLScriptElement::nonce" attrGet _ = getDOMHTMLScriptElementNonce attrSet _ = setDOMHTMLScriptElementNonce attrConstruct _ = constructDOMHTMLScriptElementNonce -- VVV Prop "src" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLScriptElementSrc :: (MonadIO m, DOMHTMLScriptElementK o) => o -> m T.Text getDOMHTMLScriptElementSrc obj = liftIO $ getObjectPropertyString obj "src" setDOMHTMLScriptElementSrc :: (MonadIO m, DOMHTMLScriptElementK o) => o -> T.Text -> m () setDOMHTMLScriptElementSrc obj val = liftIO $ setObjectPropertyString obj "src" val constructDOMHTMLScriptElementSrc :: T.Text -> IO ([Char], GValue) constructDOMHTMLScriptElementSrc val = constructObjectPropertyString "src" val data DOMHTMLScriptElementSrcPropertyInfo instance AttrInfo DOMHTMLScriptElementSrcPropertyInfo where type AttrAllowedOps DOMHTMLScriptElementSrcPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLScriptElementSrcPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLScriptElementSrcPropertyInfo = DOMHTMLScriptElementK type AttrGetType DOMHTMLScriptElementSrcPropertyInfo = T.Text type AttrLabel DOMHTMLScriptElementSrcPropertyInfo = "DOMHTMLScriptElement::src" attrGet _ = getDOMHTMLScriptElementSrc attrSet _ = setDOMHTMLScriptElementSrc attrConstruct _ = constructDOMHTMLScriptElementSrc -- VVV Prop "text" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLScriptElementText :: (MonadIO m, DOMHTMLScriptElementK o) => o -> m T.Text getDOMHTMLScriptElementText obj = liftIO $ getObjectPropertyString obj "text" setDOMHTMLScriptElementText :: (MonadIO m, DOMHTMLScriptElementK o) => o -> T.Text -> m () setDOMHTMLScriptElementText obj val = liftIO $ setObjectPropertyString obj "text" val constructDOMHTMLScriptElementText :: T.Text -> IO ([Char], GValue) constructDOMHTMLScriptElementText val = constructObjectPropertyString "text" val data DOMHTMLScriptElementTextPropertyInfo instance AttrInfo DOMHTMLScriptElementTextPropertyInfo where type AttrAllowedOps DOMHTMLScriptElementTextPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLScriptElementTextPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLScriptElementTextPropertyInfo = DOMHTMLScriptElementK type AttrGetType DOMHTMLScriptElementTextPropertyInfo = T.Text type AttrLabel DOMHTMLScriptElementTextPropertyInfo = "DOMHTMLScriptElement::text" attrGet _ = getDOMHTMLScriptElementText attrSet _ = setDOMHTMLScriptElementText attrConstruct _ = constructDOMHTMLScriptElementText -- VVV Prop "type" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLScriptElementType :: (MonadIO m, DOMHTMLScriptElementK o) => o -> m T.Text getDOMHTMLScriptElementType obj = liftIO $ getObjectPropertyString obj "type" setDOMHTMLScriptElementType :: (MonadIO m, DOMHTMLScriptElementK o) => o -> T.Text -> m () setDOMHTMLScriptElementType obj val = liftIO $ setObjectPropertyString obj "type" val constructDOMHTMLScriptElementType :: T.Text -> IO ([Char], GValue) constructDOMHTMLScriptElementType val = constructObjectPropertyString "type" val data DOMHTMLScriptElementTypePropertyInfo instance AttrInfo DOMHTMLScriptElementTypePropertyInfo where type AttrAllowedOps DOMHTMLScriptElementTypePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLScriptElementTypePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLScriptElementTypePropertyInfo = DOMHTMLScriptElementK type AttrGetType DOMHTMLScriptElementTypePropertyInfo = T.Text type AttrLabel DOMHTMLScriptElementTypePropertyInfo = "DOMHTMLScriptElement::type" attrGet _ = getDOMHTMLScriptElementType attrSet _ = setDOMHTMLScriptElementType attrConstruct _ = constructDOMHTMLScriptElementType type instance AttributeList DOMHTMLScriptElement = '[ '("access-key", DOMHTMLElementAccessKeyPropertyInfo), '("async", DOMHTMLScriptElementAsyncPropertyInfo), '("attributes", DOMElementAttributesPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("charset", DOMHTMLScriptElementCharsetPropertyInfo), '("child-element-count", DOMElementChildElementCountPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("children", DOMHTMLElementChildrenPropertyInfo), '("class-list", DOMElementClassListPropertyInfo), '("class-name", DOMElementClassNamePropertyInfo), '("client-height", DOMElementClientHeightPropertyInfo), '("client-left", DOMElementClientLeftPropertyInfo), '("client-top", DOMElementClientTopPropertyInfo), '("client-width", DOMElementClientWidthPropertyInfo), '("content-editable", DOMHTMLElementContentEditablePropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("cross-origin", DOMHTMLScriptElementCrossOriginPropertyInfo), '("defer", DOMHTMLScriptElementDeferPropertyInfo), '("dir", DOMHTMLElementDirPropertyInfo), '("draggable", DOMHTMLElementDraggablePropertyInfo), '("event", DOMHTMLScriptElementEventPropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("first-element-child", DOMElementFirstElementChildPropertyInfo), '("hidden", DOMHTMLElementHiddenPropertyInfo), '("html-for", DOMHTMLScriptElementHtmlForPropertyInfo), '("id", DOMElementIdPropertyInfo), '("inner-html", DOMHTMLElementInnerHtmlPropertyInfo), '("inner-text", DOMHTMLElementInnerTextPropertyInfo), '("is-content-editable", DOMHTMLElementIsContentEditablePropertyInfo), '("lang", DOMHTMLElementLangPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-element-child", DOMElementLastElementChildPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-element-sibling", DOMElementNextElementSiblingPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("nonce", DOMHTMLScriptElementNoncePropertyInfo), '("offset-height", DOMElementOffsetHeightPropertyInfo), '("offset-left", DOMElementOffsetLeftPropertyInfo), '("offset-parent", DOMElementOffsetParentPropertyInfo), '("offset-top", DOMElementOffsetTopPropertyInfo), '("offset-width", DOMElementOffsetWidthPropertyInfo), '("outer-html", DOMHTMLElementOuterHtmlPropertyInfo), '("outer-text", DOMHTMLElementOuterTextPropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-element-sibling", DOMElementPreviousElementSiblingPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("scroll-height", DOMElementScrollHeightPropertyInfo), '("scroll-left", DOMElementScrollLeftPropertyInfo), '("scroll-top", DOMElementScrollTopPropertyInfo), '("scroll-width", DOMElementScrollWidthPropertyInfo), '("spellcheck", DOMHTMLElementSpellcheckPropertyInfo), '("src", DOMHTMLScriptElementSrcPropertyInfo), '("style", DOMElementStylePropertyInfo), '("tab-index", DOMHTMLElementTabIndexPropertyInfo), '("tag-name", DOMElementTagNamePropertyInfo), '("text", DOMHTMLScriptElementTextPropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("title", DOMHTMLElementTitlePropertyInfo), '("translate", DOMHTMLElementTranslatePropertyInfo), '("type", DOMHTMLScriptElementTypePropertyInfo), '("webkit-region-overset", DOMElementWebkitRegionOversetPropertyInfo), '("webkitdropzone", DOMHTMLElementWebkitdropzonePropertyInfo)] -- VVV Prop "autofocus" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLSelectElementAutofocus :: (MonadIO m, DOMHTMLSelectElementK o) => o -> m Bool getDOMHTMLSelectElementAutofocus obj = liftIO $ getObjectPropertyBool obj "autofocus" setDOMHTMLSelectElementAutofocus :: (MonadIO m, DOMHTMLSelectElementK o) => o -> Bool -> m () setDOMHTMLSelectElementAutofocus obj val = liftIO $ setObjectPropertyBool obj "autofocus" val constructDOMHTMLSelectElementAutofocus :: Bool -> IO ([Char], GValue) constructDOMHTMLSelectElementAutofocus val = constructObjectPropertyBool "autofocus" val data DOMHTMLSelectElementAutofocusPropertyInfo instance AttrInfo DOMHTMLSelectElementAutofocusPropertyInfo where type AttrAllowedOps DOMHTMLSelectElementAutofocusPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLSelectElementAutofocusPropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLSelectElementAutofocusPropertyInfo = DOMHTMLSelectElementK type AttrGetType DOMHTMLSelectElementAutofocusPropertyInfo = Bool type AttrLabel DOMHTMLSelectElementAutofocusPropertyInfo = "DOMHTMLSelectElement::autofocus" attrGet _ = getDOMHTMLSelectElementAutofocus attrSet _ = setDOMHTMLSelectElementAutofocus attrConstruct _ = constructDOMHTMLSelectElementAutofocus -- VVV Prop "disabled" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLSelectElementDisabled :: (MonadIO m, DOMHTMLSelectElementK o) => o -> m Bool getDOMHTMLSelectElementDisabled obj = liftIO $ getObjectPropertyBool obj "disabled" setDOMHTMLSelectElementDisabled :: (MonadIO m, DOMHTMLSelectElementK o) => o -> Bool -> m () setDOMHTMLSelectElementDisabled obj val = liftIO $ setObjectPropertyBool obj "disabled" val constructDOMHTMLSelectElementDisabled :: Bool -> IO ([Char], GValue) constructDOMHTMLSelectElementDisabled val = constructObjectPropertyBool "disabled" val data DOMHTMLSelectElementDisabledPropertyInfo instance AttrInfo DOMHTMLSelectElementDisabledPropertyInfo where type AttrAllowedOps DOMHTMLSelectElementDisabledPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLSelectElementDisabledPropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLSelectElementDisabledPropertyInfo = DOMHTMLSelectElementK type AttrGetType DOMHTMLSelectElementDisabledPropertyInfo = Bool type AttrLabel DOMHTMLSelectElementDisabledPropertyInfo = "DOMHTMLSelectElement::disabled" attrGet _ = getDOMHTMLSelectElementDisabled attrSet _ = setDOMHTMLSelectElementDisabled attrConstruct _ = constructDOMHTMLSelectElementDisabled -- VVV Prop "form" -- Type: TInterface "WebKit" "DOMHTMLFormElement" -- Flags: [PropertyReadable] getDOMHTMLSelectElementForm :: (MonadIO m, DOMHTMLSelectElementK o) => o -> m DOMHTMLFormElement getDOMHTMLSelectElementForm obj = liftIO $ getObjectPropertyObject obj "form" DOMHTMLFormElement data DOMHTMLSelectElementFormPropertyInfo instance AttrInfo DOMHTMLSelectElementFormPropertyInfo where type AttrAllowedOps DOMHTMLSelectElementFormPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLSelectElementFormPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLSelectElementFormPropertyInfo = DOMHTMLSelectElementK type AttrGetType DOMHTMLSelectElementFormPropertyInfo = DOMHTMLFormElement type AttrLabel DOMHTMLSelectElementFormPropertyInfo = "DOMHTMLSelectElement::form" attrGet _ = getDOMHTMLSelectElementForm attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "labels" -- Type: TInterface "WebKit" "DOMNodeList" -- Flags: [PropertyReadable] getDOMHTMLSelectElementLabels :: (MonadIO m, DOMHTMLSelectElementK o) => o -> m DOMNodeList getDOMHTMLSelectElementLabels obj = liftIO $ getObjectPropertyObject obj "labels" DOMNodeList data DOMHTMLSelectElementLabelsPropertyInfo instance AttrInfo DOMHTMLSelectElementLabelsPropertyInfo where type AttrAllowedOps DOMHTMLSelectElementLabelsPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLSelectElementLabelsPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLSelectElementLabelsPropertyInfo = DOMHTMLSelectElementK type AttrGetType DOMHTMLSelectElementLabelsPropertyInfo = DOMNodeList type AttrLabel DOMHTMLSelectElementLabelsPropertyInfo = "DOMHTMLSelectElement::labels" attrGet _ = getDOMHTMLSelectElementLabels attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "length" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLSelectElementLength :: (MonadIO m, DOMHTMLSelectElementK o) => o -> m Word64 getDOMHTMLSelectElementLength obj = liftIO $ getObjectPropertyUInt64 obj "length" setDOMHTMLSelectElementLength :: (MonadIO m, DOMHTMLSelectElementK o) => o -> Word64 -> m () setDOMHTMLSelectElementLength obj val = liftIO $ setObjectPropertyUInt64 obj "length" val constructDOMHTMLSelectElementLength :: Word64 -> IO ([Char], GValue) constructDOMHTMLSelectElementLength val = constructObjectPropertyUInt64 "length" val data DOMHTMLSelectElementLengthPropertyInfo instance AttrInfo DOMHTMLSelectElementLengthPropertyInfo where type AttrAllowedOps DOMHTMLSelectElementLengthPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLSelectElementLengthPropertyInfo = (~) Word64 type AttrBaseTypeConstraint DOMHTMLSelectElementLengthPropertyInfo = DOMHTMLSelectElementK type AttrGetType DOMHTMLSelectElementLengthPropertyInfo = Word64 type AttrLabel DOMHTMLSelectElementLengthPropertyInfo = "DOMHTMLSelectElement::length" attrGet _ = getDOMHTMLSelectElementLength attrSet _ = setDOMHTMLSelectElementLength attrConstruct _ = constructDOMHTMLSelectElementLength -- VVV Prop "multiple" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLSelectElementMultiple :: (MonadIO m, DOMHTMLSelectElementK o) => o -> m Bool getDOMHTMLSelectElementMultiple obj = liftIO $ getObjectPropertyBool obj "multiple" setDOMHTMLSelectElementMultiple :: (MonadIO m, DOMHTMLSelectElementK o) => o -> Bool -> m () setDOMHTMLSelectElementMultiple obj val = liftIO $ setObjectPropertyBool obj "multiple" val constructDOMHTMLSelectElementMultiple :: Bool -> IO ([Char], GValue) constructDOMHTMLSelectElementMultiple val = constructObjectPropertyBool "multiple" val data DOMHTMLSelectElementMultiplePropertyInfo instance AttrInfo DOMHTMLSelectElementMultiplePropertyInfo where type AttrAllowedOps DOMHTMLSelectElementMultiplePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLSelectElementMultiplePropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLSelectElementMultiplePropertyInfo = DOMHTMLSelectElementK type AttrGetType DOMHTMLSelectElementMultiplePropertyInfo = Bool type AttrLabel DOMHTMLSelectElementMultiplePropertyInfo = "DOMHTMLSelectElement::multiple" attrGet _ = getDOMHTMLSelectElementMultiple attrSet _ = setDOMHTMLSelectElementMultiple attrConstruct _ = constructDOMHTMLSelectElementMultiple -- VVV Prop "name" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLSelectElementName :: (MonadIO m, DOMHTMLSelectElementK o) => o -> m T.Text getDOMHTMLSelectElementName obj = liftIO $ getObjectPropertyString obj "name" setDOMHTMLSelectElementName :: (MonadIO m, DOMHTMLSelectElementK o) => o -> T.Text -> m () setDOMHTMLSelectElementName obj val = liftIO $ setObjectPropertyString obj "name" val constructDOMHTMLSelectElementName :: T.Text -> IO ([Char], GValue) constructDOMHTMLSelectElementName val = constructObjectPropertyString "name" val data DOMHTMLSelectElementNamePropertyInfo instance AttrInfo DOMHTMLSelectElementNamePropertyInfo where type AttrAllowedOps DOMHTMLSelectElementNamePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLSelectElementNamePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLSelectElementNamePropertyInfo = DOMHTMLSelectElementK type AttrGetType DOMHTMLSelectElementNamePropertyInfo = T.Text type AttrLabel DOMHTMLSelectElementNamePropertyInfo = "DOMHTMLSelectElement::name" attrGet _ = getDOMHTMLSelectElementName attrSet _ = setDOMHTMLSelectElementName attrConstruct _ = constructDOMHTMLSelectElementName -- VVV Prop "options" -- Type: TInterface "WebKit" "DOMHTMLOptionsCollection" -- Flags: [PropertyReadable] getDOMHTMLSelectElementOptions :: (MonadIO m, DOMHTMLSelectElementK o) => o -> m DOMHTMLOptionsCollection getDOMHTMLSelectElementOptions obj = liftIO $ getObjectPropertyObject obj "options" DOMHTMLOptionsCollection data DOMHTMLSelectElementOptionsPropertyInfo instance AttrInfo DOMHTMLSelectElementOptionsPropertyInfo where type AttrAllowedOps DOMHTMLSelectElementOptionsPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLSelectElementOptionsPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLSelectElementOptionsPropertyInfo = DOMHTMLSelectElementK type AttrGetType DOMHTMLSelectElementOptionsPropertyInfo = DOMHTMLOptionsCollection type AttrLabel DOMHTMLSelectElementOptionsPropertyInfo = "DOMHTMLSelectElement::options" attrGet _ = getDOMHTMLSelectElementOptions attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "required" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLSelectElementRequired :: (MonadIO m, DOMHTMLSelectElementK o) => o -> m Bool getDOMHTMLSelectElementRequired obj = liftIO $ getObjectPropertyBool obj "required" setDOMHTMLSelectElementRequired :: (MonadIO m, DOMHTMLSelectElementK o) => o -> Bool -> m () setDOMHTMLSelectElementRequired obj val = liftIO $ setObjectPropertyBool obj "required" val constructDOMHTMLSelectElementRequired :: Bool -> IO ([Char], GValue) constructDOMHTMLSelectElementRequired val = constructObjectPropertyBool "required" val data DOMHTMLSelectElementRequiredPropertyInfo instance AttrInfo DOMHTMLSelectElementRequiredPropertyInfo where type AttrAllowedOps DOMHTMLSelectElementRequiredPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLSelectElementRequiredPropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLSelectElementRequiredPropertyInfo = DOMHTMLSelectElementK type AttrGetType DOMHTMLSelectElementRequiredPropertyInfo = Bool type AttrLabel DOMHTMLSelectElementRequiredPropertyInfo = "DOMHTMLSelectElement::required" attrGet _ = getDOMHTMLSelectElementRequired attrSet _ = setDOMHTMLSelectElementRequired attrConstruct _ = constructDOMHTMLSelectElementRequired -- VVV Prop "selected-index" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLSelectElementSelectedIndex :: (MonadIO m, DOMHTMLSelectElementK o) => o -> m Int64 getDOMHTMLSelectElementSelectedIndex obj = liftIO $ getObjectPropertyInt64 obj "selected-index" setDOMHTMLSelectElementSelectedIndex :: (MonadIO m, DOMHTMLSelectElementK o) => o -> Int64 -> m () setDOMHTMLSelectElementSelectedIndex obj val = liftIO $ setObjectPropertyInt64 obj "selected-index" val constructDOMHTMLSelectElementSelectedIndex :: Int64 -> IO ([Char], GValue) constructDOMHTMLSelectElementSelectedIndex val = constructObjectPropertyInt64 "selected-index" val data DOMHTMLSelectElementSelectedIndexPropertyInfo instance AttrInfo DOMHTMLSelectElementSelectedIndexPropertyInfo where type AttrAllowedOps DOMHTMLSelectElementSelectedIndexPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLSelectElementSelectedIndexPropertyInfo = (~) Int64 type AttrBaseTypeConstraint DOMHTMLSelectElementSelectedIndexPropertyInfo = DOMHTMLSelectElementK type AttrGetType DOMHTMLSelectElementSelectedIndexPropertyInfo = Int64 type AttrLabel DOMHTMLSelectElementSelectedIndexPropertyInfo = "DOMHTMLSelectElement::selected-index" attrGet _ = getDOMHTMLSelectElementSelectedIndex attrSet _ = setDOMHTMLSelectElementSelectedIndex attrConstruct _ = constructDOMHTMLSelectElementSelectedIndex -- VVV Prop "selected-options" -- Type: TInterface "WebKit" "DOMHTMLCollection" -- Flags: [PropertyReadable] getDOMHTMLSelectElementSelectedOptions :: (MonadIO m, DOMHTMLSelectElementK o) => o -> m DOMHTMLCollection getDOMHTMLSelectElementSelectedOptions obj = liftIO $ getObjectPropertyObject obj "selected-options" DOMHTMLCollection data DOMHTMLSelectElementSelectedOptionsPropertyInfo instance AttrInfo DOMHTMLSelectElementSelectedOptionsPropertyInfo where type AttrAllowedOps DOMHTMLSelectElementSelectedOptionsPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLSelectElementSelectedOptionsPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLSelectElementSelectedOptionsPropertyInfo = DOMHTMLSelectElementK type AttrGetType DOMHTMLSelectElementSelectedOptionsPropertyInfo = DOMHTMLCollection type AttrLabel DOMHTMLSelectElementSelectedOptionsPropertyInfo = "DOMHTMLSelectElement::selected-options" attrGet _ = getDOMHTMLSelectElementSelectedOptions attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "size" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLSelectElementSize :: (MonadIO m, DOMHTMLSelectElementK o) => o -> m Int64 getDOMHTMLSelectElementSize obj = liftIO $ getObjectPropertyInt64 obj "size" setDOMHTMLSelectElementSize :: (MonadIO m, DOMHTMLSelectElementK o) => o -> Int64 -> m () setDOMHTMLSelectElementSize obj val = liftIO $ setObjectPropertyInt64 obj "size" val constructDOMHTMLSelectElementSize :: Int64 -> IO ([Char], GValue) constructDOMHTMLSelectElementSize val = constructObjectPropertyInt64 "size" val data DOMHTMLSelectElementSizePropertyInfo instance AttrInfo DOMHTMLSelectElementSizePropertyInfo where type AttrAllowedOps DOMHTMLSelectElementSizePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLSelectElementSizePropertyInfo = (~) Int64 type AttrBaseTypeConstraint DOMHTMLSelectElementSizePropertyInfo = DOMHTMLSelectElementK type AttrGetType DOMHTMLSelectElementSizePropertyInfo = Int64 type AttrLabel DOMHTMLSelectElementSizePropertyInfo = "DOMHTMLSelectElement::size" attrGet _ = getDOMHTMLSelectElementSize attrSet _ = setDOMHTMLSelectElementSize attrConstruct _ = constructDOMHTMLSelectElementSize -- VVV Prop "type" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMHTMLSelectElementType :: (MonadIO m, DOMHTMLSelectElementK o) => o -> m T.Text getDOMHTMLSelectElementType obj = liftIO $ getObjectPropertyString obj "type" data DOMHTMLSelectElementTypePropertyInfo instance AttrInfo DOMHTMLSelectElementTypePropertyInfo where type AttrAllowedOps DOMHTMLSelectElementTypePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLSelectElementTypePropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLSelectElementTypePropertyInfo = DOMHTMLSelectElementK type AttrGetType DOMHTMLSelectElementTypePropertyInfo = T.Text type AttrLabel DOMHTMLSelectElementTypePropertyInfo = "DOMHTMLSelectElement::type" attrGet _ = getDOMHTMLSelectElementType attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "validation-message" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMHTMLSelectElementValidationMessage :: (MonadIO m, DOMHTMLSelectElementK o) => o -> m T.Text getDOMHTMLSelectElementValidationMessage obj = liftIO $ getObjectPropertyString obj "validation-message" data DOMHTMLSelectElementValidationMessagePropertyInfo instance AttrInfo DOMHTMLSelectElementValidationMessagePropertyInfo where type AttrAllowedOps DOMHTMLSelectElementValidationMessagePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLSelectElementValidationMessagePropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLSelectElementValidationMessagePropertyInfo = DOMHTMLSelectElementK type AttrGetType DOMHTMLSelectElementValidationMessagePropertyInfo = T.Text type AttrLabel DOMHTMLSelectElementValidationMessagePropertyInfo = "DOMHTMLSelectElement::validation-message" attrGet _ = getDOMHTMLSelectElementValidationMessage attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "validity" -- Type: TInterface "WebKit" "DOMValidityState" -- Flags: [PropertyReadable] getDOMHTMLSelectElementValidity :: (MonadIO m, DOMHTMLSelectElementK o) => o -> m DOMValidityState getDOMHTMLSelectElementValidity obj = liftIO $ getObjectPropertyObject obj "validity" DOMValidityState data DOMHTMLSelectElementValidityPropertyInfo instance AttrInfo DOMHTMLSelectElementValidityPropertyInfo where type AttrAllowedOps DOMHTMLSelectElementValidityPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLSelectElementValidityPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLSelectElementValidityPropertyInfo = DOMHTMLSelectElementK type AttrGetType DOMHTMLSelectElementValidityPropertyInfo = DOMValidityState type AttrLabel DOMHTMLSelectElementValidityPropertyInfo = "DOMHTMLSelectElement::validity" attrGet _ = getDOMHTMLSelectElementValidity attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "value" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLSelectElementValue :: (MonadIO m, DOMHTMLSelectElementK o) => o -> m T.Text getDOMHTMLSelectElementValue obj = liftIO $ getObjectPropertyString obj "value" setDOMHTMLSelectElementValue :: (MonadIO m, DOMHTMLSelectElementK o) => o -> T.Text -> m () setDOMHTMLSelectElementValue obj val = liftIO $ setObjectPropertyString obj "value" val constructDOMHTMLSelectElementValue :: T.Text -> IO ([Char], GValue) constructDOMHTMLSelectElementValue val = constructObjectPropertyString "value" val data DOMHTMLSelectElementValuePropertyInfo instance AttrInfo DOMHTMLSelectElementValuePropertyInfo where type AttrAllowedOps DOMHTMLSelectElementValuePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLSelectElementValuePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLSelectElementValuePropertyInfo = DOMHTMLSelectElementK type AttrGetType DOMHTMLSelectElementValuePropertyInfo = T.Text type AttrLabel DOMHTMLSelectElementValuePropertyInfo = "DOMHTMLSelectElement::value" attrGet _ = getDOMHTMLSelectElementValue attrSet _ = setDOMHTMLSelectElementValue attrConstruct _ = constructDOMHTMLSelectElementValue -- VVV Prop "will-validate" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMHTMLSelectElementWillValidate :: (MonadIO m, DOMHTMLSelectElementK o) => o -> m Bool getDOMHTMLSelectElementWillValidate obj = liftIO $ getObjectPropertyBool obj "will-validate" data DOMHTMLSelectElementWillValidatePropertyInfo instance AttrInfo DOMHTMLSelectElementWillValidatePropertyInfo where type AttrAllowedOps DOMHTMLSelectElementWillValidatePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLSelectElementWillValidatePropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLSelectElementWillValidatePropertyInfo = DOMHTMLSelectElementK type AttrGetType DOMHTMLSelectElementWillValidatePropertyInfo = Bool type AttrLabel DOMHTMLSelectElementWillValidatePropertyInfo = "DOMHTMLSelectElement::will-validate" attrGet _ = getDOMHTMLSelectElementWillValidate attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMHTMLSelectElement = '[ '("access-key", DOMHTMLElementAccessKeyPropertyInfo), '("attributes", DOMElementAttributesPropertyInfo), '("autofocus", DOMHTMLSelectElementAutofocusPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("child-element-count", DOMElementChildElementCountPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("children", DOMHTMLElementChildrenPropertyInfo), '("class-list", DOMElementClassListPropertyInfo), '("class-name", DOMElementClassNamePropertyInfo), '("client-height", DOMElementClientHeightPropertyInfo), '("client-left", DOMElementClientLeftPropertyInfo), '("client-top", DOMElementClientTopPropertyInfo), '("client-width", DOMElementClientWidthPropertyInfo), '("content-editable", DOMHTMLElementContentEditablePropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("dir", DOMHTMLElementDirPropertyInfo), '("disabled", DOMHTMLSelectElementDisabledPropertyInfo), '("draggable", DOMHTMLElementDraggablePropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("first-element-child", DOMElementFirstElementChildPropertyInfo), '("form", DOMHTMLSelectElementFormPropertyInfo), '("hidden", DOMHTMLElementHiddenPropertyInfo), '("id", DOMElementIdPropertyInfo), '("inner-html", DOMHTMLElementInnerHtmlPropertyInfo), '("inner-text", DOMHTMLElementInnerTextPropertyInfo), '("is-content-editable", DOMHTMLElementIsContentEditablePropertyInfo), '("labels", DOMHTMLSelectElementLabelsPropertyInfo), '("lang", DOMHTMLElementLangPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-element-child", DOMElementLastElementChildPropertyInfo), '("length", DOMHTMLSelectElementLengthPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("multiple", DOMHTMLSelectElementMultiplePropertyInfo), '("name", DOMHTMLSelectElementNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-element-sibling", DOMElementNextElementSiblingPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("offset-height", DOMElementOffsetHeightPropertyInfo), '("offset-left", DOMElementOffsetLeftPropertyInfo), '("offset-parent", DOMElementOffsetParentPropertyInfo), '("offset-top", DOMElementOffsetTopPropertyInfo), '("offset-width", DOMElementOffsetWidthPropertyInfo), '("options", DOMHTMLSelectElementOptionsPropertyInfo), '("outer-html", DOMHTMLElementOuterHtmlPropertyInfo), '("outer-text", DOMHTMLElementOuterTextPropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-element-sibling", DOMElementPreviousElementSiblingPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("required", DOMHTMLSelectElementRequiredPropertyInfo), '("scroll-height", DOMElementScrollHeightPropertyInfo), '("scroll-left", DOMElementScrollLeftPropertyInfo), '("scroll-top", DOMElementScrollTopPropertyInfo), '("scroll-width", DOMElementScrollWidthPropertyInfo), '("selected-index", DOMHTMLSelectElementSelectedIndexPropertyInfo), '("selected-options", DOMHTMLSelectElementSelectedOptionsPropertyInfo), '("size", DOMHTMLSelectElementSizePropertyInfo), '("spellcheck", DOMHTMLElementSpellcheckPropertyInfo), '("style", DOMElementStylePropertyInfo), '("tab-index", DOMHTMLElementTabIndexPropertyInfo), '("tag-name", DOMElementTagNamePropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("title", DOMHTMLElementTitlePropertyInfo), '("translate", DOMHTMLElementTranslatePropertyInfo), '("type", DOMHTMLSelectElementTypePropertyInfo), '("validation-message", DOMHTMLSelectElementValidationMessagePropertyInfo), '("validity", DOMHTMLSelectElementValidityPropertyInfo), '("value", DOMHTMLSelectElementValuePropertyInfo), '("webkit-region-overset", DOMElementWebkitRegionOversetPropertyInfo), '("webkitdropzone", DOMHTMLElementWebkitdropzonePropertyInfo), '("will-validate", DOMHTMLSelectElementWillValidatePropertyInfo)] -- VVV Prop "disabled" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLStyleElementDisabled :: (MonadIO m, DOMHTMLStyleElementK o) => o -> m Bool getDOMHTMLStyleElementDisabled obj = liftIO $ getObjectPropertyBool obj "disabled" setDOMHTMLStyleElementDisabled :: (MonadIO m, DOMHTMLStyleElementK o) => o -> Bool -> m () setDOMHTMLStyleElementDisabled obj val = liftIO $ setObjectPropertyBool obj "disabled" val constructDOMHTMLStyleElementDisabled :: Bool -> IO ([Char], GValue) constructDOMHTMLStyleElementDisabled val = constructObjectPropertyBool "disabled" val data DOMHTMLStyleElementDisabledPropertyInfo instance AttrInfo DOMHTMLStyleElementDisabledPropertyInfo where type AttrAllowedOps DOMHTMLStyleElementDisabledPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLStyleElementDisabledPropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLStyleElementDisabledPropertyInfo = DOMHTMLStyleElementK type AttrGetType DOMHTMLStyleElementDisabledPropertyInfo = Bool type AttrLabel DOMHTMLStyleElementDisabledPropertyInfo = "DOMHTMLStyleElement::disabled" attrGet _ = getDOMHTMLStyleElementDisabled attrSet _ = setDOMHTMLStyleElementDisabled attrConstruct _ = constructDOMHTMLStyleElementDisabled -- VVV Prop "media" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLStyleElementMedia :: (MonadIO m, DOMHTMLStyleElementK o) => o -> m T.Text getDOMHTMLStyleElementMedia obj = liftIO $ getObjectPropertyString obj "media" setDOMHTMLStyleElementMedia :: (MonadIO m, DOMHTMLStyleElementK o) => o -> T.Text -> m () setDOMHTMLStyleElementMedia obj val = liftIO $ setObjectPropertyString obj "media" val constructDOMHTMLStyleElementMedia :: T.Text -> IO ([Char], GValue) constructDOMHTMLStyleElementMedia val = constructObjectPropertyString "media" val data DOMHTMLStyleElementMediaPropertyInfo instance AttrInfo DOMHTMLStyleElementMediaPropertyInfo where type AttrAllowedOps DOMHTMLStyleElementMediaPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLStyleElementMediaPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLStyleElementMediaPropertyInfo = DOMHTMLStyleElementK type AttrGetType DOMHTMLStyleElementMediaPropertyInfo = T.Text type AttrLabel DOMHTMLStyleElementMediaPropertyInfo = "DOMHTMLStyleElement::media" attrGet _ = getDOMHTMLStyleElementMedia attrSet _ = setDOMHTMLStyleElementMedia attrConstruct _ = constructDOMHTMLStyleElementMedia -- VVV Prop "sheet" -- Type: TInterface "WebKit" "DOMStyleSheet" -- Flags: [PropertyReadable] getDOMHTMLStyleElementSheet :: (MonadIO m, DOMHTMLStyleElementK o) => o -> m DOMStyleSheet getDOMHTMLStyleElementSheet obj = liftIO $ getObjectPropertyObject obj "sheet" DOMStyleSheet data DOMHTMLStyleElementSheetPropertyInfo instance AttrInfo DOMHTMLStyleElementSheetPropertyInfo where type AttrAllowedOps DOMHTMLStyleElementSheetPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLStyleElementSheetPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLStyleElementSheetPropertyInfo = DOMHTMLStyleElementK type AttrGetType DOMHTMLStyleElementSheetPropertyInfo = DOMStyleSheet type AttrLabel DOMHTMLStyleElementSheetPropertyInfo = "DOMHTMLStyleElement::sheet" attrGet _ = getDOMHTMLStyleElementSheet attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "type" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLStyleElementType :: (MonadIO m, DOMHTMLStyleElementK o) => o -> m T.Text getDOMHTMLStyleElementType obj = liftIO $ getObjectPropertyString obj "type" setDOMHTMLStyleElementType :: (MonadIO m, DOMHTMLStyleElementK o) => o -> T.Text -> m () setDOMHTMLStyleElementType obj val = liftIO $ setObjectPropertyString obj "type" val constructDOMHTMLStyleElementType :: T.Text -> IO ([Char], GValue) constructDOMHTMLStyleElementType val = constructObjectPropertyString "type" val data DOMHTMLStyleElementTypePropertyInfo instance AttrInfo DOMHTMLStyleElementTypePropertyInfo where type AttrAllowedOps DOMHTMLStyleElementTypePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLStyleElementTypePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLStyleElementTypePropertyInfo = DOMHTMLStyleElementK type AttrGetType DOMHTMLStyleElementTypePropertyInfo = T.Text type AttrLabel DOMHTMLStyleElementTypePropertyInfo = "DOMHTMLStyleElement::type" attrGet _ = getDOMHTMLStyleElementType attrSet _ = setDOMHTMLStyleElementType attrConstruct _ = constructDOMHTMLStyleElementType type instance AttributeList DOMHTMLStyleElement = '[ '("access-key", DOMHTMLElementAccessKeyPropertyInfo), '("attributes", DOMElementAttributesPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("child-element-count", DOMElementChildElementCountPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("children", DOMHTMLElementChildrenPropertyInfo), '("class-list", DOMElementClassListPropertyInfo), '("class-name", DOMElementClassNamePropertyInfo), '("client-height", DOMElementClientHeightPropertyInfo), '("client-left", DOMElementClientLeftPropertyInfo), '("client-top", DOMElementClientTopPropertyInfo), '("client-width", DOMElementClientWidthPropertyInfo), '("content-editable", DOMHTMLElementContentEditablePropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("dir", DOMHTMLElementDirPropertyInfo), '("disabled", DOMHTMLStyleElementDisabledPropertyInfo), '("draggable", DOMHTMLElementDraggablePropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("first-element-child", DOMElementFirstElementChildPropertyInfo), '("hidden", DOMHTMLElementHiddenPropertyInfo), '("id", DOMElementIdPropertyInfo), '("inner-html", DOMHTMLElementInnerHtmlPropertyInfo), '("inner-text", DOMHTMLElementInnerTextPropertyInfo), '("is-content-editable", DOMHTMLElementIsContentEditablePropertyInfo), '("lang", DOMHTMLElementLangPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-element-child", DOMElementLastElementChildPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("media", DOMHTMLStyleElementMediaPropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-element-sibling", DOMElementNextElementSiblingPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("offset-height", DOMElementOffsetHeightPropertyInfo), '("offset-left", DOMElementOffsetLeftPropertyInfo), '("offset-parent", DOMElementOffsetParentPropertyInfo), '("offset-top", DOMElementOffsetTopPropertyInfo), '("offset-width", DOMElementOffsetWidthPropertyInfo), '("outer-html", DOMHTMLElementOuterHtmlPropertyInfo), '("outer-text", DOMHTMLElementOuterTextPropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-element-sibling", DOMElementPreviousElementSiblingPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("scroll-height", DOMElementScrollHeightPropertyInfo), '("scroll-left", DOMElementScrollLeftPropertyInfo), '("scroll-top", DOMElementScrollTopPropertyInfo), '("scroll-width", DOMElementScrollWidthPropertyInfo), '("sheet", DOMHTMLStyleElementSheetPropertyInfo), '("spellcheck", DOMHTMLElementSpellcheckPropertyInfo), '("style", DOMElementStylePropertyInfo), '("tab-index", DOMHTMLElementTabIndexPropertyInfo), '("tag-name", DOMElementTagNamePropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("title", DOMHTMLElementTitlePropertyInfo), '("translate", DOMHTMLElementTranslatePropertyInfo), '("type", DOMHTMLStyleElementTypePropertyInfo), '("webkit-region-overset", DOMElementWebkitRegionOversetPropertyInfo), '("webkitdropzone", DOMHTMLElementWebkitdropzonePropertyInfo)] -- VVV Prop "align" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLTableCaptionElementAlign :: (MonadIO m, DOMHTMLTableCaptionElementK o) => o -> m T.Text getDOMHTMLTableCaptionElementAlign obj = liftIO $ getObjectPropertyString obj "align" setDOMHTMLTableCaptionElementAlign :: (MonadIO m, DOMHTMLTableCaptionElementK o) => o -> T.Text -> m () setDOMHTMLTableCaptionElementAlign obj val = liftIO $ setObjectPropertyString obj "align" val constructDOMHTMLTableCaptionElementAlign :: T.Text -> IO ([Char], GValue) constructDOMHTMLTableCaptionElementAlign val = constructObjectPropertyString "align" val data DOMHTMLTableCaptionElementAlignPropertyInfo instance AttrInfo DOMHTMLTableCaptionElementAlignPropertyInfo where type AttrAllowedOps DOMHTMLTableCaptionElementAlignPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLTableCaptionElementAlignPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLTableCaptionElementAlignPropertyInfo = DOMHTMLTableCaptionElementK type AttrGetType DOMHTMLTableCaptionElementAlignPropertyInfo = T.Text type AttrLabel DOMHTMLTableCaptionElementAlignPropertyInfo = "DOMHTMLTableCaptionElement::align" attrGet _ = getDOMHTMLTableCaptionElementAlign attrSet _ = setDOMHTMLTableCaptionElementAlign attrConstruct _ = constructDOMHTMLTableCaptionElementAlign type instance AttributeList DOMHTMLTableCaptionElement = '[ '("access-key", DOMHTMLElementAccessKeyPropertyInfo), '("align", DOMHTMLTableCaptionElementAlignPropertyInfo), '("attributes", DOMElementAttributesPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("child-element-count", DOMElementChildElementCountPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("children", DOMHTMLElementChildrenPropertyInfo), '("class-list", DOMElementClassListPropertyInfo), '("class-name", DOMElementClassNamePropertyInfo), '("client-height", DOMElementClientHeightPropertyInfo), '("client-left", DOMElementClientLeftPropertyInfo), '("client-top", DOMElementClientTopPropertyInfo), '("client-width", DOMElementClientWidthPropertyInfo), '("content-editable", DOMHTMLElementContentEditablePropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("dir", DOMHTMLElementDirPropertyInfo), '("draggable", DOMHTMLElementDraggablePropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("first-element-child", DOMElementFirstElementChildPropertyInfo), '("hidden", DOMHTMLElementHiddenPropertyInfo), '("id", DOMElementIdPropertyInfo), '("inner-html", DOMHTMLElementInnerHtmlPropertyInfo), '("inner-text", DOMHTMLElementInnerTextPropertyInfo), '("is-content-editable", DOMHTMLElementIsContentEditablePropertyInfo), '("lang", DOMHTMLElementLangPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-element-child", DOMElementLastElementChildPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-element-sibling", DOMElementNextElementSiblingPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("offset-height", DOMElementOffsetHeightPropertyInfo), '("offset-left", DOMElementOffsetLeftPropertyInfo), '("offset-parent", DOMElementOffsetParentPropertyInfo), '("offset-top", DOMElementOffsetTopPropertyInfo), '("offset-width", DOMElementOffsetWidthPropertyInfo), '("outer-html", DOMHTMLElementOuterHtmlPropertyInfo), '("outer-text", DOMHTMLElementOuterTextPropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-element-sibling", DOMElementPreviousElementSiblingPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("scroll-height", DOMElementScrollHeightPropertyInfo), '("scroll-left", DOMElementScrollLeftPropertyInfo), '("scroll-top", DOMElementScrollTopPropertyInfo), '("scroll-width", DOMElementScrollWidthPropertyInfo), '("spellcheck", DOMHTMLElementSpellcheckPropertyInfo), '("style", DOMElementStylePropertyInfo), '("tab-index", DOMHTMLElementTabIndexPropertyInfo), '("tag-name", DOMElementTagNamePropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("title", DOMHTMLElementTitlePropertyInfo), '("translate", DOMHTMLElementTranslatePropertyInfo), '("webkit-region-overset", DOMElementWebkitRegionOversetPropertyInfo), '("webkitdropzone", DOMHTMLElementWebkitdropzonePropertyInfo)] -- VVV Prop "abbr" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLTableCellElementAbbr :: (MonadIO m, DOMHTMLTableCellElementK o) => o -> m T.Text getDOMHTMLTableCellElementAbbr obj = liftIO $ getObjectPropertyString obj "abbr" setDOMHTMLTableCellElementAbbr :: (MonadIO m, DOMHTMLTableCellElementK o) => o -> T.Text -> m () setDOMHTMLTableCellElementAbbr obj val = liftIO $ setObjectPropertyString obj "abbr" val constructDOMHTMLTableCellElementAbbr :: T.Text -> IO ([Char], GValue) constructDOMHTMLTableCellElementAbbr val = constructObjectPropertyString "abbr" val data DOMHTMLTableCellElementAbbrPropertyInfo instance AttrInfo DOMHTMLTableCellElementAbbrPropertyInfo where type AttrAllowedOps DOMHTMLTableCellElementAbbrPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLTableCellElementAbbrPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLTableCellElementAbbrPropertyInfo = DOMHTMLTableCellElementK type AttrGetType DOMHTMLTableCellElementAbbrPropertyInfo = T.Text type AttrLabel DOMHTMLTableCellElementAbbrPropertyInfo = "DOMHTMLTableCellElement::abbr" attrGet _ = getDOMHTMLTableCellElementAbbr attrSet _ = setDOMHTMLTableCellElementAbbr attrConstruct _ = constructDOMHTMLTableCellElementAbbr -- VVV Prop "align" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLTableCellElementAlign :: (MonadIO m, DOMHTMLTableCellElementK o) => o -> m T.Text getDOMHTMLTableCellElementAlign obj = liftIO $ getObjectPropertyString obj "align" setDOMHTMLTableCellElementAlign :: (MonadIO m, DOMHTMLTableCellElementK o) => o -> T.Text -> m () setDOMHTMLTableCellElementAlign obj val = liftIO $ setObjectPropertyString obj "align" val constructDOMHTMLTableCellElementAlign :: T.Text -> IO ([Char], GValue) constructDOMHTMLTableCellElementAlign val = constructObjectPropertyString "align" val data DOMHTMLTableCellElementAlignPropertyInfo instance AttrInfo DOMHTMLTableCellElementAlignPropertyInfo where type AttrAllowedOps DOMHTMLTableCellElementAlignPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLTableCellElementAlignPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLTableCellElementAlignPropertyInfo = DOMHTMLTableCellElementK type AttrGetType DOMHTMLTableCellElementAlignPropertyInfo = T.Text type AttrLabel DOMHTMLTableCellElementAlignPropertyInfo = "DOMHTMLTableCellElement::align" attrGet _ = getDOMHTMLTableCellElementAlign attrSet _ = setDOMHTMLTableCellElementAlign attrConstruct _ = constructDOMHTMLTableCellElementAlign -- VVV Prop "axis" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLTableCellElementAxis :: (MonadIO m, DOMHTMLTableCellElementK o) => o -> m T.Text getDOMHTMLTableCellElementAxis obj = liftIO $ getObjectPropertyString obj "axis" setDOMHTMLTableCellElementAxis :: (MonadIO m, DOMHTMLTableCellElementK o) => o -> T.Text -> m () setDOMHTMLTableCellElementAxis obj val = liftIO $ setObjectPropertyString obj "axis" val constructDOMHTMLTableCellElementAxis :: T.Text -> IO ([Char], GValue) constructDOMHTMLTableCellElementAxis val = constructObjectPropertyString "axis" val data DOMHTMLTableCellElementAxisPropertyInfo instance AttrInfo DOMHTMLTableCellElementAxisPropertyInfo where type AttrAllowedOps DOMHTMLTableCellElementAxisPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLTableCellElementAxisPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLTableCellElementAxisPropertyInfo = DOMHTMLTableCellElementK type AttrGetType DOMHTMLTableCellElementAxisPropertyInfo = T.Text type AttrLabel DOMHTMLTableCellElementAxisPropertyInfo = "DOMHTMLTableCellElement::axis" attrGet _ = getDOMHTMLTableCellElementAxis attrSet _ = setDOMHTMLTableCellElementAxis attrConstruct _ = constructDOMHTMLTableCellElementAxis -- VVV Prop "bg-color" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLTableCellElementBgColor :: (MonadIO m, DOMHTMLTableCellElementK o) => o -> m T.Text getDOMHTMLTableCellElementBgColor obj = liftIO $ getObjectPropertyString obj "bg-color" setDOMHTMLTableCellElementBgColor :: (MonadIO m, DOMHTMLTableCellElementK o) => o -> T.Text -> m () setDOMHTMLTableCellElementBgColor obj val = liftIO $ setObjectPropertyString obj "bg-color" val constructDOMHTMLTableCellElementBgColor :: T.Text -> IO ([Char], GValue) constructDOMHTMLTableCellElementBgColor val = constructObjectPropertyString "bg-color" val data DOMHTMLTableCellElementBgColorPropertyInfo instance AttrInfo DOMHTMLTableCellElementBgColorPropertyInfo where type AttrAllowedOps DOMHTMLTableCellElementBgColorPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLTableCellElementBgColorPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLTableCellElementBgColorPropertyInfo = DOMHTMLTableCellElementK type AttrGetType DOMHTMLTableCellElementBgColorPropertyInfo = T.Text type AttrLabel DOMHTMLTableCellElementBgColorPropertyInfo = "DOMHTMLTableCellElement::bg-color" attrGet _ = getDOMHTMLTableCellElementBgColor attrSet _ = setDOMHTMLTableCellElementBgColor attrConstruct _ = constructDOMHTMLTableCellElementBgColor -- VVV Prop "cell-index" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMHTMLTableCellElementCellIndex :: (MonadIO m, DOMHTMLTableCellElementK o) => o -> m Int64 getDOMHTMLTableCellElementCellIndex obj = liftIO $ getObjectPropertyInt64 obj "cell-index" data DOMHTMLTableCellElementCellIndexPropertyInfo instance AttrInfo DOMHTMLTableCellElementCellIndexPropertyInfo where type AttrAllowedOps DOMHTMLTableCellElementCellIndexPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLTableCellElementCellIndexPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLTableCellElementCellIndexPropertyInfo = DOMHTMLTableCellElementK type AttrGetType DOMHTMLTableCellElementCellIndexPropertyInfo = Int64 type AttrLabel DOMHTMLTableCellElementCellIndexPropertyInfo = "DOMHTMLTableCellElement::cell-index" attrGet _ = getDOMHTMLTableCellElementCellIndex attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "ch" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLTableCellElementCh :: (MonadIO m, DOMHTMLTableCellElementK o) => o -> m T.Text getDOMHTMLTableCellElementCh obj = liftIO $ getObjectPropertyString obj "ch" setDOMHTMLTableCellElementCh :: (MonadIO m, DOMHTMLTableCellElementK o) => o -> T.Text -> m () setDOMHTMLTableCellElementCh obj val = liftIO $ setObjectPropertyString obj "ch" val constructDOMHTMLTableCellElementCh :: T.Text -> IO ([Char], GValue) constructDOMHTMLTableCellElementCh val = constructObjectPropertyString "ch" val data DOMHTMLTableCellElementChPropertyInfo instance AttrInfo DOMHTMLTableCellElementChPropertyInfo where type AttrAllowedOps DOMHTMLTableCellElementChPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLTableCellElementChPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLTableCellElementChPropertyInfo = DOMHTMLTableCellElementK type AttrGetType DOMHTMLTableCellElementChPropertyInfo = T.Text type AttrLabel DOMHTMLTableCellElementChPropertyInfo = "DOMHTMLTableCellElement::ch" attrGet _ = getDOMHTMLTableCellElementCh attrSet _ = setDOMHTMLTableCellElementCh attrConstruct _ = constructDOMHTMLTableCellElementCh -- VVV Prop "ch-off" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLTableCellElementChOff :: (MonadIO m, DOMHTMLTableCellElementK o) => o -> m T.Text getDOMHTMLTableCellElementChOff obj = liftIO $ getObjectPropertyString obj "ch-off" setDOMHTMLTableCellElementChOff :: (MonadIO m, DOMHTMLTableCellElementK o) => o -> T.Text -> m () setDOMHTMLTableCellElementChOff obj val = liftIO $ setObjectPropertyString obj "ch-off" val constructDOMHTMLTableCellElementChOff :: T.Text -> IO ([Char], GValue) constructDOMHTMLTableCellElementChOff val = constructObjectPropertyString "ch-off" val data DOMHTMLTableCellElementChOffPropertyInfo instance AttrInfo DOMHTMLTableCellElementChOffPropertyInfo where type AttrAllowedOps DOMHTMLTableCellElementChOffPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLTableCellElementChOffPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLTableCellElementChOffPropertyInfo = DOMHTMLTableCellElementK type AttrGetType DOMHTMLTableCellElementChOffPropertyInfo = T.Text type AttrLabel DOMHTMLTableCellElementChOffPropertyInfo = "DOMHTMLTableCellElement::ch-off" attrGet _ = getDOMHTMLTableCellElementChOff attrSet _ = setDOMHTMLTableCellElementChOff attrConstruct _ = constructDOMHTMLTableCellElementChOff -- VVV Prop "col-span" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLTableCellElementColSpan :: (MonadIO m, DOMHTMLTableCellElementK o) => o -> m Int64 getDOMHTMLTableCellElementColSpan obj = liftIO $ getObjectPropertyInt64 obj "col-span" setDOMHTMLTableCellElementColSpan :: (MonadIO m, DOMHTMLTableCellElementK o) => o -> Int64 -> m () setDOMHTMLTableCellElementColSpan obj val = liftIO $ setObjectPropertyInt64 obj "col-span" val constructDOMHTMLTableCellElementColSpan :: Int64 -> IO ([Char], GValue) constructDOMHTMLTableCellElementColSpan val = constructObjectPropertyInt64 "col-span" val data DOMHTMLTableCellElementColSpanPropertyInfo instance AttrInfo DOMHTMLTableCellElementColSpanPropertyInfo where type AttrAllowedOps DOMHTMLTableCellElementColSpanPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLTableCellElementColSpanPropertyInfo = (~) Int64 type AttrBaseTypeConstraint DOMHTMLTableCellElementColSpanPropertyInfo = DOMHTMLTableCellElementK type AttrGetType DOMHTMLTableCellElementColSpanPropertyInfo = Int64 type AttrLabel DOMHTMLTableCellElementColSpanPropertyInfo = "DOMHTMLTableCellElement::col-span" attrGet _ = getDOMHTMLTableCellElementColSpan attrSet _ = setDOMHTMLTableCellElementColSpan attrConstruct _ = constructDOMHTMLTableCellElementColSpan -- VVV Prop "headers" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLTableCellElementHeaders :: (MonadIO m, DOMHTMLTableCellElementK o) => o -> m T.Text getDOMHTMLTableCellElementHeaders obj = liftIO $ getObjectPropertyString obj "headers" setDOMHTMLTableCellElementHeaders :: (MonadIO m, DOMHTMLTableCellElementK o) => o -> T.Text -> m () setDOMHTMLTableCellElementHeaders obj val = liftIO $ setObjectPropertyString obj "headers" val constructDOMHTMLTableCellElementHeaders :: T.Text -> IO ([Char], GValue) constructDOMHTMLTableCellElementHeaders val = constructObjectPropertyString "headers" val data DOMHTMLTableCellElementHeadersPropertyInfo instance AttrInfo DOMHTMLTableCellElementHeadersPropertyInfo where type AttrAllowedOps DOMHTMLTableCellElementHeadersPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLTableCellElementHeadersPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLTableCellElementHeadersPropertyInfo = DOMHTMLTableCellElementK type AttrGetType DOMHTMLTableCellElementHeadersPropertyInfo = T.Text type AttrLabel DOMHTMLTableCellElementHeadersPropertyInfo = "DOMHTMLTableCellElement::headers" attrGet _ = getDOMHTMLTableCellElementHeaders attrSet _ = setDOMHTMLTableCellElementHeaders attrConstruct _ = constructDOMHTMLTableCellElementHeaders -- VVV Prop "height" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLTableCellElementHeight :: (MonadIO m, DOMHTMLTableCellElementK o) => o -> m T.Text getDOMHTMLTableCellElementHeight obj = liftIO $ getObjectPropertyString obj "height" setDOMHTMLTableCellElementHeight :: (MonadIO m, DOMHTMLTableCellElementK o) => o -> T.Text -> m () setDOMHTMLTableCellElementHeight obj val = liftIO $ setObjectPropertyString obj "height" val constructDOMHTMLTableCellElementHeight :: T.Text -> IO ([Char], GValue) constructDOMHTMLTableCellElementHeight val = constructObjectPropertyString "height" val data DOMHTMLTableCellElementHeightPropertyInfo instance AttrInfo DOMHTMLTableCellElementHeightPropertyInfo where type AttrAllowedOps DOMHTMLTableCellElementHeightPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLTableCellElementHeightPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLTableCellElementHeightPropertyInfo = DOMHTMLTableCellElementK type AttrGetType DOMHTMLTableCellElementHeightPropertyInfo = T.Text type AttrLabel DOMHTMLTableCellElementHeightPropertyInfo = "DOMHTMLTableCellElement::height" attrGet _ = getDOMHTMLTableCellElementHeight attrSet _ = setDOMHTMLTableCellElementHeight attrConstruct _ = constructDOMHTMLTableCellElementHeight -- VVV Prop "no-wrap" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLTableCellElementNoWrap :: (MonadIO m, DOMHTMLTableCellElementK o) => o -> m Bool getDOMHTMLTableCellElementNoWrap obj = liftIO $ getObjectPropertyBool obj "no-wrap" setDOMHTMLTableCellElementNoWrap :: (MonadIO m, DOMHTMLTableCellElementK o) => o -> Bool -> m () setDOMHTMLTableCellElementNoWrap obj val = liftIO $ setObjectPropertyBool obj "no-wrap" val constructDOMHTMLTableCellElementNoWrap :: Bool -> IO ([Char], GValue) constructDOMHTMLTableCellElementNoWrap val = constructObjectPropertyBool "no-wrap" val data DOMHTMLTableCellElementNoWrapPropertyInfo instance AttrInfo DOMHTMLTableCellElementNoWrapPropertyInfo where type AttrAllowedOps DOMHTMLTableCellElementNoWrapPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLTableCellElementNoWrapPropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLTableCellElementNoWrapPropertyInfo = DOMHTMLTableCellElementK type AttrGetType DOMHTMLTableCellElementNoWrapPropertyInfo = Bool type AttrLabel DOMHTMLTableCellElementNoWrapPropertyInfo = "DOMHTMLTableCellElement::no-wrap" attrGet _ = getDOMHTMLTableCellElementNoWrap attrSet _ = setDOMHTMLTableCellElementNoWrap attrConstruct _ = constructDOMHTMLTableCellElementNoWrap -- VVV Prop "row-span" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLTableCellElementRowSpan :: (MonadIO m, DOMHTMLTableCellElementK o) => o -> m Int64 getDOMHTMLTableCellElementRowSpan obj = liftIO $ getObjectPropertyInt64 obj "row-span" setDOMHTMLTableCellElementRowSpan :: (MonadIO m, DOMHTMLTableCellElementK o) => o -> Int64 -> m () setDOMHTMLTableCellElementRowSpan obj val = liftIO $ setObjectPropertyInt64 obj "row-span" val constructDOMHTMLTableCellElementRowSpan :: Int64 -> IO ([Char], GValue) constructDOMHTMLTableCellElementRowSpan val = constructObjectPropertyInt64 "row-span" val data DOMHTMLTableCellElementRowSpanPropertyInfo instance AttrInfo DOMHTMLTableCellElementRowSpanPropertyInfo where type AttrAllowedOps DOMHTMLTableCellElementRowSpanPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLTableCellElementRowSpanPropertyInfo = (~) Int64 type AttrBaseTypeConstraint DOMHTMLTableCellElementRowSpanPropertyInfo = DOMHTMLTableCellElementK type AttrGetType DOMHTMLTableCellElementRowSpanPropertyInfo = Int64 type AttrLabel DOMHTMLTableCellElementRowSpanPropertyInfo = "DOMHTMLTableCellElement::row-span" attrGet _ = getDOMHTMLTableCellElementRowSpan attrSet _ = setDOMHTMLTableCellElementRowSpan attrConstruct _ = constructDOMHTMLTableCellElementRowSpan -- VVV Prop "scope" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLTableCellElementScope :: (MonadIO m, DOMHTMLTableCellElementK o) => o -> m T.Text getDOMHTMLTableCellElementScope obj = liftIO $ getObjectPropertyString obj "scope" setDOMHTMLTableCellElementScope :: (MonadIO m, DOMHTMLTableCellElementK o) => o -> T.Text -> m () setDOMHTMLTableCellElementScope obj val = liftIO $ setObjectPropertyString obj "scope" val constructDOMHTMLTableCellElementScope :: T.Text -> IO ([Char], GValue) constructDOMHTMLTableCellElementScope val = constructObjectPropertyString "scope" val data DOMHTMLTableCellElementScopePropertyInfo instance AttrInfo DOMHTMLTableCellElementScopePropertyInfo where type AttrAllowedOps DOMHTMLTableCellElementScopePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLTableCellElementScopePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLTableCellElementScopePropertyInfo = DOMHTMLTableCellElementK type AttrGetType DOMHTMLTableCellElementScopePropertyInfo = T.Text type AttrLabel DOMHTMLTableCellElementScopePropertyInfo = "DOMHTMLTableCellElement::scope" attrGet _ = getDOMHTMLTableCellElementScope attrSet _ = setDOMHTMLTableCellElementScope attrConstruct _ = constructDOMHTMLTableCellElementScope -- VVV Prop "v-align" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLTableCellElementVAlign :: (MonadIO m, DOMHTMLTableCellElementK o) => o -> m T.Text getDOMHTMLTableCellElementVAlign obj = liftIO $ getObjectPropertyString obj "v-align" setDOMHTMLTableCellElementVAlign :: (MonadIO m, DOMHTMLTableCellElementK o) => o -> T.Text -> m () setDOMHTMLTableCellElementVAlign obj val = liftIO $ setObjectPropertyString obj "v-align" val constructDOMHTMLTableCellElementVAlign :: T.Text -> IO ([Char], GValue) constructDOMHTMLTableCellElementVAlign val = constructObjectPropertyString "v-align" val data DOMHTMLTableCellElementVAlignPropertyInfo instance AttrInfo DOMHTMLTableCellElementVAlignPropertyInfo where type AttrAllowedOps DOMHTMLTableCellElementVAlignPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLTableCellElementVAlignPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLTableCellElementVAlignPropertyInfo = DOMHTMLTableCellElementK type AttrGetType DOMHTMLTableCellElementVAlignPropertyInfo = T.Text type AttrLabel DOMHTMLTableCellElementVAlignPropertyInfo = "DOMHTMLTableCellElement::v-align" attrGet _ = getDOMHTMLTableCellElementVAlign attrSet _ = setDOMHTMLTableCellElementVAlign attrConstruct _ = constructDOMHTMLTableCellElementVAlign -- VVV Prop "width" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLTableCellElementWidth :: (MonadIO m, DOMHTMLTableCellElementK o) => o -> m T.Text getDOMHTMLTableCellElementWidth obj = liftIO $ getObjectPropertyString obj "width" setDOMHTMLTableCellElementWidth :: (MonadIO m, DOMHTMLTableCellElementK o) => o -> T.Text -> m () setDOMHTMLTableCellElementWidth obj val = liftIO $ setObjectPropertyString obj "width" val constructDOMHTMLTableCellElementWidth :: T.Text -> IO ([Char], GValue) constructDOMHTMLTableCellElementWidth val = constructObjectPropertyString "width" val data DOMHTMLTableCellElementWidthPropertyInfo instance AttrInfo DOMHTMLTableCellElementWidthPropertyInfo where type AttrAllowedOps DOMHTMLTableCellElementWidthPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLTableCellElementWidthPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLTableCellElementWidthPropertyInfo = DOMHTMLTableCellElementK type AttrGetType DOMHTMLTableCellElementWidthPropertyInfo = T.Text type AttrLabel DOMHTMLTableCellElementWidthPropertyInfo = "DOMHTMLTableCellElement::width" attrGet _ = getDOMHTMLTableCellElementWidth attrSet _ = setDOMHTMLTableCellElementWidth attrConstruct _ = constructDOMHTMLTableCellElementWidth type instance AttributeList DOMHTMLTableCellElement = '[ '("abbr", DOMHTMLTableCellElementAbbrPropertyInfo), '("access-key", DOMHTMLElementAccessKeyPropertyInfo), '("align", DOMHTMLTableCellElementAlignPropertyInfo), '("attributes", DOMElementAttributesPropertyInfo), '("axis", DOMHTMLTableCellElementAxisPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("bg-color", DOMHTMLTableCellElementBgColorPropertyInfo), '("cell-index", DOMHTMLTableCellElementCellIndexPropertyInfo), '("ch", DOMHTMLTableCellElementChPropertyInfo), '("ch-off", DOMHTMLTableCellElementChOffPropertyInfo), '("child-element-count", DOMElementChildElementCountPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("children", DOMHTMLElementChildrenPropertyInfo), '("class-list", DOMElementClassListPropertyInfo), '("class-name", DOMElementClassNamePropertyInfo), '("client-height", DOMElementClientHeightPropertyInfo), '("client-left", DOMElementClientLeftPropertyInfo), '("client-top", DOMElementClientTopPropertyInfo), '("client-width", DOMElementClientWidthPropertyInfo), '("col-span", DOMHTMLTableCellElementColSpanPropertyInfo), '("content-editable", DOMHTMLElementContentEditablePropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("dir", DOMHTMLElementDirPropertyInfo), '("draggable", DOMHTMLElementDraggablePropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("first-element-child", DOMElementFirstElementChildPropertyInfo), '("headers", DOMHTMLTableCellElementHeadersPropertyInfo), '("height", DOMHTMLTableCellElementHeightPropertyInfo), '("hidden", DOMHTMLElementHiddenPropertyInfo), '("id", DOMElementIdPropertyInfo), '("inner-html", DOMHTMLElementInnerHtmlPropertyInfo), '("inner-text", DOMHTMLElementInnerTextPropertyInfo), '("is-content-editable", DOMHTMLElementIsContentEditablePropertyInfo), '("lang", DOMHTMLElementLangPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-element-child", DOMElementLastElementChildPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-element-sibling", DOMElementNextElementSiblingPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("no-wrap", DOMHTMLTableCellElementNoWrapPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("offset-height", DOMElementOffsetHeightPropertyInfo), '("offset-left", DOMElementOffsetLeftPropertyInfo), '("offset-parent", DOMElementOffsetParentPropertyInfo), '("offset-top", DOMElementOffsetTopPropertyInfo), '("offset-width", DOMElementOffsetWidthPropertyInfo), '("outer-html", DOMHTMLElementOuterHtmlPropertyInfo), '("outer-text", DOMHTMLElementOuterTextPropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-element-sibling", DOMElementPreviousElementSiblingPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("row-span", DOMHTMLTableCellElementRowSpanPropertyInfo), '("scope", DOMHTMLTableCellElementScopePropertyInfo), '("scroll-height", DOMElementScrollHeightPropertyInfo), '("scroll-left", DOMElementScrollLeftPropertyInfo), '("scroll-top", DOMElementScrollTopPropertyInfo), '("scroll-width", DOMElementScrollWidthPropertyInfo), '("spellcheck", DOMHTMLElementSpellcheckPropertyInfo), '("style", DOMElementStylePropertyInfo), '("tab-index", DOMHTMLElementTabIndexPropertyInfo), '("tag-name", DOMElementTagNamePropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("title", DOMHTMLElementTitlePropertyInfo), '("translate", DOMHTMLElementTranslatePropertyInfo), '("v-align", DOMHTMLTableCellElementVAlignPropertyInfo), '("webkit-region-overset", DOMElementWebkitRegionOversetPropertyInfo), '("webkitdropzone", DOMHTMLElementWebkitdropzonePropertyInfo), '("width", DOMHTMLTableCellElementWidthPropertyInfo)] -- VVV Prop "align" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLTableColElementAlign :: (MonadIO m, DOMHTMLTableColElementK o) => o -> m T.Text getDOMHTMLTableColElementAlign obj = liftIO $ getObjectPropertyString obj "align" setDOMHTMLTableColElementAlign :: (MonadIO m, DOMHTMLTableColElementK o) => o -> T.Text -> m () setDOMHTMLTableColElementAlign obj val = liftIO $ setObjectPropertyString obj "align" val constructDOMHTMLTableColElementAlign :: T.Text -> IO ([Char], GValue) constructDOMHTMLTableColElementAlign val = constructObjectPropertyString "align" val data DOMHTMLTableColElementAlignPropertyInfo instance AttrInfo DOMHTMLTableColElementAlignPropertyInfo where type AttrAllowedOps DOMHTMLTableColElementAlignPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLTableColElementAlignPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLTableColElementAlignPropertyInfo = DOMHTMLTableColElementK type AttrGetType DOMHTMLTableColElementAlignPropertyInfo = T.Text type AttrLabel DOMHTMLTableColElementAlignPropertyInfo = "DOMHTMLTableColElement::align" attrGet _ = getDOMHTMLTableColElementAlign attrSet _ = setDOMHTMLTableColElementAlign attrConstruct _ = constructDOMHTMLTableColElementAlign -- VVV Prop "ch" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLTableColElementCh :: (MonadIO m, DOMHTMLTableColElementK o) => o -> m T.Text getDOMHTMLTableColElementCh obj = liftIO $ getObjectPropertyString obj "ch" setDOMHTMLTableColElementCh :: (MonadIO m, DOMHTMLTableColElementK o) => o -> T.Text -> m () setDOMHTMLTableColElementCh obj val = liftIO $ setObjectPropertyString obj "ch" val constructDOMHTMLTableColElementCh :: T.Text -> IO ([Char], GValue) constructDOMHTMLTableColElementCh val = constructObjectPropertyString "ch" val data DOMHTMLTableColElementChPropertyInfo instance AttrInfo DOMHTMLTableColElementChPropertyInfo where type AttrAllowedOps DOMHTMLTableColElementChPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLTableColElementChPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLTableColElementChPropertyInfo = DOMHTMLTableColElementK type AttrGetType DOMHTMLTableColElementChPropertyInfo = T.Text type AttrLabel DOMHTMLTableColElementChPropertyInfo = "DOMHTMLTableColElement::ch" attrGet _ = getDOMHTMLTableColElementCh attrSet _ = setDOMHTMLTableColElementCh attrConstruct _ = constructDOMHTMLTableColElementCh -- VVV Prop "ch-off" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLTableColElementChOff :: (MonadIO m, DOMHTMLTableColElementK o) => o -> m T.Text getDOMHTMLTableColElementChOff obj = liftIO $ getObjectPropertyString obj "ch-off" setDOMHTMLTableColElementChOff :: (MonadIO m, DOMHTMLTableColElementK o) => o -> T.Text -> m () setDOMHTMLTableColElementChOff obj val = liftIO $ setObjectPropertyString obj "ch-off" val constructDOMHTMLTableColElementChOff :: T.Text -> IO ([Char], GValue) constructDOMHTMLTableColElementChOff val = constructObjectPropertyString "ch-off" val data DOMHTMLTableColElementChOffPropertyInfo instance AttrInfo DOMHTMLTableColElementChOffPropertyInfo where type AttrAllowedOps DOMHTMLTableColElementChOffPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLTableColElementChOffPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLTableColElementChOffPropertyInfo = DOMHTMLTableColElementK type AttrGetType DOMHTMLTableColElementChOffPropertyInfo = T.Text type AttrLabel DOMHTMLTableColElementChOffPropertyInfo = "DOMHTMLTableColElement::ch-off" attrGet _ = getDOMHTMLTableColElementChOff attrSet _ = setDOMHTMLTableColElementChOff attrConstruct _ = constructDOMHTMLTableColElementChOff -- VVV Prop "span" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLTableColElementSpan :: (MonadIO m, DOMHTMLTableColElementK o) => o -> m Int64 getDOMHTMLTableColElementSpan obj = liftIO $ getObjectPropertyInt64 obj "span" setDOMHTMLTableColElementSpan :: (MonadIO m, DOMHTMLTableColElementK o) => o -> Int64 -> m () setDOMHTMLTableColElementSpan obj val = liftIO $ setObjectPropertyInt64 obj "span" val constructDOMHTMLTableColElementSpan :: Int64 -> IO ([Char], GValue) constructDOMHTMLTableColElementSpan val = constructObjectPropertyInt64 "span" val data DOMHTMLTableColElementSpanPropertyInfo instance AttrInfo DOMHTMLTableColElementSpanPropertyInfo where type AttrAllowedOps DOMHTMLTableColElementSpanPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLTableColElementSpanPropertyInfo = (~) Int64 type AttrBaseTypeConstraint DOMHTMLTableColElementSpanPropertyInfo = DOMHTMLTableColElementK type AttrGetType DOMHTMLTableColElementSpanPropertyInfo = Int64 type AttrLabel DOMHTMLTableColElementSpanPropertyInfo = "DOMHTMLTableColElement::span" attrGet _ = getDOMHTMLTableColElementSpan attrSet _ = setDOMHTMLTableColElementSpan attrConstruct _ = constructDOMHTMLTableColElementSpan -- VVV Prop "v-align" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLTableColElementVAlign :: (MonadIO m, DOMHTMLTableColElementK o) => o -> m T.Text getDOMHTMLTableColElementVAlign obj = liftIO $ getObjectPropertyString obj "v-align" setDOMHTMLTableColElementVAlign :: (MonadIO m, DOMHTMLTableColElementK o) => o -> T.Text -> m () setDOMHTMLTableColElementVAlign obj val = liftIO $ setObjectPropertyString obj "v-align" val constructDOMHTMLTableColElementVAlign :: T.Text -> IO ([Char], GValue) constructDOMHTMLTableColElementVAlign val = constructObjectPropertyString "v-align" val data DOMHTMLTableColElementVAlignPropertyInfo instance AttrInfo DOMHTMLTableColElementVAlignPropertyInfo where type AttrAllowedOps DOMHTMLTableColElementVAlignPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLTableColElementVAlignPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLTableColElementVAlignPropertyInfo = DOMHTMLTableColElementK type AttrGetType DOMHTMLTableColElementVAlignPropertyInfo = T.Text type AttrLabel DOMHTMLTableColElementVAlignPropertyInfo = "DOMHTMLTableColElement::v-align" attrGet _ = getDOMHTMLTableColElementVAlign attrSet _ = setDOMHTMLTableColElementVAlign attrConstruct _ = constructDOMHTMLTableColElementVAlign -- VVV Prop "width" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLTableColElementWidth :: (MonadIO m, DOMHTMLTableColElementK o) => o -> m T.Text getDOMHTMLTableColElementWidth obj = liftIO $ getObjectPropertyString obj "width" setDOMHTMLTableColElementWidth :: (MonadIO m, DOMHTMLTableColElementK o) => o -> T.Text -> m () setDOMHTMLTableColElementWidth obj val = liftIO $ setObjectPropertyString obj "width" val constructDOMHTMLTableColElementWidth :: T.Text -> IO ([Char], GValue) constructDOMHTMLTableColElementWidth val = constructObjectPropertyString "width" val data DOMHTMLTableColElementWidthPropertyInfo instance AttrInfo DOMHTMLTableColElementWidthPropertyInfo where type AttrAllowedOps DOMHTMLTableColElementWidthPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLTableColElementWidthPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLTableColElementWidthPropertyInfo = DOMHTMLTableColElementK type AttrGetType DOMHTMLTableColElementWidthPropertyInfo = T.Text type AttrLabel DOMHTMLTableColElementWidthPropertyInfo = "DOMHTMLTableColElement::width" attrGet _ = getDOMHTMLTableColElementWidth attrSet _ = setDOMHTMLTableColElementWidth attrConstruct _ = constructDOMHTMLTableColElementWidth type instance AttributeList DOMHTMLTableColElement = '[ '("access-key", DOMHTMLElementAccessKeyPropertyInfo), '("align", DOMHTMLTableColElementAlignPropertyInfo), '("attributes", DOMElementAttributesPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("ch", DOMHTMLTableColElementChPropertyInfo), '("ch-off", DOMHTMLTableColElementChOffPropertyInfo), '("child-element-count", DOMElementChildElementCountPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("children", DOMHTMLElementChildrenPropertyInfo), '("class-list", DOMElementClassListPropertyInfo), '("class-name", DOMElementClassNamePropertyInfo), '("client-height", DOMElementClientHeightPropertyInfo), '("client-left", DOMElementClientLeftPropertyInfo), '("client-top", DOMElementClientTopPropertyInfo), '("client-width", DOMElementClientWidthPropertyInfo), '("content-editable", DOMHTMLElementContentEditablePropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("dir", DOMHTMLElementDirPropertyInfo), '("draggable", DOMHTMLElementDraggablePropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("first-element-child", DOMElementFirstElementChildPropertyInfo), '("hidden", DOMHTMLElementHiddenPropertyInfo), '("id", DOMElementIdPropertyInfo), '("inner-html", DOMHTMLElementInnerHtmlPropertyInfo), '("inner-text", DOMHTMLElementInnerTextPropertyInfo), '("is-content-editable", DOMHTMLElementIsContentEditablePropertyInfo), '("lang", DOMHTMLElementLangPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-element-child", DOMElementLastElementChildPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-element-sibling", DOMElementNextElementSiblingPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("offset-height", DOMElementOffsetHeightPropertyInfo), '("offset-left", DOMElementOffsetLeftPropertyInfo), '("offset-parent", DOMElementOffsetParentPropertyInfo), '("offset-top", DOMElementOffsetTopPropertyInfo), '("offset-width", DOMElementOffsetWidthPropertyInfo), '("outer-html", DOMHTMLElementOuterHtmlPropertyInfo), '("outer-text", DOMHTMLElementOuterTextPropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-element-sibling", DOMElementPreviousElementSiblingPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("scroll-height", DOMElementScrollHeightPropertyInfo), '("scroll-left", DOMElementScrollLeftPropertyInfo), '("scroll-top", DOMElementScrollTopPropertyInfo), '("scroll-width", DOMElementScrollWidthPropertyInfo), '("span", DOMHTMLTableColElementSpanPropertyInfo), '("spellcheck", DOMHTMLElementSpellcheckPropertyInfo), '("style", DOMElementStylePropertyInfo), '("tab-index", DOMHTMLElementTabIndexPropertyInfo), '("tag-name", DOMElementTagNamePropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("title", DOMHTMLElementTitlePropertyInfo), '("translate", DOMHTMLElementTranslatePropertyInfo), '("v-align", DOMHTMLTableColElementVAlignPropertyInfo), '("webkit-region-overset", DOMElementWebkitRegionOversetPropertyInfo), '("webkitdropzone", DOMHTMLElementWebkitdropzonePropertyInfo), '("width", DOMHTMLTableColElementWidthPropertyInfo)] -- VVV Prop "align" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLTableElementAlign :: (MonadIO m, DOMHTMLTableElementK o) => o -> m T.Text getDOMHTMLTableElementAlign obj = liftIO $ getObjectPropertyString obj "align" setDOMHTMLTableElementAlign :: (MonadIO m, DOMHTMLTableElementK o) => o -> T.Text -> m () setDOMHTMLTableElementAlign obj val = liftIO $ setObjectPropertyString obj "align" val constructDOMHTMLTableElementAlign :: T.Text -> IO ([Char], GValue) constructDOMHTMLTableElementAlign val = constructObjectPropertyString "align" val data DOMHTMLTableElementAlignPropertyInfo instance AttrInfo DOMHTMLTableElementAlignPropertyInfo where type AttrAllowedOps DOMHTMLTableElementAlignPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLTableElementAlignPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLTableElementAlignPropertyInfo = DOMHTMLTableElementK type AttrGetType DOMHTMLTableElementAlignPropertyInfo = T.Text type AttrLabel DOMHTMLTableElementAlignPropertyInfo = "DOMHTMLTableElement::align" attrGet _ = getDOMHTMLTableElementAlign attrSet _ = setDOMHTMLTableElementAlign attrConstruct _ = constructDOMHTMLTableElementAlign -- VVV Prop "bg-color" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLTableElementBgColor :: (MonadIO m, DOMHTMLTableElementK o) => o -> m T.Text getDOMHTMLTableElementBgColor obj = liftIO $ getObjectPropertyString obj "bg-color" setDOMHTMLTableElementBgColor :: (MonadIO m, DOMHTMLTableElementK o) => o -> T.Text -> m () setDOMHTMLTableElementBgColor obj val = liftIO $ setObjectPropertyString obj "bg-color" val constructDOMHTMLTableElementBgColor :: T.Text -> IO ([Char], GValue) constructDOMHTMLTableElementBgColor val = constructObjectPropertyString "bg-color" val data DOMHTMLTableElementBgColorPropertyInfo instance AttrInfo DOMHTMLTableElementBgColorPropertyInfo where type AttrAllowedOps DOMHTMLTableElementBgColorPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLTableElementBgColorPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLTableElementBgColorPropertyInfo = DOMHTMLTableElementK type AttrGetType DOMHTMLTableElementBgColorPropertyInfo = T.Text type AttrLabel DOMHTMLTableElementBgColorPropertyInfo = "DOMHTMLTableElement::bg-color" attrGet _ = getDOMHTMLTableElementBgColor attrSet _ = setDOMHTMLTableElementBgColor attrConstruct _ = constructDOMHTMLTableElementBgColor -- VVV Prop "border" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLTableElementBorder :: (MonadIO m, DOMHTMLTableElementK o) => o -> m T.Text getDOMHTMLTableElementBorder obj = liftIO $ getObjectPropertyString obj "border" setDOMHTMLTableElementBorder :: (MonadIO m, DOMHTMLTableElementK o) => o -> T.Text -> m () setDOMHTMLTableElementBorder obj val = liftIO $ setObjectPropertyString obj "border" val constructDOMHTMLTableElementBorder :: T.Text -> IO ([Char], GValue) constructDOMHTMLTableElementBorder val = constructObjectPropertyString "border" val data DOMHTMLTableElementBorderPropertyInfo instance AttrInfo DOMHTMLTableElementBorderPropertyInfo where type AttrAllowedOps DOMHTMLTableElementBorderPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLTableElementBorderPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLTableElementBorderPropertyInfo = DOMHTMLTableElementK type AttrGetType DOMHTMLTableElementBorderPropertyInfo = T.Text type AttrLabel DOMHTMLTableElementBorderPropertyInfo = "DOMHTMLTableElement::border" attrGet _ = getDOMHTMLTableElementBorder attrSet _ = setDOMHTMLTableElementBorder attrConstruct _ = constructDOMHTMLTableElementBorder -- VVV Prop "caption" -- Type: TInterface "WebKit" "DOMHTMLTableCaptionElement" -- Flags: [PropertyReadable] getDOMHTMLTableElementCaption :: (MonadIO m, DOMHTMLTableElementK o) => o -> m DOMHTMLTableCaptionElement getDOMHTMLTableElementCaption obj = liftIO $ getObjectPropertyObject obj "caption" DOMHTMLTableCaptionElement data DOMHTMLTableElementCaptionPropertyInfo instance AttrInfo DOMHTMLTableElementCaptionPropertyInfo where type AttrAllowedOps DOMHTMLTableElementCaptionPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLTableElementCaptionPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLTableElementCaptionPropertyInfo = DOMHTMLTableElementK type AttrGetType DOMHTMLTableElementCaptionPropertyInfo = DOMHTMLTableCaptionElement type AttrLabel DOMHTMLTableElementCaptionPropertyInfo = "DOMHTMLTableElement::caption" attrGet _ = getDOMHTMLTableElementCaption attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "cell-padding" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLTableElementCellPadding :: (MonadIO m, DOMHTMLTableElementK o) => o -> m T.Text getDOMHTMLTableElementCellPadding obj = liftIO $ getObjectPropertyString obj "cell-padding" setDOMHTMLTableElementCellPadding :: (MonadIO m, DOMHTMLTableElementK o) => o -> T.Text -> m () setDOMHTMLTableElementCellPadding obj val = liftIO $ setObjectPropertyString obj "cell-padding" val constructDOMHTMLTableElementCellPadding :: T.Text -> IO ([Char], GValue) constructDOMHTMLTableElementCellPadding val = constructObjectPropertyString "cell-padding" val data DOMHTMLTableElementCellPaddingPropertyInfo instance AttrInfo DOMHTMLTableElementCellPaddingPropertyInfo where type AttrAllowedOps DOMHTMLTableElementCellPaddingPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLTableElementCellPaddingPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLTableElementCellPaddingPropertyInfo = DOMHTMLTableElementK type AttrGetType DOMHTMLTableElementCellPaddingPropertyInfo = T.Text type AttrLabel DOMHTMLTableElementCellPaddingPropertyInfo = "DOMHTMLTableElement::cell-padding" attrGet _ = getDOMHTMLTableElementCellPadding attrSet _ = setDOMHTMLTableElementCellPadding attrConstruct _ = constructDOMHTMLTableElementCellPadding -- VVV Prop "cell-spacing" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLTableElementCellSpacing :: (MonadIO m, DOMHTMLTableElementK o) => o -> m T.Text getDOMHTMLTableElementCellSpacing obj = liftIO $ getObjectPropertyString obj "cell-spacing" setDOMHTMLTableElementCellSpacing :: (MonadIO m, DOMHTMLTableElementK o) => o -> T.Text -> m () setDOMHTMLTableElementCellSpacing obj val = liftIO $ setObjectPropertyString obj "cell-spacing" val constructDOMHTMLTableElementCellSpacing :: T.Text -> IO ([Char], GValue) constructDOMHTMLTableElementCellSpacing val = constructObjectPropertyString "cell-spacing" val data DOMHTMLTableElementCellSpacingPropertyInfo instance AttrInfo DOMHTMLTableElementCellSpacingPropertyInfo where type AttrAllowedOps DOMHTMLTableElementCellSpacingPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLTableElementCellSpacingPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLTableElementCellSpacingPropertyInfo = DOMHTMLTableElementK type AttrGetType DOMHTMLTableElementCellSpacingPropertyInfo = T.Text type AttrLabel DOMHTMLTableElementCellSpacingPropertyInfo = "DOMHTMLTableElement::cell-spacing" attrGet _ = getDOMHTMLTableElementCellSpacing attrSet _ = setDOMHTMLTableElementCellSpacing attrConstruct _ = constructDOMHTMLTableElementCellSpacing -- VVV Prop "frame" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLTableElementFrame :: (MonadIO m, DOMHTMLTableElementK o) => o -> m T.Text getDOMHTMLTableElementFrame obj = liftIO $ getObjectPropertyString obj "frame" setDOMHTMLTableElementFrame :: (MonadIO m, DOMHTMLTableElementK o) => o -> T.Text -> m () setDOMHTMLTableElementFrame obj val = liftIO $ setObjectPropertyString obj "frame" val constructDOMHTMLTableElementFrame :: T.Text -> IO ([Char], GValue) constructDOMHTMLTableElementFrame val = constructObjectPropertyString "frame" val data DOMHTMLTableElementFramePropertyInfo instance AttrInfo DOMHTMLTableElementFramePropertyInfo where type AttrAllowedOps DOMHTMLTableElementFramePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLTableElementFramePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLTableElementFramePropertyInfo = DOMHTMLTableElementK type AttrGetType DOMHTMLTableElementFramePropertyInfo = T.Text type AttrLabel DOMHTMLTableElementFramePropertyInfo = "DOMHTMLTableElement::frame" attrGet _ = getDOMHTMLTableElementFrame attrSet _ = setDOMHTMLTableElementFrame attrConstruct _ = constructDOMHTMLTableElementFrame -- VVV Prop "rows" -- Type: TInterface "WebKit" "DOMHTMLCollection" -- Flags: [PropertyReadable] getDOMHTMLTableElementRows :: (MonadIO m, DOMHTMLTableElementK o) => o -> m DOMHTMLCollection getDOMHTMLTableElementRows obj = liftIO $ getObjectPropertyObject obj "rows" DOMHTMLCollection data DOMHTMLTableElementRowsPropertyInfo instance AttrInfo DOMHTMLTableElementRowsPropertyInfo where type AttrAllowedOps DOMHTMLTableElementRowsPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLTableElementRowsPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLTableElementRowsPropertyInfo = DOMHTMLTableElementK type AttrGetType DOMHTMLTableElementRowsPropertyInfo = DOMHTMLCollection type AttrLabel DOMHTMLTableElementRowsPropertyInfo = "DOMHTMLTableElement::rows" attrGet _ = getDOMHTMLTableElementRows attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "rules" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLTableElementRules :: (MonadIO m, DOMHTMLTableElementK o) => o -> m T.Text getDOMHTMLTableElementRules obj = liftIO $ getObjectPropertyString obj "rules" setDOMHTMLTableElementRules :: (MonadIO m, DOMHTMLTableElementK o) => o -> T.Text -> m () setDOMHTMLTableElementRules obj val = liftIO $ setObjectPropertyString obj "rules" val constructDOMHTMLTableElementRules :: T.Text -> IO ([Char], GValue) constructDOMHTMLTableElementRules val = constructObjectPropertyString "rules" val data DOMHTMLTableElementRulesPropertyInfo instance AttrInfo DOMHTMLTableElementRulesPropertyInfo where type AttrAllowedOps DOMHTMLTableElementRulesPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLTableElementRulesPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLTableElementRulesPropertyInfo = DOMHTMLTableElementK type AttrGetType DOMHTMLTableElementRulesPropertyInfo = T.Text type AttrLabel DOMHTMLTableElementRulesPropertyInfo = "DOMHTMLTableElement::rules" attrGet _ = getDOMHTMLTableElementRules attrSet _ = setDOMHTMLTableElementRules attrConstruct _ = constructDOMHTMLTableElementRules -- VVV Prop "summary" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLTableElementSummary :: (MonadIO m, DOMHTMLTableElementK o) => o -> m T.Text getDOMHTMLTableElementSummary obj = liftIO $ getObjectPropertyString obj "summary" setDOMHTMLTableElementSummary :: (MonadIO m, DOMHTMLTableElementK o) => o -> T.Text -> m () setDOMHTMLTableElementSummary obj val = liftIO $ setObjectPropertyString obj "summary" val constructDOMHTMLTableElementSummary :: T.Text -> IO ([Char], GValue) constructDOMHTMLTableElementSummary val = constructObjectPropertyString "summary" val data DOMHTMLTableElementSummaryPropertyInfo instance AttrInfo DOMHTMLTableElementSummaryPropertyInfo where type AttrAllowedOps DOMHTMLTableElementSummaryPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLTableElementSummaryPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLTableElementSummaryPropertyInfo = DOMHTMLTableElementK type AttrGetType DOMHTMLTableElementSummaryPropertyInfo = T.Text type AttrLabel DOMHTMLTableElementSummaryPropertyInfo = "DOMHTMLTableElement::summary" attrGet _ = getDOMHTMLTableElementSummary attrSet _ = setDOMHTMLTableElementSummary attrConstruct _ = constructDOMHTMLTableElementSummary -- VVV Prop "t-bodies" -- Type: TInterface "WebKit" "DOMHTMLCollection" -- Flags: [PropertyReadable] getDOMHTMLTableElementTBodies :: (MonadIO m, DOMHTMLTableElementK o) => o -> m DOMHTMLCollection getDOMHTMLTableElementTBodies obj = liftIO $ getObjectPropertyObject obj "t-bodies" DOMHTMLCollection data DOMHTMLTableElementTBodiesPropertyInfo instance AttrInfo DOMHTMLTableElementTBodiesPropertyInfo where type AttrAllowedOps DOMHTMLTableElementTBodiesPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLTableElementTBodiesPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLTableElementTBodiesPropertyInfo = DOMHTMLTableElementK type AttrGetType DOMHTMLTableElementTBodiesPropertyInfo = DOMHTMLCollection type AttrLabel DOMHTMLTableElementTBodiesPropertyInfo = "DOMHTMLTableElement::t-bodies" attrGet _ = getDOMHTMLTableElementTBodies attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "t-foot" -- Type: TInterface "WebKit" "DOMHTMLTableSectionElement" -- Flags: [PropertyReadable] getDOMHTMLTableElementTFoot :: (MonadIO m, DOMHTMLTableElementK o) => o -> m DOMHTMLTableSectionElement getDOMHTMLTableElementTFoot obj = liftIO $ getObjectPropertyObject obj "t-foot" DOMHTMLTableSectionElement data DOMHTMLTableElementTFootPropertyInfo instance AttrInfo DOMHTMLTableElementTFootPropertyInfo where type AttrAllowedOps DOMHTMLTableElementTFootPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLTableElementTFootPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLTableElementTFootPropertyInfo = DOMHTMLTableElementK type AttrGetType DOMHTMLTableElementTFootPropertyInfo = DOMHTMLTableSectionElement type AttrLabel DOMHTMLTableElementTFootPropertyInfo = "DOMHTMLTableElement::t-foot" attrGet _ = getDOMHTMLTableElementTFoot attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "t-head" -- Type: TInterface "WebKit" "DOMHTMLTableSectionElement" -- Flags: [PropertyReadable] getDOMHTMLTableElementTHead :: (MonadIO m, DOMHTMLTableElementK o) => o -> m DOMHTMLTableSectionElement getDOMHTMLTableElementTHead obj = liftIO $ getObjectPropertyObject obj "t-head" DOMHTMLTableSectionElement data DOMHTMLTableElementTHeadPropertyInfo instance AttrInfo DOMHTMLTableElementTHeadPropertyInfo where type AttrAllowedOps DOMHTMLTableElementTHeadPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLTableElementTHeadPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLTableElementTHeadPropertyInfo = DOMHTMLTableElementK type AttrGetType DOMHTMLTableElementTHeadPropertyInfo = DOMHTMLTableSectionElement type AttrLabel DOMHTMLTableElementTHeadPropertyInfo = "DOMHTMLTableElement::t-head" attrGet _ = getDOMHTMLTableElementTHead attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "width" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLTableElementWidth :: (MonadIO m, DOMHTMLTableElementK o) => o -> m T.Text getDOMHTMLTableElementWidth obj = liftIO $ getObjectPropertyString obj "width" setDOMHTMLTableElementWidth :: (MonadIO m, DOMHTMLTableElementK o) => o -> T.Text -> m () setDOMHTMLTableElementWidth obj val = liftIO $ setObjectPropertyString obj "width" val constructDOMHTMLTableElementWidth :: T.Text -> IO ([Char], GValue) constructDOMHTMLTableElementWidth val = constructObjectPropertyString "width" val data DOMHTMLTableElementWidthPropertyInfo instance AttrInfo DOMHTMLTableElementWidthPropertyInfo where type AttrAllowedOps DOMHTMLTableElementWidthPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLTableElementWidthPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLTableElementWidthPropertyInfo = DOMHTMLTableElementK type AttrGetType DOMHTMLTableElementWidthPropertyInfo = T.Text type AttrLabel DOMHTMLTableElementWidthPropertyInfo = "DOMHTMLTableElement::width" attrGet _ = getDOMHTMLTableElementWidth attrSet _ = setDOMHTMLTableElementWidth attrConstruct _ = constructDOMHTMLTableElementWidth type instance AttributeList DOMHTMLTableElement = '[ '("access-key", DOMHTMLElementAccessKeyPropertyInfo), '("align", DOMHTMLTableElementAlignPropertyInfo), '("attributes", DOMElementAttributesPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("bg-color", DOMHTMLTableElementBgColorPropertyInfo), '("border", DOMHTMLTableElementBorderPropertyInfo), '("caption", DOMHTMLTableElementCaptionPropertyInfo), '("cell-padding", DOMHTMLTableElementCellPaddingPropertyInfo), '("cell-spacing", DOMHTMLTableElementCellSpacingPropertyInfo), '("child-element-count", DOMElementChildElementCountPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("children", DOMHTMLElementChildrenPropertyInfo), '("class-list", DOMElementClassListPropertyInfo), '("class-name", DOMElementClassNamePropertyInfo), '("client-height", DOMElementClientHeightPropertyInfo), '("client-left", DOMElementClientLeftPropertyInfo), '("client-top", DOMElementClientTopPropertyInfo), '("client-width", DOMElementClientWidthPropertyInfo), '("content-editable", DOMHTMLElementContentEditablePropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("dir", DOMHTMLElementDirPropertyInfo), '("draggable", DOMHTMLElementDraggablePropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("first-element-child", DOMElementFirstElementChildPropertyInfo), '("frame", DOMHTMLTableElementFramePropertyInfo), '("hidden", DOMHTMLElementHiddenPropertyInfo), '("id", DOMElementIdPropertyInfo), '("inner-html", DOMHTMLElementInnerHtmlPropertyInfo), '("inner-text", DOMHTMLElementInnerTextPropertyInfo), '("is-content-editable", DOMHTMLElementIsContentEditablePropertyInfo), '("lang", DOMHTMLElementLangPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-element-child", DOMElementLastElementChildPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-element-sibling", DOMElementNextElementSiblingPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("offset-height", DOMElementOffsetHeightPropertyInfo), '("offset-left", DOMElementOffsetLeftPropertyInfo), '("offset-parent", DOMElementOffsetParentPropertyInfo), '("offset-top", DOMElementOffsetTopPropertyInfo), '("offset-width", DOMElementOffsetWidthPropertyInfo), '("outer-html", DOMHTMLElementOuterHtmlPropertyInfo), '("outer-text", DOMHTMLElementOuterTextPropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-element-sibling", DOMElementPreviousElementSiblingPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("rows", DOMHTMLTableElementRowsPropertyInfo), '("rules", DOMHTMLTableElementRulesPropertyInfo), '("scroll-height", DOMElementScrollHeightPropertyInfo), '("scroll-left", DOMElementScrollLeftPropertyInfo), '("scroll-top", DOMElementScrollTopPropertyInfo), '("scroll-width", DOMElementScrollWidthPropertyInfo), '("spellcheck", DOMHTMLElementSpellcheckPropertyInfo), '("style", DOMElementStylePropertyInfo), '("summary", DOMHTMLTableElementSummaryPropertyInfo), '("t-bodies", DOMHTMLTableElementTBodiesPropertyInfo), '("t-foot", DOMHTMLTableElementTFootPropertyInfo), '("t-head", DOMHTMLTableElementTHeadPropertyInfo), '("tab-index", DOMHTMLElementTabIndexPropertyInfo), '("tag-name", DOMElementTagNamePropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("title", DOMHTMLElementTitlePropertyInfo), '("translate", DOMHTMLElementTranslatePropertyInfo), '("webkit-region-overset", DOMElementWebkitRegionOversetPropertyInfo), '("webkitdropzone", DOMHTMLElementWebkitdropzonePropertyInfo), '("width", DOMHTMLTableElementWidthPropertyInfo)] -- VVV Prop "align" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLTableRowElementAlign :: (MonadIO m, DOMHTMLTableRowElementK o) => o -> m T.Text getDOMHTMLTableRowElementAlign obj = liftIO $ getObjectPropertyString obj "align" setDOMHTMLTableRowElementAlign :: (MonadIO m, DOMHTMLTableRowElementK o) => o -> T.Text -> m () setDOMHTMLTableRowElementAlign obj val = liftIO $ setObjectPropertyString obj "align" val constructDOMHTMLTableRowElementAlign :: T.Text -> IO ([Char], GValue) constructDOMHTMLTableRowElementAlign val = constructObjectPropertyString "align" val data DOMHTMLTableRowElementAlignPropertyInfo instance AttrInfo DOMHTMLTableRowElementAlignPropertyInfo where type AttrAllowedOps DOMHTMLTableRowElementAlignPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLTableRowElementAlignPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLTableRowElementAlignPropertyInfo = DOMHTMLTableRowElementK type AttrGetType DOMHTMLTableRowElementAlignPropertyInfo = T.Text type AttrLabel DOMHTMLTableRowElementAlignPropertyInfo = "DOMHTMLTableRowElement::align" attrGet _ = getDOMHTMLTableRowElementAlign attrSet _ = setDOMHTMLTableRowElementAlign attrConstruct _ = constructDOMHTMLTableRowElementAlign -- VVV Prop "bg-color" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLTableRowElementBgColor :: (MonadIO m, DOMHTMLTableRowElementK o) => o -> m T.Text getDOMHTMLTableRowElementBgColor obj = liftIO $ getObjectPropertyString obj "bg-color" setDOMHTMLTableRowElementBgColor :: (MonadIO m, DOMHTMLTableRowElementK o) => o -> T.Text -> m () setDOMHTMLTableRowElementBgColor obj val = liftIO $ setObjectPropertyString obj "bg-color" val constructDOMHTMLTableRowElementBgColor :: T.Text -> IO ([Char], GValue) constructDOMHTMLTableRowElementBgColor val = constructObjectPropertyString "bg-color" val data DOMHTMLTableRowElementBgColorPropertyInfo instance AttrInfo DOMHTMLTableRowElementBgColorPropertyInfo where type AttrAllowedOps DOMHTMLTableRowElementBgColorPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLTableRowElementBgColorPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLTableRowElementBgColorPropertyInfo = DOMHTMLTableRowElementK type AttrGetType DOMHTMLTableRowElementBgColorPropertyInfo = T.Text type AttrLabel DOMHTMLTableRowElementBgColorPropertyInfo = "DOMHTMLTableRowElement::bg-color" attrGet _ = getDOMHTMLTableRowElementBgColor attrSet _ = setDOMHTMLTableRowElementBgColor attrConstruct _ = constructDOMHTMLTableRowElementBgColor -- VVV Prop "cells" -- Type: TInterface "WebKit" "DOMHTMLCollection" -- Flags: [PropertyReadable] getDOMHTMLTableRowElementCells :: (MonadIO m, DOMHTMLTableRowElementK o) => o -> m DOMHTMLCollection getDOMHTMLTableRowElementCells obj = liftIO $ getObjectPropertyObject obj "cells" DOMHTMLCollection data DOMHTMLTableRowElementCellsPropertyInfo instance AttrInfo DOMHTMLTableRowElementCellsPropertyInfo where type AttrAllowedOps DOMHTMLTableRowElementCellsPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLTableRowElementCellsPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLTableRowElementCellsPropertyInfo = DOMHTMLTableRowElementK type AttrGetType DOMHTMLTableRowElementCellsPropertyInfo = DOMHTMLCollection type AttrLabel DOMHTMLTableRowElementCellsPropertyInfo = "DOMHTMLTableRowElement::cells" attrGet _ = getDOMHTMLTableRowElementCells attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "ch" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLTableRowElementCh :: (MonadIO m, DOMHTMLTableRowElementK o) => o -> m T.Text getDOMHTMLTableRowElementCh obj = liftIO $ getObjectPropertyString obj "ch" setDOMHTMLTableRowElementCh :: (MonadIO m, DOMHTMLTableRowElementK o) => o -> T.Text -> m () setDOMHTMLTableRowElementCh obj val = liftIO $ setObjectPropertyString obj "ch" val constructDOMHTMLTableRowElementCh :: T.Text -> IO ([Char], GValue) constructDOMHTMLTableRowElementCh val = constructObjectPropertyString "ch" val data DOMHTMLTableRowElementChPropertyInfo instance AttrInfo DOMHTMLTableRowElementChPropertyInfo where type AttrAllowedOps DOMHTMLTableRowElementChPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLTableRowElementChPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLTableRowElementChPropertyInfo = DOMHTMLTableRowElementK type AttrGetType DOMHTMLTableRowElementChPropertyInfo = T.Text type AttrLabel DOMHTMLTableRowElementChPropertyInfo = "DOMHTMLTableRowElement::ch" attrGet _ = getDOMHTMLTableRowElementCh attrSet _ = setDOMHTMLTableRowElementCh attrConstruct _ = constructDOMHTMLTableRowElementCh -- VVV Prop "ch-off" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLTableRowElementChOff :: (MonadIO m, DOMHTMLTableRowElementK o) => o -> m T.Text getDOMHTMLTableRowElementChOff obj = liftIO $ getObjectPropertyString obj "ch-off" setDOMHTMLTableRowElementChOff :: (MonadIO m, DOMHTMLTableRowElementK o) => o -> T.Text -> m () setDOMHTMLTableRowElementChOff obj val = liftIO $ setObjectPropertyString obj "ch-off" val constructDOMHTMLTableRowElementChOff :: T.Text -> IO ([Char], GValue) constructDOMHTMLTableRowElementChOff val = constructObjectPropertyString "ch-off" val data DOMHTMLTableRowElementChOffPropertyInfo instance AttrInfo DOMHTMLTableRowElementChOffPropertyInfo where type AttrAllowedOps DOMHTMLTableRowElementChOffPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLTableRowElementChOffPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLTableRowElementChOffPropertyInfo = DOMHTMLTableRowElementK type AttrGetType DOMHTMLTableRowElementChOffPropertyInfo = T.Text type AttrLabel DOMHTMLTableRowElementChOffPropertyInfo = "DOMHTMLTableRowElement::ch-off" attrGet _ = getDOMHTMLTableRowElementChOff attrSet _ = setDOMHTMLTableRowElementChOff attrConstruct _ = constructDOMHTMLTableRowElementChOff -- VVV Prop "row-index" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMHTMLTableRowElementRowIndex :: (MonadIO m, DOMHTMLTableRowElementK o) => o -> m Int64 getDOMHTMLTableRowElementRowIndex obj = liftIO $ getObjectPropertyInt64 obj "row-index" data DOMHTMLTableRowElementRowIndexPropertyInfo instance AttrInfo DOMHTMLTableRowElementRowIndexPropertyInfo where type AttrAllowedOps DOMHTMLTableRowElementRowIndexPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLTableRowElementRowIndexPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLTableRowElementRowIndexPropertyInfo = DOMHTMLTableRowElementK type AttrGetType DOMHTMLTableRowElementRowIndexPropertyInfo = Int64 type AttrLabel DOMHTMLTableRowElementRowIndexPropertyInfo = "DOMHTMLTableRowElement::row-index" attrGet _ = getDOMHTMLTableRowElementRowIndex attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "section-row-index" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMHTMLTableRowElementSectionRowIndex :: (MonadIO m, DOMHTMLTableRowElementK o) => o -> m Int64 getDOMHTMLTableRowElementSectionRowIndex obj = liftIO $ getObjectPropertyInt64 obj "section-row-index" data DOMHTMLTableRowElementSectionRowIndexPropertyInfo instance AttrInfo DOMHTMLTableRowElementSectionRowIndexPropertyInfo where type AttrAllowedOps DOMHTMLTableRowElementSectionRowIndexPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLTableRowElementSectionRowIndexPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLTableRowElementSectionRowIndexPropertyInfo = DOMHTMLTableRowElementK type AttrGetType DOMHTMLTableRowElementSectionRowIndexPropertyInfo = Int64 type AttrLabel DOMHTMLTableRowElementSectionRowIndexPropertyInfo = "DOMHTMLTableRowElement::section-row-index" attrGet _ = getDOMHTMLTableRowElementSectionRowIndex attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "v-align" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLTableRowElementVAlign :: (MonadIO m, DOMHTMLTableRowElementK o) => o -> m T.Text getDOMHTMLTableRowElementVAlign obj = liftIO $ getObjectPropertyString obj "v-align" setDOMHTMLTableRowElementVAlign :: (MonadIO m, DOMHTMLTableRowElementK o) => o -> T.Text -> m () setDOMHTMLTableRowElementVAlign obj val = liftIO $ setObjectPropertyString obj "v-align" val constructDOMHTMLTableRowElementVAlign :: T.Text -> IO ([Char], GValue) constructDOMHTMLTableRowElementVAlign val = constructObjectPropertyString "v-align" val data DOMHTMLTableRowElementVAlignPropertyInfo instance AttrInfo DOMHTMLTableRowElementVAlignPropertyInfo where type AttrAllowedOps DOMHTMLTableRowElementVAlignPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLTableRowElementVAlignPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLTableRowElementVAlignPropertyInfo = DOMHTMLTableRowElementK type AttrGetType DOMHTMLTableRowElementVAlignPropertyInfo = T.Text type AttrLabel DOMHTMLTableRowElementVAlignPropertyInfo = "DOMHTMLTableRowElement::v-align" attrGet _ = getDOMHTMLTableRowElementVAlign attrSet _ = setDOMHTMLTableRowElementVAlign attrConstruct _ = constructDOMHTMLTableRowElementVAlign type instance AttributeList DOMHTMLTableRowElement = '[ '("access-key", DOMHTMLElementAccessKeyPropertyInfo), '("align", DOMHTMLTableRowElementAlignPropertyInfo), '("attributes", DOMElementAttributesPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("bg-color", DOMHTMLTableRowElementBgColorPropertyInfo), '("cells", DOMHTMLTableRowElementCellsPropertyInfo), '("ch", DOMHTMLTableRowElementChPropertyInfo), '("ch-off", DOMHTMLTableRowElementChOffPropertyInfo), '("child-element-count", DOMElementChildElementCountPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("children", DOMHTMLElementChildrenPropertyInfo), '("class-list", DOMElementClassListPropertyInfo), '("class-name", DOMElementClassNamePropertyInfo), '("client-height", DOMElementClientHeightPropertyInfo), '("client-left", DOMElementClientLeftPropertyInfo), '("client-top", DOMElementClientTopPropertyInfo), '("client-width", DOMElementClientWidthPropertyInfo), '("content-editable", DOMHTMLElementContentEditablePropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("dir", DOMHTMLElementDirPropertyInfo), '("draggable", DOMHTMLElementDraggablePropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("first-element-child", DOMElementFirstElementChildPropertyInfo), '("hidden", DOMHTMLElementHiddenPropertyInfo), '("id", DOMElementIdPropertyInfo), '("inner-html", DOMHTMLElementInnerHtmlPropertyInfo), '("inner-text", DOMHTMLElementInnerTextPropertyInfo), '("is-content-editable", DOMHTMLElementIsContentEditablePropertyInfo), '("lang", DOMHTMLElementLangPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-element-child", DOMElementLastElementChildPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-element-sibling", DOMElementNextElementSiblingPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("offset-height", DOMElementOffsetHeightPropertyInfo), '("offset-left", DOMElementOffsetLeftPropertyInfo), '("offset-parent", DOMElementOffsetParentPropertyInfo), '("offset-top", DOMElementOffsetTopPropertyInfo), '("offset-width", DOMElementOffsetWidthPropertyInfo), '("outer-html", DOMHTMLElementOuterHtmlPropertyInfo), '("outer-text", DOMHTMLElementOuterTextPropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-element-sibling", DOMElementPreviousElementSiblingPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("row-index", DOMHTMLTableRowElementRowIndexPropertyInfo), '("scroll-height", DOMElementScrollHeightPropertyInfo), '("scroll-left", DOMElementScrollLeftPropertyInfo), '("scroll-top", DOMElementScrollTopPropertyInfo), '("scroll-width", DOMElementScrollWidthPropertyInfo), '("section-row-index", DOMHTMLTableRowElementSectionRowIndexPropertyInfo), '("spellcheck", DOMHTMLElementSpellcheckPropertyInfo), '("style", DOMElementStylePropertyInfo), '("tab-index", DOMHTMLElementTabIndexPropertyInfo), '("tag-name", DOMElementTagNamePropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("title", DOMHTMLElementTitlePropertyInfo), '("translate", DOMHTMLElementTranslatePropertyInfo), '("v-align", DOMHTMLTableRowElementVAlignPropertyInfo), '("webkit-region-overset", DOMElementWebkitRegionOversetPropertyInfo), '("webkitdropzone", DOMHTMLElementWebkitdropzonePropertyInfo)] -- VVV Prop "align" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLTableSectionElementAlign :: (MonadIO m, DOMHTMLTableSectionElementK o) => o -> m T.Text getDOMHTMLTableSectionElementAlign obj = liftIO $ getObjectPropertyString obj "align" setDOMHTMLTableSectionElementAlign :: (MonadIO m, DOMHTMLTableSectionElementK o) => o -> T.Text -> m () setDOMHTMLTableSectionElementAlign obj val = liftIO $ setObjectPropertyString obj "align" val constructDOMHTMLTableSectionElementAlign :: T.Text -> IO ([Char], GValue) constructDOMHTMLTableSectionElementAlign val = constructObjectPropertyString "align" val data DOMHTMLTableSectionElementAlignPropertyInfo instance AttrInfo DOMHTMLTableSectionElementAlignPropertyInfo where type AttrAllowedOps DOMHTMLTableSectionElementAlignPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLTableSectionElementAlignPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLTableSectionElementAlignPropertyInfo = DOMHTMLTableSectionElementK type AttrGetType DOMHTMLTableSectionElementAlignPropertyInfo = T.Text type AttrLabel DOMHTMLTableSectionElementAlignPropertyInfo = "DOMHTMLTableSectionElement::align" attrGet _ = getDOMHTMLTableSectionElementAlign attrSet _ = setDOMHTMLTableSectionElementAlign attrConstruct _ = constructDOMHTMLTableSectionElementAlign -- VVV Prop "ch" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLTableSectionElementCh :: (MonadIO m, DOMHTMLTableSectionElementK o) => o -> m T.Text getDOMHTMLTableSectionElementCh obj = liftIO $ getObjectPropertyString obj "ch" setDOMHTMLTableSectionElementCh :: (MonadIO m, DOMHTMLTableSectionElementK o) => o -> T.Text -> m () setDOMHTMLTableSectionElementCh obj val = liftIO $ setObjectPropertyString obj "ch" val constructDOMHTMLTableSectionElementCh :: T.Text -> IO ([Char], GValue) constructDOMHTMLTableSectionElementCh val = constructObjectPropertyString "ch" val data DOMHTMLTableSectionElementChPropertyInfo instance AttrInfo DOMHTMLTableSectionElementChPropertyInfo where type AttrAllowedOps DOMHTMLTableSectionElementChPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLTableSectionElementChPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLTableSectionElementChPropertyInfo = DOMHTMLTableSectionElementK type AttrGetType DOMHTMLTableSectionElementChPropertyInfo = T.Text type AttrLabel DOMHTMLTableSectionElementChPropertyInfo = "DOMHTMLTableSectionElement::ch" attrGet _ = getDOMHTMLTableSectionElementCh attrSet _ = setDOMHTMLTableSectionElementCh attrConstruct _ = constructDOMHTMLTableSectionElementCh -- VVV Prop "ch-off" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLTableSectionElementChOff :: (MonadIO m, DOMHTMLTableSectionElementK o) => o -> m T.Text getDOMHTMLTableSectionElementChOff obj = liftIO $ getObjectPropertyString obj "ch-off" setDOMHTMLTableSectionElementChOff :: (MonadIO m, DOMHTMLTableSectionElementK o) => o -> T.Text -> m () setDOMHTMLTableSectionElementChOff obj val = liftIO $ setObjectPropertyString obj "ch-off" val constructDOMHTMLTableSectionElementChOff :: T.Text -> IO ([Char], GValue) constructDOMHTMLTableSectionElementChOff val = constructObjectPropertyString "ch-off" val data DOMHTMLTableSectionElementChOffPropertyInfo instance AttrInfo DOMHTMLTableSectionElementChOffPropertyInfo where type AttrAllowedOps DOMHTMLTableSectionElementChOffPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLTableSectionElementChOffPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLTableSectionElementChOffPropertyInfo = DOMHTMLTableSectionElementK type AttrGetType DOMHTMLTableSectionElementChOffPropertyInfo = T.Text type AttrLabel DOMHTMLTableSectionElementChOffPropertyInfo = "DOMHTMLTableSectionElement::ch-off" attrGet _ = getDOMHTMLTableSectionElementChOff attrSet _ = setDOMHTMLTableSectionElementChOff attrConstruct _ = constructDOMHTMLTableSectionElementChOff -- VVV Prop "rows" -- Type: TInterface "WebKit" "DOMHTMLCollection" -- Flags: [PropertyReadable] getDOMHTMLTableSectionElementRows :: (MonadIO m, DOMHTMLTableSectionElementK o) => o -> m DOMHTMLCollection getDOMHTMLTableSectionElementRows obj = liftIO $ getObjectPropertyObject obj "rows" DOMHTMLCollection data DOMHTMLTableSectionElementRowsPropertyInfo instance AttrInfo DOMHTMLTableSectionElementRowsPropertyInfo where type AttrAllowedOps DOMHTMLTableSectionElementRowsPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLTableSectionElementRowsPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLTableSectionElementRowsPropertyInfo = DOMHTMLTableSectionElementK type AttrGetType DOMHTMLTableSectionElementRowsPropertyInfo = DOMHTMLCollection type AttrLabel DOMHTMLTableSectionElementRowsPropertyInfo = "DOMHTMLTableSectionElement::rows" attrGet _ = getDOMHTMLTableSectionElementRows attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "v-align" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLTableSectionElementVAlign :: (MonadIO m, DOMHTMLTableSectionElementK o) => o -> m T.Text getDOMHTMLTableSectionElementVAlign obj = liftIO $ getObjectPropertyString obj "v-align" setDOMHTMLTableSectionElementVAlign :: (MonadIO m, DOMHTMLTableSectionElementK o) => o -> T.Text -> m () setDOMHTMLTableSectionElementVAlign obj val = liftIO $ setObjectPropertyString obj "v-align" val constructDOMHTMLTableSectionElementVAlign :: T.Text -> IO ([Char], GValue) constructDOMHTMLTableSectionElementVAlign val = constructObjectPropertyString "v-align" val data DOMHTMLTableSectionElementVAlignPropertyInfo instance AttrInfo DOMHTMLTableSectionElementVAlignPropertyInfo where type AttrAllowedOps DOMHTMLTableSectionElementVAlignPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLTableSectionElementVAlignPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLTableSectionElementVAlignPropertyInfo = DOMHTMLTableSectionElementK type AttrGetType DOMHTMLTableSectionElementVAlignPropertyInfo = T.Text type AttrLabel DOMHTMLTableSectionElementVAlignPropertyInfo = "DOMHTMLTableSectionElement::v-align" attrGet _ = getDOMHTMLTableSectionElementVAlign attrSet _ = setDOMHTMLTableSectionElementVAlign attrConstruct _ = constructDOMHTMLTableSectionElementVAlign type instance AttributeList DOMHTMLTableSectionElement = '[ '("access-key", DOMHTMLElementAccessKeyPropertyInfo), '("align", DOMHTMLTableSectionElementAlignPropertyInfo), '("attributes", DOMElementAttributesPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("ch", DOMHTMLTableSectionElementChPropertyInfo), '("ch-off", DOMHTMLTableSectionElementChOffPropertyInfo), '("child-element-count", DOMElementChildElementCountPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("children", DOMHTMLElementChildrenPropertyInfo), '("class-list", DOMElementClassListPropertyInfo), '("class-name", DOMElementClassNamePropertyInfo), '("client-height", DOMElementClientHeightPropertyInfo), '("client-left", DOMElementClientLeftPropertyInfo), '("client-top", DOMElementClientTopPropertyInfo), '("client-width", DOMElementClientWidthPropertyInfo), '("content-editable", DOMHTMLElementContentEditablePropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("dir", DOMHTMLElementDirPropertyInfo), '("draggable", DOMHTMLElementDraggablePropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("first-element-child", DOMElementFirstElementChildPropertyInfo), '("hidden", DOMHTMLElementHiddenPropertyInfo), '("id", DOMElementIdPropertyInfo), '("inner-html", DOMHTMLElementInnerHtmlPropertyInfo), '("inner-text", DOMHTMLElementInnerTextPropertyInfo), '("is-content-editable", DOMHTMLElementIsContentEditablePropertyInfo), '("lang", DOMHTMLElementLangPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-element-child", DOMElementLastElementChildPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-element-sibling", DOMElementNextElementSiblingPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("offset-height", DOMElementOffsetHeightPropertyInfo), '("offset-left", DOMElementOffsetLeftPropertyInfo), '("offset-parent", DOMElementOffsetParentPropertyInfo), '("offset-top", DOMElementOffsetTopPropertyInfo), '("offset-width", DOMElementOffsetWidthPropertyInfo), '("outer-html", DOMHTMLElementOuterHtmlPropertyInfo), '("outer-text", DOMHTMLElementOuterTextPropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-element-sibling", DOMElementPreviousElementSiblingPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("rows", DOMHTMLTableSectionElementRowsPropertyInfo), '("scroll-height", DOMElementScrollHeightPropertyInfo), '("scroll-left", DOMElementScrollLeftPropertyInfo), '("scroll-top", DOMElementScrollTopPropertyInfo), '("scroll-width", DOMElementScrollWidthPropertyInfo), '("spellcheck", DOMHTMLElementSpellcheckPropertyInfo), '("style", DOMElementStylePropertyInfo), '("tab-index", DOMHTMLElementTabIndexPropertyInfo), '("tag-name", DOMElementTagNamePropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("title", DOMHTMLElementTitlePropertyInfo), '("translate", DOMHTMLElementTranslatePropertyInfo), '("v-align", DOMHTMLTableSectionElementVAlignPropertyInfo), '("webkit-region-overset", DOMElementWebkitRegionOversetPropertyInfo), '("webkitdropzone", DOMHTMLElementWebkitdropzonePropertyInfo)] -- VVV Prop "autocapitalize" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLTextAreaElementAutocapitalize :: (MonadIO m, DOMHTMLTextAreaElementK o) => o -> m T.Text getDOMHTMLTextAreaElementAutocapitalize obj = liftIO $ getObjectPropertyString obj "autocapitalize" setDOMHTMLTextAreaElementAutocapitalize :: (MonadIO m, DOMHTMLTextAreaElementK o) => o -> T.Text -> m () setDOMHTMLTextAreaElementAutocapitalize obj val = liftIO $ setObjectPropertyString obj "autocapitalize" val constructDOMHTMLTextAreaElementAutocapitalize :: T.Text -> IO ([Char], GValue) constructDOMHTMLTextAreaElementAutocapitalize val = constructObjectPropertyString "autocapitalize" val data DOMHTMLTextAreaElementAutocapitalizePropertyInfo instance AttrInfo DOMHTMLTextAreaElementAutocapitalizePropertyInfo where type AttrAllowedOps DOMHTMLTextAreaElementAutocapitalizePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLTextAreaElementAutocapitalizePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLTextAreaElementAutocapitalizePropertyInfo = DOMHTMLTextAreaElementK type AttrGetType DOMHTMLTextAreaElementAutocapitalizePropertyInfo = T.Text type AttrLabel DOMHTMLTextAreaElementAutocapitalizePropertyInfo = "DOMHTMLTextAreaElement::autocapitalize" attrGet _ = getDOMHTMLTextAreaElementAutocapitalize attrSet _ = setDOMHTMLTextAreaElementAutocapitalize attrConstruct _ = constructDOMHTMLTextAreaElementAutocapitalize -- VVV Prop "autocorrect" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLTextAreaElementAutocorrect :: (MonadIO m, DOMHTMLTextAreaElementK o) => o -> m Bool getDOMHTMLTextAreaElementAutocorrect obj = liftIO $ getObjectPropertyBool obj "autocorrect" setDOMHTMLTextAreaElementAutocorrect :: (MonadIO m, DOMHTMLTextAreaElementK o) => o -> Bool -> m () setDOMHTMLTextAreaElementAutocorrect obj val = liftIO $ setObjectPropertyBool obj "autocorrect" val constructDOMHTMLTextAreaElementAutocorrect :: Bool -> IO ([Char], GValue) constructDOMHTMLTextAreaElementAutocorrect val = constructObjectPropertyBool "autocorrect" val data DOMHTMLTextAreaElementAutocorrectPropertyInfo instance AttrInfo DOMHTMLTextAreaElementAutocorrectPropertyInfo where type AttrAllowedOps DOMHTMLTextAreaElementAutocorrectPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLTextAreaElementAutocorrectPropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLTextAreaElementAutocorrectPropertyInfo = DOMHTMLTextAreaElementK type AttrGetType DOMHTMLTextAreaElementAutocorrectPropertyInfo = Bool type AttrLabel DOMHTMLTextAreaElementAutocorrectPropertyInfo = "DOMHTMLTextAreaElement::autocorrect" attrGet _ = getDOMHTMLTextAreaElementAutocorrect attrSet _ = setDOMHTMLTextAreaElementAutocorrect attrConstruct _ = constructDOMHTMLTextAreaElementAutocorrect -- VVV Prop "autofocus" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLTextAreaElementAutofocus :: (MonadIO m, DOMHTMLTextAreaElementK o) => o -> m Bool getDOMHTMLTextAreaElementAutofocus obj = liftIO $ getObjectPropertyBool obj "autofocus" setDOMHTMLTextAreaElementAutofocus :: (MonadIO m, DOMHTMLTextAreaElementK o) => o -> Bool -> m () setDOMHTMLTextAreaElementAutofocus obj val = liftIO $ setObjectPropertyBool obj "autofocus" val constructDOMHTMLTextAreaElementAutofocus :: Bool -> IO ([Char], GValue) constructDOMHTMLTextAreaElementAutofocus val = constructObjectPropertyBool "autofocus" val data DOMHTMLTextAreaElementAutofocusPropertyInfo instance AttrInfo DOMHTMLTextAreaElementAutofocusPropertyInfo where type AttrAllowedOps DOMHTMLTextAreaElementAutofocusPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLTextAreaElementAutofocusPropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLTextAreaElementAutofocusPropertyInfo = DOMHTMLTextAreaElementK type AttrGetType DOMHTMLTextAreaElementAutofocusPropertyInfo = Bool type AttrLabel DOMHTMLTextAreaElementAutofocusPropertyInfo = "DOMHTMLTextAreaElement::autofocus" attrGet _ = getDOMHTMLTextAreaElementAutofocus attrSet _ = setDOMHTMLTextAreaElementAutofocus attrConstruct _ = constructDOMHTMLTextAreaElementAutofocus -- VVV Prop "cols" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLTextAreaElementCols :: (MonadIO m, DOMHTMLTextAreaElementK o) => o -> m Int64 getDOMHTMLTextAreaElementCols obj = liftIO $ getObjectPropertyInt64 obj "cols" setDOMHTMLTextAreaElementCols :: (MonadIO m, DOMHTMLTextAreaElementK o) => o -> Int64 -> m () setDOMHTMLTextAreaElementCols obj val = liftIO $ setObjectPropertyInt64 obj "cols" val constructDOMHTMLTextAreaElementCols :: Int64 -> IO ([Char], GValue) constructDOMHTMLTextAreaElementCols val = constructObjectPropertyInt64 "cols" val data DOMHTMLTextAreaElementColsPropertyInfo instance AttrInfo DOMHTMLTextAreaElementColsPropertyInfo where type AttrAllowedOps DOMHTMLTextAreaElementColsPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLTextAreaElementColsPropertyInfo = (~) Int64 type AttrBaseTypeConstraint DOMHTMLTextAreaElementColsPropertyInfo = DOMHTMLTextAreaElementK type AttrGetType DOMHTMLTextAreaElementColsPropertyInfo = Int64 type AttrLabel DOMHTMLTextAreaElementColsPropertyInfo = "DOMHTMLTextAreaElement::cols" attrGet _ = getDOMHTMLTextAreaElementCols attrSet _ = setDOMHTMLTextAreaElementCols attrConstruct _ = constructDOMHTMLTextAreaElementCols -- VVV Prop "default-value" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLTextAreaElementDefaultValue :: (MonadIO m, DOMHTMLTextAreaElementK o) => o -> m T.Text getDOMHTMLTextAreaElementDefaultValue obj = liftIO $ getObjectPropertyString obj "default-value" setDOMHTMLTextAreaElementDefaultValue :: (MonadIO m, DOMHTMLTextAreaElementK o) => o -> T.Text -> m () setDOMHTMLTextAreaElementDefaultValue obj val = liftIO $ setObjectPropertyString obj "default-value" val constructDOMHTMLTextAreaElementDefaultValue :: T.Text -> IO ([Char], GValue) constructDOMHTMLTextAreaElementDefaultValue val = constructObjectPropertyString "default-value" val data DOMHTMLTextAreaElementDefaultValuePropertyInfo instance AttrInfo DOMHTMLTextAreaElementDefaultValuePropertyInfo where type AttrAllowedOps DOMHTMLTextAreaElementDefaultValuePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLTextAreaElementDefaultValuePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLTextAreaElementDefaultValuePropertyInfo = DOMHTMLTextAreaElementK type AttrGetType DOMHTMLTextAreaElementDefaultValuePropertyInfo = T.Text type AttrLabel DOMHTMLTextAreaElementDefaultValuePropertyInfo = "DOMHTMLTextAreaElement::default-value" attrGet _ = getDOMHTMLTextAreaElementDefaultValue attrSet _ = setDOMHTMLTextAreaElementDefaultValue attrConstruct _ = constructDOMHTMLTextAreaElementDefaultValue -- VVV Prop "dir-name" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLTextAreaElementDirName :: (MonadIO m, DOMHTMLTextAreaElementK o) => o -> m T.Text getDOMHTMLTextAreaElementDirName obj = liftIO $ getObjectPropertyString obj "dir-name" setDOMHTMLTextAreaElementDirName :: (MonadIO m, DOMHTMLTextAreaElementK o) => o -> T.Text -> m () setDOMHTMLTextAreaElementDirName obj val = liftIO $ setObjectPropertyString obj "dir-name" val constructDOMHTMLTextAreaElementDirName :: T.Text -> IO ([Char], GValue) constructDOMHTMLTextAreaElementDirName val = constructObjectPropertyString "dir-name" val data DOMHTMLTextAreaElementDirNamePropertyInfo instance AttrInfo DOMHTMLTextAreaElementDirNamePropertyInfo where type AttrAllowedOps DOMHTMLTextAreaElementDirNamePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLTextAreaElementDirNamePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLTextAreaElementDirNamePropertyInfo = DOMHTMLTextAreaElementK type AttrGetType DOMHTMLTextAreaElementDirNamePropertyInfo = T.Text type AttrLabel DOMHTMLTextAreaElementDirNamePropertyInfo = "DOMHTMLTextAreaElement::dir-name" attrGet _ = getDOMHTMLTextAreaElementDirName attrSet _ = setDOMHTMLTextAreaElementDirName attrConstruct _ = constructDOMHTMLTextAreaElementDirName -- VVV Prop "disabled" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLTextAreaElementDisabled :: (MonadIO m, DOMHTMLTextAreaElementK o) => o -> m Bool getDOMHTMLTextAreaElementDisabled obj = liftIO $ getObjectPropertyBool obj "disabled" setDOMHTMLTextAreaElementDisabled :: (MonadIO m, DOMHTMLTextAreaElementK o) => o -> Bool -> m () setDOMHTMLTextAreaElementDisabled obj val = liftIO $ setObjectPropertyBool obj "disabled" val constructDOMHTMLTextAreaElementDisabled :: Bool -> IO ([Char], GValue) constructDOMHTMLTextAreaElementDisabled val = constructObjectPropertyBool "disabled" val data DOMHTMLTextAreaElementDisabledPropertyInfo instance AttrInfo DOMHTMLTextAreaElementDisabledPropertyInfo where type AttrAllowedOps DOMHTMLTextAreaElementDisabledPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLTextAreaElementDisabledPropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLTextAreaElementDisabledPropertyInfo = DOMHTMLTextAreaElementK type AttrGetType DOMHTMLTextAreaElementDisabledPropertyInfo = Bool type AttrLabel DOMHTMLTextAreaElementDisabledPropertyInfo = "DOMHTMLTextAreaElement::disabled" attrGet _ = getDOMHTMLTextAreaElementDisabled attrSet _ = setDOMHTMLTextAreaElementDisabled attrConstruct _ = constructDOMHTMLTextAreaElementDisabled -- VVV Prop "form" -- Type: TInterface "WebKit" "DOMHTMLFormElement" -- Flags: [PropertyReadable] getDOMHTMLTextAreaElementForm :: (MonadIO m, DOMHTMLTextAreaElementK o) => o -> m DOMHTMLFormElement getDOMHTMLTextAreaElementForm obj = liftIO $ getObjectPropertyObject obj "form" DOMHTMLFormElement data DOMHTMLTextAreaElementFormPropertyInfo instance AttrInfo DOMHTMLTextAreaElementFormPropertyInfo where type AttrAllowedOps DOMHTMLTextAreaElementFormPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLTextAreaElementFormPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLTextAreaElementFormPropertyInfo = DOMHTMLTextAreaElementK type AttrGetType DOMHTMLTextAreaElementFormPropertyInfo = DOMHTMLFormElement type AttrLabel DOMHTMLTextAreaElementFormPropertyInfo = "DOMHTMLTextAreaElement::form" attrGet _ = getDOMHTMLTextAreaElementForm attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "labels" -- Type: TInterface "WebKit" "DOMNodeList" -- Flags: [PropertyReadable] getDOMHTMLTextAreaElementLabels :: (MonadIO m, DOMHTMLTextAreaElementK o) => o -> m DOMNodeList getDOMHTMLTextAreaElementLabels obj = liftIO $ getObjectPropertyObject obj "labels" DOMNodeList data DOMHTMLTextAreaElementLabelsPropertyInfo instance AttrInfo DOMHTMLTextAreaElementLabelsPropertyInfo where type AttrAllowedOps DOMHTMLTextAreaElementLabelsPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLTextAreaElementLabelsPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLTextAreaElementLabelsPropertyInfo = DOMHTMLTextAreaElementK type AttrGetType DOMHTMLTextAreaElementLabelsPropertyInfo = DOMNodeList type AttrLabel DOMHTMLTextAreaElementLabelsPropertyInfo = "DOMHTMLTextAreaElement::labels" attrGet _ = getDOMHTMLTextAreaElementLabels attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "max-length" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLTextAreaElementMaxLength :: (MonadIO m, DOMHTMLTextAreaElementK o) => o -> m Int64 getDOMHTMLTextAreaElementMaxLength obj = liftIO $ getObjectPropertyInt64 obj "max-length" setDOMHTMLTextAreaElementMaxLength :: (MonadIO m, DOMHTMLTextAreaElementK o) => o -> Int64 -> m () setDOMHTMLTextAreaElementMaxLength obj val = liftIO $ setObjectPropertyInt64 obj "max-length" val constructDOMHTMLTextAreaElementMaxLength :: Int64 -> IO ([Char], GValue) constructDOMHTMLTextAreaElementMaxLength val = constructObjectPropertyInt64 "max-length" val data DOMHTMLTextAreaElementMaxLengthPropertyInfo instance AttrInfo DOMHTMLTextAreaElementMaxLengthPropertyInfo where type AttrAllowedOps DOMHTMLTextAreaElementMaxLengthPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLTextAreaElementMaxLengthPropertyInfo = (~) Int64 type AttrBaseTypeConstraint DOMHTMLTextAreaElementMaxLengthPropertyInfo = DOMHTMLTextAreaElementK type AttrGetType DOMHTMLTextAreaElementMaxLengthPropertyInfo = Int64 type AttrLabel DOMHTMLTextAreaElementMaxLengthPropertyInfo = "DOMHTMLTextAreaElement::max-length" attrGet _ = getDOMHTMLTextAreaElementMaxLength attrSet _ = setDOMHTMLTextAreaElementMaxLength attrConstruct _ = constructDOMHTMLTextAreaElementMaxLength -- VVV Prop "name" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLTextAreaElementName :: (MonadIO m, DOMHTMLTextAreaElementK o) => o -> m T.Text getDOMHTMLTextAreaElementName obj = liftIO $ getObjectPropertyString obj "name" setDOMHTMLTextAreaElementName :: (MonadIO m, DOMHTMLTextAreaElementK o) => o -> T.Text -> m () setDOMHTMLTextAreaElementName obj val = liftIO $ setObjectPropertyString obj "name" val constructDOMHTMLTextAreaElementName :: T.Text -> IO ([Char], GValue) constructDOMHTMLTextAreaElementName val = constructObjectPropertyString "name" val data DOMHTMLTextAreaElementNamePropertyInfo instance AttrInfo DOMHTMLTextAreaElementNamePropertyInfo where type AttrAllowedOps DOMHTMLTextAreaElementNamePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLTextAreaElementNamePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLTextAreaElementNamePropertyInfo = DOMHTMLTextAreaElementK type AttrGetType DOMHTMLTextAreaElementNamePropertyInfo = T.Text type AttrLabel DOMHTMLTextAreaElementNamePropertyInfo = "DOMHTMLTextAreaElement::name" attrGet _ = getDOMHTMLTextAreaElementName attrSet _ = setDOMHTMLTextAreaElementName attrConstruct _ = constructDOMHTMLTextAreaElementName -- VVV Prop "placeholder" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLTextAreaElementPlaceholder :: (MonadIO m, DOMHTMLTextAreaElementK o) => o -> m T.Text getDOMHTMLTextAreaElementPlaceholder obj = liftIO $ getObjectPropertyString obj "placeholder" setDOMHTMLTextAreaElementPlaceholder :: (MonadIO m, DOMHTMLTextAreaElementK o) => o -> T.Text -> m () setDOMHTMLTextAreaElementPlaceholder obj val = liftIO $ setObjectPropertyString obj "placeholder" val constructDOMHTMLTextAreaElementPlaceholder :: T.Text -> IO ([Char], GValue) constructDOMHTMLTextAreaElementPlaceholder val = constructObjectPropertyString "placeholder" val data DOMHTMLTextAreaElementPlaceholderPropertyInfo instance AttrInfo DOMHTMLTextAreaElementPlaceholderPropertyInfo where type AttrAllowedOps DOMHTMLTextAreaElementPlaceholderPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLTextAreaElementPlaceholderPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLTextAreaElementPlaceholderPropertyInfo = DOMHTMLTextAreaElementK type AttrGetType DOMHTMLTextAreaElementPlaceholderPropertyInfo = T.Text type AttrLabel DOMHTMLTextAreaElementPlaceholderPropertyInfo = "DOMHTMLTextAreaElement::placeholder" attrGet _ = getDOMHTMLTextAreaElementPlaceholder attrSet _ = setDOMHTMLTextAreaElementPlaceholder attrConstruct _ = constructDOMHTMLTextAreaElementPlaceholder -- VVV Prop "read-only" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLTextAreaElementReadOnly :: (MonadIO m, DOMHTMLTextAreaElementK o) => o -> m Bool getDOMHTMLTextAreaElementReadOnly obj = liftIO $ getObjectPropertyBool obj "read-only" setDOMHTMLTextAreaElementReadOnly :: (MonadIO m, DOMHTMLTextAreaElementK o) => o -> Bool -> m () setDOMHTMLTextAreaElementReadOnly obj val = liftIO $ setObjectPropertyBool obj "read-only" val constructDOMHTMLTextAreaElementReadOnly :: Bool -> IO ([Char], GValue) constructDOMHTMLTextAreaElementReadOnly val = constructObjectPropertyBool "read-only" val data DOMHTMLTextAreaElementReadOnlyPropertyInfo instance AttrInfo DOMHTMLTextAreaElementReadOnlyPropertyInfo where type AttrAllowedOps DOMHTMLTextAreaElementReadOnlyPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLTextAreaElementReadOnlyPropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLTextAreaElementReadOnlyPropertyInfo = DOMHTMLTextAreaElementK type AttrGetType DOMHTMLTextAreaElementReadOnlyPropertyInfo = Bool type AttrLabel DOMHTMLTextAreaElementReadOnlyPropertyInfo = "DOMHTMLTextAreaElement::read-only" attrGet _ = getDOMHTMLTextAreaElementReadOnly attrSet _ = setDOMHTMLTextAreaElementReadOnly attrConstruct _ = constructDOMHTMLTextAreaElementReadOnly -- VVV Prop "required" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLTextAreaElementRequired :: (MonadIO m, DOMHTMLTextAreaElementK o) => o -> m Bool getDOMHTMLTextAreaElementRequired obj = liftIO $ getObjectPropertyBool obj "required" setDOMHTMLTextAreaElementRequired :: (MonadIO m, DOMHTMLTextAreaElementK o) => o -> Bool -> m () setDOMHTMLTextAreaElementRequired obj val = liftIO $ setObjectPropertyBool obj "required" val constructDOMHTMLTextAreaElementRequired :: Bool -> IO ([Char], GValue) constructDOMHTMLTextAreaElementRequired val = constructObjectPropertyBool "required" val data DOMHTMLTextAreaElementRequiredPropertyInfo instance AttrInfo DOMHTMLTextAreaElementRequiredPropertyInfo where type AttrAllowedOps DOMHTMLTextAreaElementRequiredPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLTextAreaElementRequiredPropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLTextAreaElementRequiredPropertyInfo = DOMHTMLTextAreaElementK type AttrGetType DOMHTMLTextAreaElementRequiredPropertyInfo = Bool type AttrLabel DOMHTMLTextAreaElementRequiredPropertyInfo = "DOMHTMLTextAreaElement::required" attrGet _ = getDOMHTMLTextAreaElementRequired attrSet _ = setDOMHTMLTextAreaElementRequired attrConstruct _ = constructDOMHTMLTextAreaElementRequired -- VVV Prop "rows" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLTextAreaElementRows :: (MonadIO m, DOMHTMLTextAreaElementK o) => o -> m Int64 getDOMHTMLTextAreaElementRows obj = liftIO $ getObjectPropertyInt64 obj "rows" setDOMHTMLTextAreaElementRows :: (MonadIO m, DOMHTMLTextAreaElementK o) => o -> Int64 -> m () setDOMHTMLTextAreaElementRows obj val = liftIO $ setObjectPropertyInt64 obj "rows" val constructDOMHTMLTextAreaElementRows :: Int64 -> IO ([Char], GValue) constructDOMHTMLTextAreaElementRows val = constructObjectPropertyInt64 "rows" val data DOMHTMLTextAreaElementRowsPropertyInfo instance AttrInfo DOMHTMLTextAreaElementRowsPropertyInfo where type AttrAllowedOps DOMHTMLTextAreaElementRowsPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLTextAreaElementRowsPropertyInfo = (~) Int64 type AttrBaseTypeConstraint DOMHTMLTextAreaElementRowsPropertyInfo = DOMHTMLTextAreaElementK type AttrGetType DOMHTMLTextAreaElementRowsPropertyInfo = Int64 type AttrLabel DOMHTMLTextAreaElementRowsPropertyInfo = "DOMHTMLTextAreaElement::rows" attrGet _ = getDOMHTMLTextAreaElementRows attrSet _ = setDOMHTMLTextAreaElementRows attrConstruct _ = constructDOMHTMLTextAreaElementRows -- VVV Prop "selection-direction" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLTextAreaElementSelectionDirection :: (MonadIO m, DOMHTMLTextAreaElementK o) => o -> m T.Text getDOMHTMLTextAreaElementSelectionDirection obj = liftIO $ getObjectPropertyString obj "selection-direction" setDOMHTMLTextAreaElementSelectionDirection :: (MonadIO m, DOMHTMLTextAreaElementK o) => o -> T.Text -> m () setDOMHTMLTextAreaElementSelectionDirection obj val = liftIO $ setObjectPropertyString obj "selection-direction" val constructDOMHTMLTextAreaElementSelectionDirection :: T.Text -> IO ([Char], GValue) constructDOMHTMLTextAreaElementSelectionDirection val = constructObjectPropertyString "selection-direction" val data DOMHTMLTextAreaElementSelectionDirectionPropertyInfo instance AttrInfo DOMHTMLTextAreaElementSelectionDirectionPropertyInfo where type AttrAllowedOps DOMHTMLTextAreaElementSelectionDirectionPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLTextAreaElementSelectionDirectionPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLTextAreaElementSelectionDirectionPropertyInfo = DOMHTMLTextAreaElementK type AttrGetType DOMHTMLTextAreaElementSelectionDirectionPropertyInfo = T.Text type AttrLabel DOMHTMLTextAreaElementSelectionDirectionPropertyInfo = "DOMHTMLTextAreaElement::selection-direction" attrGet _ = getDOMHTMLTextAreaElementSelectionDirection attrSet _ = setDOMHTMLTextAreaElementSelectionDirection attrConstruct _ = constructDOMHTMLTextAreaElementSelectionDirection -- VVV Prop "selection-end" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLTextAreaElementSelectionEnd :: (MonadIO m, DOMHTMLTextAreaElementK o) => o -> m Int64 getDOMHTMLTextAreaElementSelectionEnd obj = liftIO $ getObjectPropertyInt64 obj "selection-end" setDOMHTMLTextAreaElementSelectionEnd :: (MonadIO m, DOMHTMLTextAreaElementK o) => o -> Int64 -> m () setDOMHTMLTextAreaElementSelectionEnd obj val = liftIO $ setObjectPropertyInt64 obj "selection-end" val constructDOMHTMLTextAreaElementSelectionEnd :: Int64 -> IO ([Char], GValue) constructDOMHTMLTextAreaElementSelectionEnd val = constructObjectPropertyInt64 "selection-end" val data DOMHTMLTextAreaElementSelectionEndPropertyInfo instance AttrInfo DOMHTMLTextAreaElementSelectionEndPropertyInfo where type AttrAllowedOps DOMHTMLTextAreaElementSelectionEndPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLTextAreaElementSelectionEndPropertyInfo = (~) Int64 type AttrBaseTypeConstraint DOMHTMLTextAreaElementSelectionEndPropertyInfo = DOMHTMLTextAreaElementK type AttrGetType DOMHTMLTextAreaElementSelectionEndPropertyInfo = Int64 type AttrLabel DOMHTMLTextAreaElementSelectionEndPropertyInfo = "DOMHTMLTextAreaElement::selection-end" attrGet _ = getDOMHTMLTextAreaElementSelectionEnd attrSet _ = setDOMHTMLTextAreaElementSelectionEnd attrConstruct _ = constructDOMHTMLTextAreaElementSelectionEnd -- VVV Prop "selection-start" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLTextAreaElementSelectionStart :: (MonadIO m, DOMHTMLTextAreaElementK o) => o -> m Int64 getDOMHTMLTextAreaElementSelectionStart obj = liftIO $ getObjectPropertyInt64 obj "selection-start" setDOMHTMLTextAreaElementSelectionStart :: (MonadIO m, DOMHTMLTextAreaElementK o) => o -> Int64 -> m () setDOMHTMLTextAreaElementSelectionStart obj val = liftIO $ setObjectPropertyInt64 obj "selection-start" val constructDOMHTMLTextAreaElementSelectionStart :: Int64 -> IO ([Char], GValue) constructDOMHTMLTextAreaElementSelectionStart val = constructObjectPropertyInt64 "selection-start" val data DOMHTMLTextAreaElementSelectionStartPropertyInfo instance AttrInfo DOMHTMLTextAreaElementSelectionStartPropertyInfo where type AttrAllowedOps DOMHTMLTextAreaElementSelectionStartPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLTextAreaElementSelectionStartPropertyInfo = (~) Int64 type AttrBaseTypeConstraint DOMHTMLTextAreaElementSelectionStartPropertyInfo = DOMHTMLTextAreaElementK type AttrGetType DOMHTMLTextAreaElementSelectionStartPropertyInfo = Int64 type AttrLabel DOMHTMLTextAreaElementSelectionStartPropertyInfo = "DOMHTMLTextAreaElement::selection-start" attrGet _ = getDOMHTMLTextAreaElementSelectionStart attrSet _ = setDOMHTMLTextAreaElementSelectionStart attrConstruct _ = constructDOMHTMLTextAreaElementSelectionStart -- VVV Prop "text-length" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMHTMLTextAreaElementTextLength :: (MonadIO m, DOMHTMLTextAreaElementK o) => o -> m Word64 getDOMHTMLTextAreaElementTextLength obj = liftIO $ getObjectPropertyUInt64 obj "text-length" data DOMHTMLTextAreaElementTextLengthPropertyInfo instance AttrInfo DOMHTMLTextAreaElementTextLengthPropertyInfo where type AttrAllowedOps DOMHTMLTextAreaElementTextLengthPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLTextAreaElementTextLengthPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLTextAreaElementTextLengthPropertyInfo = DOMHTMLTextAreaElementK type AttrGetType DOMHTMLTextAreaElementTextLengthPropertyInfo = Word64 type AttrLabel DOMHTMLTextAreaElementTextLengthPropertyInfo = "DOMHTMLTextAreaElement::text-length" attrGet _ = getDOMHTMLTextAreaElementTextLength attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "type" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMHTMLTextAreaElementType :: (MonadIO m, DOMHTMLTextAreaElementK o) => o -> m T.Text getDOMHTMLTextAreaElementType obj = liftIO $ getObjectPropertyString obj "type" data DOMHTMLTextAreaElementTypePropertyInfo instance AttrInfo DOMHTMLTextAreaElementTypePropertyInfo where type AttrAllowedOps DOMHTMLTextAreaElementTypePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLTextAreaElementTypePropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLTextAreaElementTypePropertyInfo = DOMHTMLTextAreaElementK type AttrGetType DOMHTMLTextAreaElementTypePropertyInfo = T.Text type AttrLabel DOMHTMLTextAreaElementTypePropertyInfo = "DOMHTMLTextAreaElement::type" attrGet _ = getDOMHTMLTextAreaElementType attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "validation-message" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMHTMLTextAreaElementValidationMessage :: (MonadIO m, DOMHTMLTextAreaElementK o) => o -> m T.Text getDOMHTMLTextAreaElementValidationMessage obj = liftIO $ getObjectPropertyString obj "validation-message" data DOMHTMLTextAreaElementValidationMessagePropertyInfo instance AttrInfo DOMHTMLTextAreaElementValidationMessagePropertyInfo where type AttrAllowedOps DOMHTMLTextAreaElementValidationMessagePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLTextAreaElementValidationMessagePropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLTextAreaElementValidationMessagePropertyInfo = DOMHTMLTextAreaElementK type AttrGetType DOMHTMLTextAreaElementValidationMessagePropertyInfo = T.Text type AttrLabel DOMHTMLTextAreaElementValidationMessagePropertyInfo = "DOMHTMLTextAreaElement::validation-message" attrGet _ = getDOMHTMLTextAreaElementValidationMessage attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "validity" -- Type: TInterface "WebKit" "DOMValidityState" -- Flags: [PropertyReadable] getDOMHTMLTextAreaElementValidity :: (MonadIO m, DOMHTMLTextAreaElementK o) => o -> m DOMValidityState getDOMHTMLTextAreaElementValidity obj = liftIO $ getObjectPropertyObject obj "validity" DOMValidityState data DOMHTMLTextAreaElementValidityPropertyInfo instance AttrInfo DOMHTMLTextAreaElementValidityPropertyInfo where type AttrAllowedOps DOMHTMLTextAreaElementValidityPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLTextAreaElementValidityPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLTextAreaElementValidityPropertyInfo = DOMHTMLTextAreaElementK type AttrGetType DOMHTMLTextAreaElementValidityPropertyInfo = DOMValidityState type AttrLabel DOMHTMLTextAreaElementValidityPropertyInfo = "DOMHTMLTextAreaElement::validity" attrGet _ = getDOMHTMLTextAreaElementValidity attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "value" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLTextAreaElementValue :: (MonadIO m, DOMHTMLTextAreaElementK o) => o -> m T.Text getDOMHTMLTextAreaElementValue obj = liftIO $ getObjectPropertyString obj "value" setDOMHTMLTextAreaElementValue :: (MonadIO m, DOMHTMLTextAreaElementK o) => o -> T.Text -> m () setDOMHTMLTextAreaElementValue obj val = liftIO $ setObjectPropertyString obj "value" val constructDOMHTMLTextAreaElementValue :: T.Text -> IO ([Char], GValue) constructDOMHTMLTextAreaElementValue val = constructObjectPropertyString "value" val data DOMHTMLTextAreaElementValuePropertyInfo instance AttrInfo DOMHTMLTextAreaElementValuePropertyInfo where type AttrAllowedOps DOMHTMLTextAreaElementValuePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLTextAreaElementValuePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLTextAreaElementValuePropertyInfo = DOMHTMLTextAreaElementK type AttrGetType DOMHTMLTextAreaElementValuePropertyInfo = T.Text type AttrLabel DOMHTMLTextAreaElementValuePropertyInfo = "DOMHTMLTextAreaElement::value" attrGet _ = getDOMHTMLTextAreaElementValue attrSet _ = setDOMHTMLTextAreaElementValue attrConstruct _ = constructDOMHTMLTextAreaElementValue -- VVV Prop "will-validate" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMHTMLTextAreaElementWillValidate :: (MonadIO m, DOMHTMLTextAreaElementK o) => o -> m Bool getDOMHTMLTextAreaElementWillValidate obj = liftIO $ getObjectPropertyBool obj "will-validate" data DOMHTMLTextAreaElementWillValidatePropertyInfo instance AttrInfo DOMHTMLTextAreaElementWillValidatePropertyInfo where type AttrAllowedOps DOMHTMLTextAreaElementWillValidatePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLTextAreaElementWillValidatePropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLTextAreaElementWillValidatePropertyInfo = DOMHTMLTextAreaElementK type AttrGetType DOMHTMLTextAreaElementWillValidatePropertyInfo = Bool type AttrLabel DOMHTMLTextAreaElementWillValidatePropertyInfo = "DOMHTMLTextAreaElement::will-validate" attrGet _ = getDOMHTMLTextAreaElementWillValidate attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "wrap" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLTextAreaElementWrap :: (MonadIO m, DOMHTMLTextAreaElementK o) => o -> m T.Text getDOMHTMLTextAreaElementWrap obj = liftIO $ getObjectPropertyString obj "wrap" setDOMHTMLTextAreaElementWrap :: (MonadIO m, DOMHTMLTextAreaElementK o) => o -> T.Text -> m () setDOMHTMLTextAreaElementWrap obj val = liftIO $ setObjectPropertyString obj "wrap" val constructDOMHTMLTextAreaElementWrap :: T.Text -> IO ([Char], GValue) constructDOMHTMLTextAreaElementWrap val = constructObjectPropertyString "wrap" val data DOMHTMLTextAreaElementWrapPropertyInfo instance AttrInfo DOMHTMLTextAreaElementWrapPropertyInfo where type AttrAllowedOps DOMHTMLTextAreaElementWrapPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLTextAreaElementWrapPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLTextAreaElementWrapPropertyInfo = DOMHTMLTextAreaElementK type AttrGetType DOMHTMLTextAreaElementWrapPropertyInfo = T.Text type AttrLabel DOMHTMLTextAreaElementWrapPropertyInfo = "DOMHTMLTextAreaElement::wrap" attrGet _ = getDOMHTMLTextAreaElementWrap attrSet _ = setDOMHTMLTextAreaElementWrap attrConstruct _ = constructDOMHTMLTextAreaElementWrap type instance AttributeList DOMHTMLTextAreaElement = '[ '("access-key", DOMHTMLElementAccessKeyPropertyInfo), '("attributes", DOMElementAttributesPropertyInfo), '("autocapitalize", DOMHTMLTextAreaElementAutocapitalizePropertyInfo), '("autocorrect", DOMHTMLTextAreaElementAutocorrectPropertyInfo), '("autofocus", DOMHTMLTextAreaElementAutofocusPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("child-element-count", DOMElementChildElementCountPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("children", DOMHTMLElementChildrenPropertyInfo), '("class-list", DOMElementClassListPropertyInfo), '("class-name", DOMElementClassNamePropertyInfo), '("client-height", DOMElementClientHeightPropertyInfo), '("client-left", DOMElementClientLeftPropertyInfo), '("client-top", DOMElementClientTopPropertyInfo), '("client-width", DOMElementClientWidthPropertyInfo), '("cols", DOMHTMLTextAreaElementColsPropertyInfo), '("content-editable", DOMHTMLElementContentEditablePropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("default-value", DOMHTMLTextAreaElementDefaultValuePropertyInfo), '("dir", DOMHTMLElementDirPropertyInfo), '("dir-name", DOMHTMLTextAreaElementDirNamePropertyInfo), '("disabled", DOMHTMLTextAreaElementDisabledPropertyInfo), '("draggable", DOMHTMLElementDraggablePropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("first-element-child", DOMElementFirstElementChildPropertyInfo), '("form", DOMHTMLTextAreaElementFormPropertyInfo), '("hidden", DOMHTMLElementHiddenPropertyInfo), '("id", DOMElementIdPropertyInfo), '("inner-html", DOMHTMLElementInnerHtmlPropertyInfo), '("inner-text", DOMHTMLElementInnerTextPropertyInfo), '("is-content-editable", DOMHTMLElementIsContentEditablePropertyInfo), '("labels", DOMHTMLTextAreaElementLabelsPropertyInfo), '("lang", DOMHTMLElementLangPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-element-child", DOMElementLastElementChildPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("max-length", DOMHTMLTextAreaElementMaxLengthPropertyInfo), '("name", DOMHTMLTextAreaElementNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-element-sibling", DOMElementNextElementSiblingPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("offset-height", DOMElementOffsetHeightPropertyInfo), '("offset-left", DOMElementOffsetLeftPropertyInfo), '("offset-parent", DOMElementOffsetParentPropertyInfo), '("offset-top", DOMElementOffsetTopPropertyInfo), '("offset-width", DOMElementOffsetWidthPropertyInfo), '("outer-html", DOMHTMLElementOuterHtmlPropertyInfo), '("outer-text", DOMHTMLElementOuterTextPropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("placeholder", DOMHTMLTextAreaElementPlaceholderPropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-element-sibling", DOMElementPreviousElementSiblingPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("read-only", DOMHTMLTextAreaElementReadOnlyPropertyInfo), '("required", DOMHTMLTextAreaElementRequiredPropertyInfo), '("rows", DOMHTMLTextAreaElementRowsPropertyInfo), '("scroll-height", DOMElementScrollHeightPropertyInfo), '("scroll-left", DOMElementScrollLeftPropertyInfo), '("scroll-top", DOMElementScrollTopPropertyInfo), '("scroll-width", DOMElementScrollWidthPropertyInfo), '("selection-direction", DOMHTMLTextAreaElementSelectionDirectionPropertyInfo), '("selection-end", DOMHTMLTextAreaElementSelectionEndPropertyInfo), '("selection-start", DOMHTMLTextAreaElementSelectionStartPropertyInfo), '("spellcheck", DOMHTMLElementSpellcheckPropertyInfo), '("style", DOMElementStylePropertyInfo), '("tab-index", DOMHTMLElementTabIndexPropertyInfo), '("tag-name", DOMElementTagNamePropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("text-length", DOMHTMLTextAreaElementTextLengthPropertyInfo), '("title", DOMHTMLElementTitlePropertyInfo), '("translate", DOMHTMLElementTranslatePropertyInfo), '("type", DOMHTMLTextAreaElementTypePropertyInfo), '("validation-message", DOMHTMLTextAreaElementValidationMessagePropertyInfo), '("validity", DOMHTMLTextAreaElementValidityPropertyInfo), '("value", DOMHTMLTextAreaElementValuePropertyInfo), '("webkit-region-overset", DOMElementWebkitRegionOversetPropertyInfo), '("webkitdropzone", DOMHTMLElementWebkitdropzonePropertyInfo), '("will-validate", DOMHTMLTextAreaElementWillValidatePropertyInfo), '("wrap", DOMHTMLTextAreaElementWrapPropertyInfo)] -- VVV Prop "text" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLTitleElementText :: (MonadIO m, DOMHTMLTitleElementK o) => o -> m T.Text getDOMHTMLTitleElementText obj = liftIO $ getObjectPropertyString obj "text" setDOMHTMLTitleElementText :: (MonadIO m, DOMHTMLTitleElementK o) => o -> T.Text -> m () setDOMHTMLTitleElementText obj val = liftIO $ setObjectPropertyString obj "text" val constructDOMHTMLTitleElementText :: T.Text -> IO ([Char], GValue) constructDOMHTMLTitleElementText val = constructObjectPropertyString "text" val data DOMHTMLTitleElementTextPropertyInfo instance AttrInfo DOMHTMLTitleElementTextPropertyInfo where type AttrAllowedOps DOMHTMLTitleElementTextPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLTitleElementTextPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLTitleElementTextPropertyInfo = DOMHTMLTitleElementK type AttrGetType DOMHTMLTitleElementTextPropertyInfo = T.Text type AttrLabel DOMHTMLTitleElementTextPropertyInfo = "DOMHTMLTitleElement::text" attrGet _ = getDOMHTMLTitleElementText attrSet _ = setDOMHTMLTitleElementText attrConstruct _ = constructDOMHTMLTitleElementText type instance AttributeList DOMHTMLTitleElement = '[ '("access-key", DOMHTMLElementAccessKeyPropertyInfo), '("attributes", DOMElementAttributesPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("child-element-count", DOMElementChildElementCountPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("children", DOMHTMLElementChildrenPropertyInfo), '("class-list", DOMElementClassListPropertyInfo), '("class-name", DOMElementClassNamePropertyInfo), '("client-height", DOMElementClientHeightPropertyInfo), '("client-left", DOMElementClientLeftPropertyInfo), '("client-top", DOMElementClientTopPropertyInfo), '("client-width", DOMElementClientWidthPropertyInfo), '("content-editable", DOMHTMLElementContentEditablePropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("dir", DOMHTMLElementDirPropertyInfo), '("draggable", DOMHTMLElementDraggablePropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("first-element-child", DOMElementFirstElementChildPropertyInfo), '("hidden", DOMHTMLElementHiddenPropertyInfo), '("id", DOMElementIdPropertyInfo), '("inner-html", DOMHTMLElementInnerHtmlPropertyInfo), '("inner-text", DOMHTMLElementInnerTextPropertyInfo), '("is-content-editable", DOMHTMLElementIsContentEditablePropertyInfo), '("lang", DOMHTMLElementLangPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-element-child", DOMElementLastElementChildPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-element-sibling", DOMElementNextElementSiblingPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("offset-height", DOMElementOffsetHeightPropertyInfo), '("offset-left", DOMElementOffsetLeftPropertyInfo), '("offset-parent", DOMElementOffsetParentPropertyInfo), '("offset-top", DOMElementOffsetTopPropertyInfo), '("offset-width", DOMElementOffsetWidthPropertyInfo), '("outer-html", DOMHTMLElementOuterHtmlPropertyInfo), '("outer-text", DOMHTMLElementOuterTextPropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-element-sibling", DOMElementPreviousElementSiblingPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("scroll-height", DOMElementScrollHeightPropertyInfo), '("scroll-left", DOMElementScrollLeftPropertyInfo), '("scroll-top", DOMElementScrollTopPropertyInfo), '("scroll-width", DOMElementScrollWidthPropertyInfo), '("spellcheck", DOMHTMLElementSpellcheckPropertyInfo), '("style", DOMElementStylePropertyInfo), '("tab-index", DOMHTMLElementTabIndexPropertyInfo), '("tag-name", DOMElementTagNamePropertyInfo), '("text", DOMHTMLTitleElementTextPropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("title", DOMHTMLElementTitlePropertyInfo), '("translate", DOMHTMLElementTranslatePropertyInfo), '("webkit-region-overset", DOMElementWebkitRegionOversetPropertyInfo), '("webkitdropzone", DOMHTMLElementWebkitdropzonePropertyInfo)] -- VVV Prop "compact" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLUListElementCompact :: (MonadIO m, DOMHTMLUListElementK o) => o -> m Bool getDOMHTMLUListElementCompact obj = liftIO $ getObjectPropertyBool obj "compact" setDOMHTMLUListElementCompact :: (MonadIO m, DOMHTMLUListElementK o) => o -> Bool -> m () setDOMHTMLUListElementCompact obj val = liftIO $ setObjectPropertyBool obj "compact" val constructDOMHTMLUListElementCompact :: Bool -> IO ([Char], GValue) constructDOMHTMLUListElementCompact val = constructObjectPropertyBool "compact" val data DOMHTMLUListElementCompactPropertyInfo instance AttrInfo DOMHTMLUListElementCompactPropertyInfo where type AttrAllowedOps DOMHTMLUListElementCompactPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLUListElementCompactPropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLUListElementCompactPropertyInfo = DOMHTMLUListElementK type AttrGetType DOMHTMLUListElementCompactPropertyInfo = Bool type AttrLabel DOMHTMLUListElementCompactPropertyInfo = "DOMHTMLUListElement::compact" attrGet _ = getDOMHTMLUListElementCompact attrSet _ = setDOMHTMLUListElementCompact attrConstruct _ = constructDOMHTMLUListElementCompact -- VVV Prop "type" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLUListElementType :: (MonadIO m, DOMHTMLUListElementK o) => o -> m T.Text getDOMHTMLUListElementType obj = liftIO $ getObjectPropertyString obj "type" setDOMHTMLUListElementType :: (MonadIO m, DOMHTMLUListElementK o) => o -> T.Text -> m () setDOMHTMLUListElementType obj val = liftIO $ setObjectPropertyString obj "type" val constructDOMHTMLUListElementType :: T.Text -> IO ([Char], GValue) constructDOMHTMLUListElementType val = constructObjectPropertyString "type" val data DOMHTMLUListElementTypePropertyInfo instance AttrInfo DOMHTMLUListElementTypePropertyInfo where type AttrAllowedOps DOMHTMLUListElementTypePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLUListElementTypePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLUListElementTypePropertyInfo = DOMHTMLUListElementK type AttrGetType DOMHTMLUListElementTypePropertyInfo = T.Text type AttrLabel DOMHTMLUListElementTypePropertyInfo = "DOMHTMLUListElement::type" attrGet _ = getDOMHTMLUListElementType attrSet _ = setDOMHTMLUListElementType attrConstruct _ = constructDOMHTMLUListElementType type instance AttributeList DOMHTMLUListElement = '[ '("access-key", DOMHTMLElementAccessKeyPropertyInfo), '("attributes", DOMElementAttributesPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("child-element-count", DOMElementChildElementCountPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("children", DOMHTMLElementChildrenPropertyInfo), '("class-list", DOMElementClassListPropertyInfo), '("class-name", DOMElementClassNamePropertyInfo), '("client-height", DOMElementClientHeightPropertyInfo), '("client-left", DOMElementClientLeftPropertyInfo), '("client-top", DOMElementClientTopPropertyInfo), '("client-width", DOMElementClientWidthPropertyInfo), '("compact", DOMHTMLUListElementCompactPropertyInfo), '("content-editable", DOMHTMLElementContentEditablePropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("dir", DOMHTMLElementDirPropertyInfo), '("draggable", DOMHTMLElementDraggablePropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("first-element-child", DOMElementFirstElementChildPropertyInfo), '("hidden", DOMHTMLElementHiddenPropertyInfo), '("id", DOMElementIdPropertyInfo), '("inner-html", DOMHTMLElementInnerHtmlPropertyInfo), '("inner-text", DOMHTMLElementInnerTextPropertyInfo), '("is-content-editable", DOMHTMLElementIsContentEditablePropertyInfo), '("lang", DOMHTMLElementLangPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-element-child", DOMElementLastElementChildPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-element-sibling", DOMElementNextElementSiblingPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("offset-height", DOMElementOffsetHeightPropertyInfo), '("offset-left", DOMElementOffsetLeftPropertyInfo), '("offset-parent", DOMElementOffsetParentPropertyInfo), '("offset-top", DOMElementOffsetTopPropertyInfo), '("offset-width", DOMElementOffsetWidthPropertyInfo), '("outer-html", DOMHTMLElementOuterHtmlPropertyInfo), '("outer-text", DOMHTMLElementOuterTextPropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-element-sibling", DOMElementPreviousElementSiblingPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("scroll-height", DOMElementScrollHeightPropertyInfo), '("scroll-left", DOMElementScrollLeftPropertyInfo), '("scroll-top", DOMElementScrollTopPropertyInfo), '("scroll-width", DOMElementScrollWidthPropertyInfo), '("spellcheck", DOMHTMLElementSpellcheckPropertyInfo), '("style", DOMElementStylePropertyInfo), '("tab-index", DOMHTMLElementTabIndexPropertyInfo), '("tag-name", DOMElementTagNamePropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("title", DOMHTMLElementTitlePropertyInfo), '("translate", DOMHTMLElementTranslatePropertyInfo), '("type", DOMHTMLUListElementTypePropertyInfo), '("webkit-region-overset", DOMElementWebkitRegionOversetPropertyInfo), '("webkitdropzone", DOMHTMLElementWebkitdropzonePropertyInfo)] -- VVV Prop "height" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLVideoElementHeight :: (MonadIO m, DOMHTMLVideoElementK o) => o -> m Word64 getDOMHTMLVideoElementHeight obj = liftIO $ getObjectPropertyUInt64 obj "height" setDOMHTMLVideoElementHeight :: (MonadIO m, DOMHTMLVideoElementK o) => o -> Word64 -> m () setDOMHTMLVideoElementHeight obj val = liftIO $ setObjectPropertyUInt64 obj "height" val constructDOMHTMLVideoElementHeight :: Word64 -> IO ([Char], GValue) constructDOMHTMLVideoElementHeight val = constructObjectPropertyUInt64 "height" val data DOMHTMLVideoElementHeightPropertyInfo instance AttrInfo DOMHTMLVideoElementHeightPropertyInfo where type AttrAllowedOps DOMHTMLVideoElementHeightPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLVideoElementHeightPropertyInfo = (~) Word64 type AttrBaseTypeConstraint DOMHTMLVideoElementHeightPropertyInfo = DOMHTMLVideoElementK type AttrGetType DOMHTMLVideoElementHeightPropertyInfo = Word64 type AttrLabel DOMHTMLVideoElementHeightPropertyInfo = "DOMHTMLVideoElement::height" attrGet _ = getDOMHTMLVideoElementHeight attrSet _ = setDOMHTMLVideoElementHeight attrConstruct _ = constructDOMHTMLVideoElementHeight -- VVV Prop "poster" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLVideoElementPoster :: (MonadIO m, DOMHTMLVideoElementK o) => o -> m T.Text getDOMHTMLVideoElementPoster obj = liftIO $ getObjectPropertyString obj "poster" setDOMHTMLVideoElementPoster :: (MonadIO m, DOMHTMLVideoElementK o) => o -> T.Text -> m () setDOMHTMLVideoElementPoster obj val = liftIO $ setObjectPropertyString obj "poster" val constructDOMHTMLVideoElementPoster :: T.Text -> IO ([Char], GValue) constructDOMHTMLVideoElementPoster val = constructObjectPropertyString "poster" val data DOMHTMLVideoElementPosterPropertyInfo instance AttrInfo DOMHTMLVideoElementPosterPropertyInfo where type AttrAllowedOps DOMHTMLVideoElementPosterPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLVideoElementPosterPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMHTMLVideoElementPosterPropertyInfo = DOMHTMLVideoElementK type AttrGetType DOMHTMLVideoElementPosterPropertyInfo = T.Text type AttrLabel DOMHTMLVideoElementPosterPropertyInfo = "DOMHTMLVideoElement::poster" attrGet _ = getDOMHTMLVideoElementPoster attrSet _ = setDOMHTMLVideoElementPoster attrConstruct _ = constructDOMHTMLVideoElementPoster -- VVV Prop "video-height" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMHTMLVideoElementVideoHeight :: (MonadIO m, DOMHTMLVideoElementK o) => o -> m Word64 getDOMHTMLVideoElementVideoHeight obj = liftIO $ getObjectPropertyUInt64 obj "video-height" data DOMHTMLVideoElementVideoHeightPropertyInfo instance AttrInfo DOMHTMLVideoElementVideoHeightPropertyInfo where type AttrAllowedOps DOMHTMLVideoElementVideoHeightPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLVideoElementVideoHeightPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLVideoElementVideoHeightPropertyInfo = DOMHTMLVideoElementK type AttrGetType DOMHTMLVideoElementVideoHeightPropertyInfo = Word64 type AttrLabel DOMHTMLVideoElementVideoHeightPropertyInfo = "DOMHTMLVideoElement::video-height" attrGet _ = getDOMHTMLVideoElementVideoHeight attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "video-width" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMHTMLVideoElementVideoWidth :: (MonadIO m, DOMHTMLVideoElementK o) => o -> m Word64 getDOMHTMLVideoElementVideoWidth obj = liftIO $ getObjectPropertyUInt64 obj "video-width" data DOMHTMLVideoElementVideoWidthPropertyInfo instance AttrInfo DOMHTMLVideoElementVideoWidthPropertyInfo where type AttrAllowedOps DOMHTMLVideoElementVideoWidthPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLVideoElementVideoWidthPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLVideoElementVideoWidthPropertyInfo = DOMHTMLVideoElementK type AttrGetType DOMHTMLVideoElementVideoWidthPropertyInfo = Word64 type AttrLabel DOMHTMLVideoElementVideoWidthPropertyInfo = "DOMHTMLVideoElement::video-width" attrGet _ = getDOMHTMLVideoElementVideoWidth attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "webkit-decoded-frame-count" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMHTMLVideoElementWebkitDecodedFrameCount :: (MonadIO m, DOMHTMLVideoElementK o) => o -> m Word64 getDOMHTMLVideoElementWebkitDecodedFrameCount obj = liftIO $ getObjectPropertyUInt64 obj "webkit-decoded-frame-count" data DOMHTMLVideoElementWebkitDecodedFrameCountPropertyInfo instance AttrInfo DOMHTMLVideoElementWebkitDecodedFrameCountPropertyInfo where type AttrAllowedOps DOMHTMLVideoElementWebkitDecodedFrameCountPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLVideoElementWebkitDecodedFrameCountPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLVideoElementWebkitDecodedFrameCountPropertyInfo = DOMHTMLVideoElementK type AttrGetType DOMHTMLVideoElementWebkitDecodedFrameCountPropertyInfo = Word64 type AttrLabel DOMHTMLVideoElementWebkitDecodedFrameCountPropertyInfo = "DOMHTMLVideoElement::webkit-decoded-frame-count" attrGet _ = getDOMHTMLVideoElementWebkitDecodedFrameCount attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "webkit-displaying-fullscreen" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMHTMLVideoElementWebkitDisplayingFullscreen :: (MonadIO m, DOMHTMLVideoElementK o) => o -> m Bool getDOMHTMLVideoElementWebkitDisplayingFullscreen obj = liftIO $ getObjectPropertyBool obj "webkit-displaying-fullscreen" data DOMHTMLVideoElementWebkitDisplayingFullscreenPropertyInfo instance AttrInfo DOMHTMLVideoElementWebkitDisplayingFullscreenPropertyInfo where type AttrAllowedOps DOMHTMLVideoElementWebkitDisplayingFullscreenPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLVideoElementWebkitDisplayingFullscreenPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLVideoElementWebkitDisplayingFullscreenPropertyInfo = DOMHTMLVideoElementK type AttrGetType DOMHTMLVideoElementWebkitDisplayingFullscreenPropertyInfo = Bool type AttrLabel DOMHTMLVideoElementWebkitDisplayingFullscreenPropertyInfo = "DOMHTMLVideoElement::webkit-displaying-fullscreen" attrGet _ = getDOMHTMLVideoElementWebkitDisplayingFullscreen attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "webkit-dropped-frame-count" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMHTMLVideoElementWebkitDroppedFrameCount :: (MonadIO m, DOMHTMLVideoElementK o) => o -> m Word64 getDOMHTMLVideoElementWebkitDroppedFrameCount obj = liftIO $ getObjectPropertyUInt64 obj "webkit-dropped-frame-count" data DOMHTMLVideoElementWebkitDroppedFrameCountPropertyInfo instance AttrInfo DOMHTMLVideoElementWebkitDroppedFrameCountPropertyInfo where type AttrAllowedOps DOMHTMLVideoElementWebkitDroppedFrameCountPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLVideoElementWebkitDroppedFrameCountPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLVideoElementWebkitDroppedFrameCountPropertyInfo = DOMHTMLVideoElementK type AttrGetType DOMHTMLVideoElementWebkitDroppedFrameCountPropertyInfo = Word64 type AttrLabel DOMHTMLVideoElementWebkitDroppedFrameCountPropertyInfo = "DOMHTMLVideoElement::webkit-dropped-frame-count" attrGet _ = getDOMHTMLVideoElementWebkitDroppedFrameCount attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "webkit-supports-fullscreen" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMHTMLVideoElementWebkitSupportsFullscreen :: (MonadIO m, DOMHTMLVideoElementK o) => o -> m Bool getDOMHTMLVideoElementWebkitSupportsFullscreen obj = liftIO $ getObjectPropertyBool obj "webkit-supports-fullscreen" data DOMHTMLVideoElementWebkitSupportsFullscreenPropertyInfo instance AttrInfo DOMHTMLVideoElementWebkitSupportsFullscreenPropertyInfo where type AttrAllowedOps DOMHTMLVideoElementWebkitSupportsFullscreenPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHTMLVideoElementWebkitSupportsFullscreenPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHTMLVideoElementWebkitSupportsFullscreenPropertyInfo = DOMHTMLVideoElementK type AttrGetType DOMHTMLVideoElementWebkitSupportsFullscreenPropertyInfo = Bool type AttrLabel DOMHTMLVideoElementWebkitSupportsFullscreenPropertyInfo = "DOMHTMLVideoElement::webkit-supports-fullscreen" attrGet _ = getDOMHTMLVideoElementWebkitSupportsFullscreen attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "webkit-wireless-video-playback-disabled" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLVideoElementWebkitWirelessVideoPlaybackDisabled :: (MonadIO m, DOMHTMLVideoElementK o) => o -> m Bool getDOMHTMLVideoElementWebkitWirelessVideoPlaybackDisabled obj = liftIO $ getObjectPropertyBool obj "webkit-wireless-video-playback-disabled" setDOMHTMLVideoElementWebkitWirelessVideoPlaybackDisabled :: (MonadIO m, DOMHTMLVideoElementK o) => o -> Bool -> m () setDOMHTMLVideoElementWebkitWirelessVideoPlaybackDisabled obj val = liftIO $ setObjectPropertyBool obj "webkit-wireless-video-playback-disabled" val constructDOMHTMLVideoElementWebkitWirelessVideoPlaybackDisabled :: Bool -> IO ([Char], GValue) constructDOMHTMLVideoElementWebkitWirelessVideoPlaybackDisabled val = constructObjectPropertyBool "webkit-wireless-video-playback-disabled" val data DOMHTMLVideoElementWebkitWirelessVideoPlaybackDisabledPropertyInfo instance AttrInfo DOMHTMLVideoElementWebkitWirelessVideoPlaybackDisabledPropertyInfo where type AttrAllowedOps DOMHTMLVideoElementWebkitWirelessVideoPlaybackDisabledPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLVideoElementWebkitWirelessVideoPlaybackDisabledPropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMHTMLVideoElementWebkitWirelessVideoPlaybackDisabledPropertyInfo = DOMHTMLVideoElementK type AttrGetType DOMHTMLVideoElementWebkitWirelessVideoPlaybackDisabledPropertyInfo = Bool type AttrLabel DOMHTMLVideoElementWebkitWirelessVideoPlaybackDisabledPropertyInfo = "DOMHTMLVideoElement::webkit-wireless-video-playback-disabled" attrGet _ = getDOMHTMLVideoElementWebkitWirelessVideoPlaybackDisabled attrSet _ = setDOMHTMLVideoElementWebkitWirelessVideoPlaybackDisabled attrConstruct _ = constructDOMHTMLVideoElementWebkitWirelessVideoPlaybackDisabled -- VVV Prop "width" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable,PropertyWritable] getDOMHTMLVideoElementWidth :: (MonadIO m, DOMHTMLVideoElementK o) => o -> m Word64 getDOMHTMLVideoElementWidth obj = liftIO $ getObjectPropertyUInt64 obj "width" setDOMHTMLVideoElementWidth :: (MonadIO m, DOMHTMLVideoElementK o) => o -> Word64 -> m () setDOMHTMLVideoElementWidth obj val = liftIO $ setObjectPropertyUInt64 obj "width" val constructDOMHTMLVideoElementWidth :: Word64 -> IO ([Char], GValue) constructDOMHTMLVideoElementWidth val = constructObjectPropertyUInt64 "width" val data DOMHTMLVideoElementWidthPropertyInfo instance AttrInfo DOMHTMLVideoElementWidthPropertyInfo where type AttrAllowedOps DOMHTMLVideoElementWidthPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMHTMLVideoElementWidthPropertyInfo = (~) Word64 type AttrBaseTypeConstraint DOMHTMLVideoElementWidthPropertyInfo = DOMHTMLVideoElementK type AttrGetType DOMHTMLVideoElementWidthPropertyInfo = Word64 type AttrLabel DOMHTMLVideoElementWidthPropertyInfo = "DOMHTMLVideoElement::width" attrGet _ = getDOMHTMLVideoElementWidth attrSet _ = setDOMHTMLVideoElementWidth attrConstruct _ = constructDOMHTMLVideoElementWidth type instance AttributeList DOMHTMLVideoElement = '[ '("access-key", DOMHTMLElementAccessKeyPropertyInfo), '("attributes", DOMElementAttributesPropertyInfo), '("audio-tracks", DOMHTMLMediaElementAudioTracksPropertyInfo), '("autoplay", DOMHTMLMediaElementAutoplayPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("buffered", DOMHTMLMediaElementBufferedPropertyInfo), '("child-element-count", DOMElementChildElementCountPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("children", DOMHTMLElementChildrenPropertyInfo), '("class-list", DOMElementClassListPropertyInfo), '("class-name", DOMElementClassNamePropertyInfo), '("client-height", DOMElementClientHeightPropertyInfo), '("client-left", DOMElementClientLeftPropertyInfo), '("client-top", DOMElementClientTopPropertyInfo), '("client-width", DOMElementClientWidthPropertyInfo), '("content-editable", DOMHTMLElementContentEditablePropertyInfo), '("controller", DOMHTMLMediaElementControllerPropertyInfo), '("controls", DOMHTMLMediaElementControlsPropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("current-src", DOMHTMLMediaElementCurrentSrcPropertyInfo), '("current-time", DOMHTMLMediaElementCurrentTimePropertyInfo), '("default-muted", DOMHTMLMediaElementDefaultMutedPropertyInfo), '("default-playback-rate", DOMHTMLMediaElementDefaultPlaybackRatePropertyInfo), '("dir", DOMHTMLElementDirPropertyInfo), '("draggable", DOMHTMLElementDraggablePropertyInfo), '("duration", DOMHTMLMediaElementDurationPropertyInfo), '("ended", DOMHTMLMediaElementEndedPropertyInfo), '("error", DOMHTMLMediaElementErrorPropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("first-element-child", DOMElementFirstElementChildPropertyInfo), '("height", DOMHTMLVideoElementHeightPropertyInfo), '("hidden", DOMHTMLElementHiddenPropertyInfo), '("id", DOMElementIdPropertyInfo), '("inner-html", DOMHTMLElementInnerHtmlPropertyInfo), '("inner-text", DOMHTMLElementInnerTextPropertyInfo), '("is-content-editable", DOMHTMLElementIsContentEditablePropertyInfo), '("lang", DOMHTMLElementLangPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-element-child", DOMElementLastElementChildPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("loop", DOMHTMLMediaElementLoopPropertyInfo), '("media-group", DOMHTMLMediaElementMediaGroupPropertyInfo), '("muted", DOMHTMLMediaElementMutedPropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("network-state", DOMHTMLMediaElementNetworkStatePropertyInfo), '("next-element-sibling", DOMElementNextElementSiblingPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("offset-height", DOMElementOffsetHeightPropertyInfo), '("offset-left", DOMElementOffsetLeftPropertyInfo), '("offset-parent", DOMElementOffsetParentPropertyInfo), '("offset-top", DOMElementOffsetTopPropertyInfo), '("offset-width", DOMElementOffsetWidthPropertyInfo), '("outer-html", DOMHTMLElementOuterHtmlPropertyInfo), '("outer-text", DOMHTMLElementOuterTextPropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("paused", DOMHTMLMediaElementPausedPropertyInfo), '("playback-rate", DOMHTMLMediaElementPlaybackRatePropertyInfo), '("played", DOMHTMLMediaElementPlayedPropertyInfo), '("poster", DOMHTMLVideoElementPosterPropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("preload", DOMHTMLMediaElementPreloadPropertyInfo), '("previous-element-sibling", DOMElementPreviousElementSiblingPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("ready-state", DOMHTMLMediaElementReadyStatePropertyInfo), '("scroll-height", DOMElementScrollHeightPropertyInfo), '("scroll-left", DOMElementScrollLeftPropertyInfo), '("scroll-top", DOMElementScrollTopPropertyInfo), '("scroll-width", DOMElementScrollWidthPropertyInfo), '("seekable", DOMHTMLMediaElementSeekablePropertyInfo), '("seeking", DOMHTMLMediaElementSeekingPropertyInfo), '("spellcheck", DOMHTMLElementSpellcheckPropertyInfo), '("src", DOMHTMLMediaElementSrcPropertyInfo), '("style", DOMElementStylePropertyInfo), '("tab-index", DOMHTMLElementTabIndexPropertyInfo), '("tag-name", DOMElementTagNamePropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("text-tracks", DOMHTMLMediaElementTextTracksPropertyInfo), '("title", DOMHTMLElementTitlePropertyInfo), '("translate", DOMHTMLElementTranslatePropertyInfo), '("video-height", DOMHTMLVideoElementVideoHeightPropertyInfo), '("video-tracks", DOMHTMLMediaElementVideoTracksPropertyInfo), '("video-width", DOMHTMLVideoElementVideoWidthPropertyInfo), '("volume", DOMHTMLMediaElementVolumePropertyInfo), '("webkit-audio-decoded-byte-count", DOMHTMLMediaElementWebkitAudioDecodedByteCountPropertyInfo), '("webkit-closed-captions-visible", DOMHTMLMediaElementWebkitClosedCaptionsVisiblePropertyInfo), '("webkit-current-playback-target-is-wireless", DOMHTMLMediaElementWebkitCurrentPlaybackTargetIsWirelessPropertyInfo), '("webkit-decoded-frame-count", DOMHTMLVideoElementWebkitDecodedFrameCountPropertyInfo), '("webkit-displaying-fullscreen", DOMHTMLVideoElementWebkitDisplayingFullscreenPropertyInfo), '("webkit-dropped-frame-count", DOMHTMLVideoElementWebkitDroppedFrameCountPropertyInfo), '("webkit-has-closed-captions", DOMHTMLMediaElementWebkitHasClosedCaptionsPropertyInfo), '("webkit-preserves-pitch", DOMHTMLMediaElementWebkitPreservesPitchPropertyInfo), '("webkit-region-overset", DOMElementWebkitRegionOversetPropertyInfo), '("webkit-supports-fullscreen", DOMHTMLVideoElementWebkitSupportsFullscreenPropertyInfo), '("webkit-video-decoded-byte-count", DOMHTMLMediaElementWebkitVideoDecodedByteCountPropertyInfo), '("webkit-wireless-video-playback-disabled", DOMHTMLVideoElementWebkitWirelessVideoPlaybackDisabledPropertyInfo), '("webkitdropzone", DOMHTMLElementWebkitdropzonePropertyInfo), '("width", DOMHTMLVideoElementWidthPropertyInfo)] -- VVV Prop "length" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMHistoryLength :: (MonadIO m, DOMHistoryK o) => o -> m Word64 getDOMHistoryLength obj = liftIO $ getObjectPropertyUInt64 obj "length" data DOMHistoryLengthPropertyInfo instance AttrInfo DOMHistoryLengthPropertyInfo where type AttrAllowedOps DOMHistoryLengthPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMHistoryLengthPropertyInfo = (~) () type AttrBaseTypeConstraint DOMHistoryLengthPropertyInfo = DOMHistoryK type AttrGetType DOMHistoryLengthPropertyInfo = Word64 type AttrLabel DOMHistoryLengthPropertyInfo = "DOMHistory::length" attrGet _ = getDOMHistoryLength attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMHistory = '[ '("core-object", DOMObjectCoreObjectPropertyInfo), '("length", DOMHistoryLengthPropertyInfo)] -- VVV Prop "alt-graph-key" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMKeyboardEventAltGraphKey :: (MonadIO m, DOMKeyboardEventK o) => o -> m Bool getDOMKeyboardEventAltGraphKey obj = liftIO $ getObjectPropertyBool obj "alt-graph-key" data DOMKeyboardEventAltGraphKeyPropertyInfo instance AttrInfo DOMKeyboardEventAltGraphKeyPropertyInfo where type AttrAllowedOps DOMKeyboardEventAltGraphKeyPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMKeyboardEventAltGraphKeyPropertyInfo = (~) () type AttrBaseTypeConstraint DOMKeyboardEventAltGraphKeyPropertyInfo = DOMKeyboardEventK type AttrGetType DOMKeyboardEventAltGraphKeyPropertyInfo = Bool type AttrLabel DOMKeyboardEventAltGraphKeyPropertyInfo = "DOMKeyboardEvent::alt-graph-key" attrGet _ = getDOMKeyboardEventAltGraphKey attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "alt-key" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMKeyboardEventAltKey :: (MonadIO m, DOMKeyboardEventK o) => o -> m Bool getDOMKeyboardEventAltKey obj = liftIO $ getObjectPropertyBool obj "alt-key" data DOMKeyboardEventAltKeyPropertyInfo instance AttrInfo DOMKeyboardEventAltKeyPropertyInfo where type AttrAllowedOps DOMKeyboardEventAltKeyPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMKeyboardEventAltKeyPropertyInfo = (~) () type AttrBaseTypeConstraint DOMKeyboardEventAltKeyPropertyInfo = DOMKeyboardEventK type AttrGetType DOMKeyboardEventAltKeyPropertyInfo = Bool type AttrLabel DOMKeyboardEventAltKeyPropertyInfo = "DOMKeyboardEvent::alt-key" attrGet _ = getDOMKeyboardEventAltKey attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "ctrl-key" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMKeyboardEventCtrlKey :: (MonadIO m, DOMKeyboardEventK o) => o -> m Bool getDOMKeyboardEventCtrlKey obj = liftIO $ getObjectPropertyBool obj "ctrl-key" data DOMKeyboardEventCtrlKeyPropertyInfo instance AttrInfo DOMKeyboardEventCtrlKeyPropertyInfo where type AttrAllowedOps DOMKeyboardEventCtrlKeyPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMKeyboardEventCtrlKeyPropertyInfo = (~) () type AttrBaseTypeConstraint DOMKeyboardEventCtrlKeyPropertyInfo = DOMKeyboardEventK type AttrGetType DOMKeyboardEventCtrlKeyPropertyInfo = Bool type AttrLabel DOMKeyboardEventCtrlKeyPropertyInfo = "DOMKeyboardEvent::ctrl-key" attrGet _ = getDOMKeyboardEventCtrlKey attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "key-identifier" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMKeyboardEventKeyIdentifier :: (MonadIO m, DOMKeyboardEventK o) => o -> m T.Text getDOMKeyboardEventKeyIdentifier obj = liftIO $ getObjectPropertyString obj "key-identifier" data DOMKeyboardEventKeyIdentifierPropertyInfo instance AttrInfo DOMKeyboardEventKeyIdentifierPropertyInfo where type AttrAllowedOps DOMKeyboardEventKeyIdentifierPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMKeyboardEventKeyIdentifierPropertyInfo = (~) () type AttrBaseTypeConstraint DOMKeyboardEventKeyIdentifierPropertyInfo = DOMKeyboardEventK type AttrGetType DOMKeyboardEventKeyIdentifierPropertyInfo = T.Text type AttrLabel DOMKeyboardEventKeyIdentifierPropertyInfo = "DOMKeyboardEvent::key-identifier" attrGet _ = getDOMKeyboardEventKeyIdentifier attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "key-location" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMKeyboardEventKeyLocation :: (MonadIO m, DOMKeyboardEventK o) => o -> m Word64 getDOMKeyboardEventKeyLocation obj = liftIO $ getObjectPropertyUInt64 obj "key-location" data DOMKeyboardEventKeyLocationPropertyInfo instance AttrInfo DOMKeyboardEventKeyLocationPropertyInfo where type AttrAllowedOps DOMKeyboardEventKeyLocationPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMKeyboardEventKeyLocationPropertyInfo = (~) () type AttrBaseTypeConstraint DOMKeyboardEventKeyLocationPropertyInfo = DOMKeyboardEventK type AttrGetType DOMKeyboardEventKeyLocationPropertyInfo = Word64 type AttrLabel DOMKeyboardEventKeyLocationPropertyInfo = "DOMKeyboardEvent::key-location" attrGet _ = getDOMKeyboardEventKeyLocation attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "meta-key" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMKeyboardEventMetaKey :: (MonadIO m, DOMKeyboardEventK o) => o -> m Bool getDOMKeyboardEventMetaKey obj = liftIO $ getObjectPropertyBool obj "meta-key" data DOMKeyboardEventMetaKeyPropertyInfo instance AttrInfo DOMKeyboardEventMetaKeyPropertyInfo where type AttrAllowedOps DOMKeyboardEventMetaKeyPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMKeyboardEventMetaKeyPropertyInfo = (~) () type AttrBaseTypeConstraint DOMKeyboardEventMetaKeyPropertyInfo = DOMKeyboardEventK type AttrGetType DOMKeyboardEventMetaKeyPropertyInfo = Bool type AttrLabel DOMKeyboardEventMetaKeyPropertyInfo = "DOMKeyboardEvent::meta-key" attrGet _ = getDOMKeyboardEventMetaKey attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "shift-key" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMKeyboardEventShiftKey :: (MonadIO m, DOMKeyboardEventK o) => o -> m Bool getDOMKeyboardEventShiftKey obj = liftIO $ getObjectPropertyBool obj "shift-key" data DOMKeyboardEventShiftKeyPropertyInfo instance AttrInfo DOMKeyboardEventShiftKeyPropertyInfo where type AttrAllowedOps DOMKeyboardEventShiftKeyPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMKeyboardEventShiftKeyPropertyInfo = (~) () type AttrBaseTypeConstraint DOMKeyboardEventShiftKeyPropertyInfo = DOMKeyboardEventK type AttrGetType DOMKeyboardEventShiftKeyPropertyInfo = Bool type AttrLabel DOMKeyboardEventShiftKeyPropertyInfo = "DOMKeyboardEvent::shift-key" attrGet _ = getDOMKeyboardEventShiftKey attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMKeyboardEvent = '[ '("alt-graph-key", DOMKeyboardEventAltGraphKeyPropertyInfo), '("alt-key", DOMKeyboardEventAltKeyPropertyInfo), '("bubbles", DOMEventBubblesPropertyInfo), '("cancel-bubble", DOMEventCancelBubblePropertyInfo), '("cancelable", DOMEventCancelablePropertyInfo), '("char-code", DOMUIEventCharCodePropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("ctrl-key", DOMKeyboardEventCtrlKeyPropertyInfo), '("current-target", DOMEventCurrentTargetPropertyInfo), '("default-prevented", DOMEventDefaultPreventedPropertyInfo), '("detail", DOMUIEventDetailPropertyInfo), '("event-phase", DOMEventEventPhasePropertyInfo), '("key-code", DOMUIEventKeyCodePropertyInfo), '("key-identifier", DOMKeyboardEventKeyIdentifierPropertyInfo), '("key-location", DOMKeyboardEventKeyLocationPropertyInfo), '("layer-x", DOMUIEventLayerXPropertyInfo), '("layer-y", DOMUIEventLayerYPropertyInfo), '("meta-key", DOMKeyboardEventMetaKeyPropertyInfo), '("page-x", DOMUIEventPageXPropertyInfo), '("page-y", DOMUIEventPageYPropertyInfo), '("return-value", DOMEventReturnValuePropertyInfo), '("shift-key", DOMKeyboardEventShiftKeyPropertyInfo), '("src-element", DOMEventSrcElementPropertyInfo), '("target", DOMEventTargetPropertyInfo), '("time-stamp", DOMEventTimeStampPropertyInfo), '("type", DOMEventTypePropertyInfo), '("view", DOMUIEventViewPropertyInfo), '("which", DOMUIEventWhichPropertyInfo)] -- VVV Prop "ancestor-origins" -- Type: TInterface "WebKit" "DOMDOMStringList" -- Flags: [PropertyReadable] getDOMLocationAncestorOrigins :: (MonadIO m, DOMLocationK o) => o -> m DOMDOMStringList getDOMLocationAncestorOrigins obj = liftIO $ getObjectPropertyObject obj "ancestor-origins" DOMDOMStringList data DOMLocationAncestorOriginsPropertyInfo instance AttrInfo DOMLocationAncestorOriginsPropertyInfo where type AttrAllowedOps DOMLocationAncestorOriginsPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMLocationAncestorOriginsPropertyInfo = (~) () type AttrBaseTypeConstraint DOMLocationAncestorOriginsPropertyInfo = DOMLocationK type AttrGetType DOMLocationAncestorOriginsPropertyInfo = DOMDOMStringList type AttrLabel DOMLocationAncestorOriginsPropertyInfo = "DOMLocation::ancestor-origins" attrGet _ = getDOMLocationAncestorOrigins attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "hash" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMLocationHash :: (MonadIO m, DOMLocationK o) => o -> m T.Text getDOMLocationHash obj = liftIO $ getObjectPropertyString obj "hash" data DOMLocationHashPropertyInfo instance AttrInfo DOMLocationHashPropertyInfo where type AttrAllowedOps DOMLocationHashPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMLocationHashPropertyInfo = (~) () type AttrBaseTypeConstraint DOMLocationHashPropertyInfo = DOMLocationK type AttrGetType DOMLocationHashPropertyInfo = T.Text type AttrLabel DOMLocationHashPropertyInfo = "DOMLocation::hash" attrGet _ = getDOMLocationHash attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "host" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMLocationHost :: (MonadIO m, DOMLocationK o) => o -> m T.Text getDOMLocationHost obj = liftIO $ getObjectPropertyString obj "host" data DOMLocationHostPropertyInfo instance AttrInfo DOMLocationHostPropertyInfo where type AttrAllowedOps DOMLocationHostPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMLocationHostPropertyInfo = (~) () type AttrBaseTypeConstraint DOMLocationHostPropertyInfo = DOMLocationK type AttrGetType DOMLocationHostPropertyInfo = T.Text type AttrLabel DOMLocationHostPropertyInfo = "DOMLocation::host" attrGet _ = getDOMLocationHost attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "hostname" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMLocationHostname :: (MonadIO m, DOMLocationK o) => o -> m T.Text getDOMLocationHostname obj = liftIO $ getObjectPropertyString obj "hostname" data DOMLocationHostnamePropertyInfo instance AttrInfo DOMLocationHostnamePropertyInfo where type AttrAllowedOps DOMLocationHostnamePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMLocationHostnamePropertyInfo = (~) () type AttrBaseTypeConstraint DOMLocationHostnamePropertyInfo = DOMLocationK type AttrGetType DOMLocationHostnamePropertyInfo = T.Text type AttrLabel DOMLocationHostnamePropertyInfo = "DOMLocation::hostname" attrGet _ = getDOMLocationHostname attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "href" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMLocationHref :: (MonadIO m, DOMLocationK o) => o -> m T.Text getDOMLocationHref obj = liftIO $ getObjectPropertyString obj "href" data DOMLocationHrefPropertyInfo instance AttrInfo DOMLocationHrefPropertyInfo where type AttrAllowedOps DOMLocationHrefPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMLocationHrefPropertyInfo = (~) () type AttrBaseTypeConstraint DOMLocationHrefPropertyInfo = DOMLocationK type AttrGetType DOMLocationHrefPropertyInfo = T.Text type AttrLabel DOMLocationHrefPropertyInfo = "DOMLocation::href" attrGet _ = getDOMLocationHref attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "origin" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMLocationOrigin :: (MonadIO m, DOMLocationK o) => o -> m T.Text getDOMLocationOrigin obj = liftIO $ getObjectPropertyString obj "origin" data DOMLocationOriginPropertyInfo instance AttrInfo DOMLocationOriginPropertyInfo where type AttrAllowedOps DOMLocationOriginPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMLocationOriginPropertyInfo = (~) () type AttrBaseTypeConstraint DOMLocationOriginPropertyInfo = DOMLocationK type AttrGetType DOMLocationOriginPropertyInfo = T.Text type AttrLabel DOMLocationOriginPropertyInfo = "DOMLocation::origin" attrGet _ = getDOMLocationOrigin attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "pathname" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMLocationPathname :: (MonadIO m, DOMLocationK o) => o -> m T.Text getDOMLocationPathname obj = liftIO $ getObjectPropertyString obj "pathname" data DOMLocationPathnamePropertyInfo instance AttrInfo DOMLocationPathnamePropertyInfo where type AttrAllowedOps DOMLocationPathnamePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMLocationPathnamePropertyInfo = (~) () type AttrBaseTypeConstraint DOMLocationPathnamePropertyInfo = DOMLocationK type AttrGetType DOMLocationPathnamePropertyInfo = T.Text type AttrLabel DOMLocationPathnamePropertyInfo = "DOMLocation::pathname" attrGet _ = getDOMLocationPathname attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "port" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMLocationPort :: (MonadIO m, DOMLocationK o) => o -> m T.Text getDOMLocationPort obj = liftIO $ getObjectPropertyString obj "port" data DOMLocationPortPropertyInfo instance AttrInfo DOMLocationPortPropertyInfo where type AttrAllowedOps DOMLocationPortPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMLocationPortPropertyInfo = (~) () type AttrBaseTypeConstraint DOMLocationPortPropertyInfo = DOMLocationK type AttrGetType DOMLocationPortPropertyInfo = T.Text type AttrLabel DOMLocationPortPropertyInfo = "DOMLocation::port" attrGet _ = getDOMLocationPort attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "protocol" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMLocationProtocol :: (MonadIO m, DOMLocationK o) => o -> m T.Text getDOMLocationProtocol obj = liftIO $ getObjectPropertyString obj "protocol" data DOMLocationProtocolPropertyInfo instance AttrInfo DOMLocationProtocolPropertyInfo where type AttrAllowedOps DOMLocationProtocolPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMLocationProtocolPropertyInfo = (~) () type AttrBaseTypeConstraint DOMLocationProtocolPropertyInfo = DOMLocationK type AttrGetType DOMLocationProtocolPropertyInfo = T.Text type AttrLabel DOMLocationProtocolPropertyInfo = "DOMLocation::protocol" attrGet _ = getDOMLocationProtocol attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "search" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMLocationSearch :: (MonadIO m, DOMLocationK o) => o -> m T.Text getDOMLocationSearch obj = liftIO $ getObjectPropertyString obj "search" data DOMLocationSearchPropertyInfo instance AttrInfo DOMLocationSearchPropertyInfo where type AttrAllowedOps DOMLocationSearchPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMLocationSearchPropertyInfo = (~) () type AttrBaseTypeConstraint DOMLocationSearchPropertyInfo = DOMLocationK type AttrGetType DOMLocationSearchPropertyInfo = T.Text type AttrLabel DOMLocationSearchPropertyInfo = "DOMLocation::search" attrGet _ = getDOMLocationSearch attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMLocation = '[ '("ancestor-origins", DOMLocationAncestorOriginsPropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("hash", DOMLocationHashPropertyInfo), '("host", DOMLocationHostPropertyInfo), '("hostname", DOMLocationHostnamePropertyInfo), '("href", DOMLocationHrefPropertyInfo), '("origin", DOMLocationOriginPropertyInfo), '("pathname", DOMLocationPathnamePropertyInfo), '("port", DOMLocationPortPropertyInfo), '("protocol", DOMLocationProtocolPropertyInfo), '("search", DOMLocationSearchPropertyInfo)] -- VVV Prop "buffered" -- Type: TInterface "WebKit" "DOMTimeRanges" -- Flags: [PropertyReadable] getDOMMediaControllerBuffered :: (MonadIO m, DOMMediaControllerK o) => o -> m DOMTimeRanges getDOMMediaControllerBuffered obj = liftIO $ getObjectPropertyObject obj "buffered" DOMTimeRanges data DOMMediaControllerBufferedPropertyInfo instance AttrInfo DOMMediaControllerBufferedPropertyInfo where type AttrAllowedOps DOMMediaControllerBufferedPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMMediaControllerBufferedPropertyInfo = (~) () type AttrBaseTypeConstraint DOMMediaControllerBufferedPropertyInfo = DOMMediaControllerK type AttrGetType DOMMediaControllerBufferedPropertyInfo = DOMTimeRanges type AttrLabel DOMMediaControllerBufferedPropertyInfo = "DOMMediaController::buffered" attrGet _ = getDOMMediaControllerBuffered attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "current-time" -- Type: TBasicType TDouble -- Flags: [PropertyReadable,PropertyWritable] getDOMMediaControllerCurrentTime :: (MonadIO m, DOMMediaControllerK o) => o -> m Double getDOMMediaControllerCurrentTime obj = liftIO $ getObjectPropertyDouble obj "current-time" setDOMMediaControllerCurrentTime :: (MonadIO m, DOMMediaControllerK o) => o -> Double -> m () setDOMMediaControllerCurrentTime obj val = liftIO $ setObjectPropertyDouble obj "current-time" val constructDOMMediaControllerCurrentTime :: Double -> IO ([Char], GValue) constructDOMMediaControllerCurrentTime val = constructObjectPropertyDouble "current-time" val data DOMMediaControllerCurrentTimePropertyInfo instance AttrInfo DOMMediaControllerCurrentTimePropertyInfo where type AttrAllowedOps DOMMediaControllerCurrentTimePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMMediaControllerCurrentTimePropertyInfo = (~) Double type AttrBaseTypeConstraint DOMMediaControllerCurrentTimePropertyInfo = DOMMediaControllerK type AttrGetType DOMMediaControllerCurrentTimePropertyInfo = Double type AttrLabel DOMMediaControllerCurrentTimePropertyInfo = "DOMMediaController::current-time" attrGet _ = getDOMMediaControllerCurrentTime attrSet _ = setDOMMediaControllerCurrentTime attrConstruct _ = constructDOMMediaControllerCurrentTime -- VVV Prop "default-playback-rate" -- Type: TBasicType TDouble -- Flags: [PropertyReadable,PropertyWritable] getDOMMediaControllerDefaultPlaybackRate :: (MonadIO m, DOMMediaControllerK o) => o -> m Double getDOMMediaControllerDefaultPlaybackRate obj = liftIO $ getObjectPropertyDouble obj "default-playback-rate" setDOMMediaControllerDefaultPlaybackRate :: (MonadIO m, DOMMediaControllerK o) => o -> Double -> m () setDOMMediaControllerDefaultPlaybackRate obj val = liftIO $ setObjectPropertyDouble obj "default-playback-rate" val constructDOMMediaControllerDefaultPlaybackRate :: Double -> IO ([Char], GValue) constructDOMMediaControllerDefaultPlaybackRate val = constructObjectPropertyDouble "default-playback-rate" val data DOMMediaControllerDefaultPlaybackRatePropertyInfo instance AttrInfo DOMMediaControllerDefaultPlaybackRatePropertyInfo where type AttrAllowedOps DOMMediaControllerDefaultPlaybackRatePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMMediaControllerDefaultPlaybackRatePropertyInfo = (~) Double type AttrBaseTypeConstraint DOMMediaControllerDefaultPlaybackRatePropertyInfo = DOMMediaControllerK type AttrGetType DOMMediaControllerDefaultPlaybackRatePropertyInfo = Double type AttrLabel DOMMediaControllerDefaultPlaybackRatePropertyInfo = "DOMMediaController::default-playback-rate" attrGet _ = getDOMMediaControllerDefaultPlaybackRate attrSet _ = setDOMMediaControllerDefaultPlaybackRate attrConstruct _ = constructDOMMediaControllerDefaultPlaybackRate -- VVV Prop "duration" -- Type: TBasicType TDouble -- Flags: [PropertyReadable] getDOMMediaControllerDuration :: (MonadIO m, DOMMediaControllerK o) => o -> m Double getDOMMediaControllerDuration obj = liftIO $ getObjectPropertyDouble obj "duration" data DOMMediaControllerDurationPropertyInfo instance AttrInfo DOMMediaControllerDurationPropertyInfo where type AttrAllowedOps DOMMediaControllerDurationPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMMediaControllerDurationPropertyInfo = (~) () type AttrBaseTypeConstraint DOMMediaControllerDurationPropertyInfo = DOMMediaControllerK type AttrGetType DOMMediaControllerDurationPropertyInfo = Double type AttrLabel DOMMediaControllerDurationPropertyInfo = "DOMMediaController::duration" attrGet _ = getDOMMediaControllerDuration attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "muted" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMMediaControllerMuted :: (MonadIO m, DOMMediaControllerK o) => o -> m Bool getDOMMediaControllerMuted obj = liftIO $ getObjectPropertyBool obj "muted" setDOMMediaControllerMuted :: (MonadIO m, DOMMediaControllerK o) => o -> Bool -> m () setDOMMediaControllerMuted obj val = liftIO $ setObjectPropertyBool obj "muted" val constructDOMMediaControllerMuted :: Bool -> IO ([Char], GValue) constructDOMMediaControllerMuted val = constructObjectPropertyBool "muted" val data DOMMediaControllerMutedPropertyInfo instance AttrInfo DOMMediaControllerMutedPropertyInfo where type AttrAllowedOps DOMMediaControllerMutedPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMMediaControllerMutedPropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMMediaControllerMutedPropertyInfo = DOMMediaControllerK type AttrGetType DOMMediaControllerMutedPropertyInfo = Bool type AttrLabel DOMMediaControllerMutedPropertyInfo = "DOMMediaController::muted" attrGet _ = getDOMMediaControllerMuted attrSet _ = setDOMMediaControllerMuted attrConstruct _ = constructDOMMediaControllerMuted -- VVV Prop "paused" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMMediaControllerPaused :: (MonadIO m, DOMMediaControllerK o) => o -> m Bool getDOMMediaControllerPaused obj = liftIO $ getObjectPropertyBool obj "paused" data DOMMediaControllerPausedPropertyInfo instance AttrInfo DOMMediaControllerPausedPropertyInfo where type AttrAllowedOps DOMMediaControllerPausedPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMMediaControllerPausedPropertyInfo = (~) () type AttrBaseTypeConstraint DOMMediaControllerPausedPropertyInfo = DOMMediaControllerK type AttrGetType DOMMediaControllerPausedPropertyInfo = Bool type AttrLabel DOMMediaControllerPausedPropertyInfo = "DOMMediaController::paused" attrGet _ = getDOMMediaControllerPaused attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "playback-rate" -- Type: TBasicType TDouble -- Flags: [PropertyReadable,PropertyWritable] getDOMMediaControllerPlaybackRate :: (MonadIO m, DOMMediaControllerK o) => o -> m Double getDOMMediaControllerPlaybackRate obj = liftIO $ getObjectPropertyDouble obj "playback-rate" setDOMMediaControllerPlaybackRate :: (MonadIO m, DOMMediaControllerK o) => o -> Double -> m () setDOMMediaControllerPlaybackRate obj val = liftIO $ setObjectPropertyDouble obj "playback-rate" val constructDOMMediaControllerPlaybackRate :: Double -> IO ([Char], GValue) constructDOMMediaControllerPlaybackRate val = constructObjectPropertyDouble "playback-rate" val data DOMMediaControllerPlaybackRatePropertyInfo instance AttrInfo DOMMediaControllerPlaybackRatePropertyInfo where type AttrAllowedOps DOMMediaControllerPlaybackRatePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMMediaControllerPlaybackRatePropertyInfo = (~) Double type AttrBaseTypeConstraint DOMMediaControllerPlaybackRatePropertyInfo = DOMMediaControllerK type AttrGetType DOMMediaControllerPlaybackRatePropertyInfo = Double type AttrLabel DOMMediaControllerPlaybackRatePropertyInfo = "DOMMediaController::playback-rate" attrGet _ = getDOMMediaControllerPlaybackRate attrSet _ = setDOMMediaControllerPlaybackRate attrConstruct _ = constructDOMMediaControllerPlaybackRate -- VVV Prop "playback-state" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMMediaControllerPlaybackState :: (MonadIO m, DOMMediaControllerK o) => o -> m T.Text getDOMMediaControllerPlaybackState obj = liftIO $ getObjectPropertyString obj "playback-state" data DOMMediaControllerPlaybackStatePropertyInfo instance AttrInfo DOMMediaControllerPlaybackStatePropertyInfo where type AttrAllowedOps DOMMediaControllerPlaybackStatePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMMediaControllerPlaybackStatePropertyInfo = (~) () type AttrBaseTypeConstraint DOMMediaControllerPlaybackStatePropertyInfo = DOMMediaControllerK type AttrGetType DOMMediaControllerPlaybackStatePropertyInfo = T.Text type AttrLabel DOMMediaControllerPlaybackStatePropertyInfo = "DOMMediaController::playback-state" attrGet _ = getDOMMediaControllerPlaybackState attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "played" -- Type: TInterface "WebKit" "DOMTimeRanges" -- Flags: [PropertyReadable] getDOMMediaControllerPlayed :: (MonadIO m, DOMMediaControllerK o) => o -> m DOMTimeRanges getDOMMediaControllerPlayed obj = liftIO $ getObjectPropertyObject obj "played" DOMTimeRanges data DOMMediaControllerPlayedPropertyInfo instance AttrInfo DOMMediaControllerPlayedPropertyInfo where type AttrAllowedOps DOMMediaControllerPlayedPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMMediaControllerPlayedPropertyInfo = (~) () type AttrBaseTypeConstraint DOMMediaControllerPlayedPropertyInfo = DOMMediaControllerK type AttrGetType DOMMediaControllerPlayedPropertyInfo = DOMTimeRanges type AttrLabel DOMMediaControllerPlayedPropertyInfo = "DOMMediaController::played" attrGet _ = getDOMMediaControllerPlayed attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "seekable" -- Type: TInterface "WebKit" "DOMTimeRanges" -- Flags: [PropertyReadable] getDOMMediaControllerSeekable :: (MonadIO m, DOMMediaControllerK o) => o -> m DOMTimeRanges getDOMMediaControllerSeekable obj = liftIO $ getObjectPropertyObject obj "seekable" DOMTimeRanges data DOMMediaControllerSeekablePropertyInfo instance AttrInfo DOMMediaControllerSeekablePropertyInfo where type AttrAllowedOps DOMMediaControllerSeekablePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMMediaControllerSeekablePropertyInfo = (~) () type AttrBaseTypeConstraint DOMMediaControllerSeekablePropertyInfo = DOMMediaControllerK type AttrGetType DOMMediaControllerSeekablePropertyInfo = DOMTimeRanges type AttrLabel DOMMediaControllerSeekablePropertyInfo = "DOMMediaController::seekable" attrGet _ = getDOMMediaControllerSeekable attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "volume" -- Type: TBasicType TDouble -- Flags: [PropertyReadable,PropertyWritable] getDOMMediaControllerVolume :: (MonadIO m, DOMMediaControllerK o) => o -> m Double getDOMMediaControllerVolume obj = liftIO $ getObjectPropertyDouble obj "volume" setDOMMediaControllerVolume :: (MonadIO m, DOMMediaControllerK o) => o -> Double -> m () setDOMMediaControllerVolume obj val = liftIO $ setObjectPropertyDouble obj "volume" val constructDOMMediaControllerVolume :: Double -> IO ([Char], GValue) constructDOMMediaControllerVolume val = constructObjectPropertyDouble "volume" val data DOMMediaControllerVolumePropertyInfo instance AttrInfo DOMMediaControllerVolumePropertyInfo where type AttrAllowedOps DOMMediaControllerVolumePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMMediaControllerVolumePropertyInfo = (~) Double type AttrBaseTypeConstraint DOMMediaControllerVolumePropertyInfo = DOMMediaControllerK type AttrGetType DOMMediaControllerVolumePropertyInfo = Double type AttrLabel DOMMediaControllerVolumePropertyInfo = "DOMMediaController::volume" attrGet _ = getDOMMediaControllerVolume attrSet _ = setDOMMediaControllerVolume attrConstruct _ = constructDOMMediaControllerVolume type instance AttributeList DOMMediaController = '[ '("buffered", DOMMediaControllerBufferedPropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("current-time", DOMMediaControllerCurrentTimePropertyInfo), '("default-playback-rate", DOMMediaControllerDefaultPlaybackRatePropertyInfo), '("duration", DOMMediaControllerDurationPropertyInfo), '("muted", DOMMediaControllerMutedPropertyInfo), '("paused", DOMMediaControllerPausedPropertyInfo), '("playback-rate", DOMMediaControllerPlaybackRatePropertyInfo), '("playback-state", DOMMediaControllerPlaybackStatePropertyInfo), '("played", DOMMediaControllerPlayedPropertyInfo), '("seekable", DOMMediaControllerSeekablePropertyInfo), '("volume", DOMMediaControllerVolumePropertyInfo)] -- VVV Prop "code" -- Type: TBasicType TUInt32 -- Flags: [PropertyReadable] getDOMMediaErrorCode :: (MonadIO m, DOMMediaErrorK o) => o -> m Word32 getDOMMediaErrorCode obj = liftIO $ getObjectPropertyCUInt obj "code" data DOMMediaErrorCodePropertyInfo instance AttrInfo DOMMediaErrorCodePropertyInfo where type AttrAllowedOps DOMMediaErrorCodePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMMediaErrorCodePropertyInfo = (~) () type AttrBaseTypeConstraint DOMMediaErrorCodePropertyInfo = DOMMediaErrorK type AttrGetType DOMMediaErrorCodePropertyInfo = Word32 type AttrLabel DOMMediaErrorCodePropertyInfo = "DOMMediaError::code" attrGet _ = getDOMMediaErrorCode attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMMediaError = '[ '("code", DOMMediaErrorCodePropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo)] -- VVV Prop "length" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMMediaListLength :: (MonadIO m, DOMMediaListK o) => o -> m Word64 getDOMMediaListLength obj = liftIO $ getObjectPropertyUInt64 obj "length" data DOMMediaListLengthPropertyInfo instance AttrInfo DOMMediaListLengthPropertyInfo where type AttrAllowedOps DOMMediaListLengthPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMMediaListLengthPropertyInfo = (~) () type AttrBaseTypeConstraint DOMMediaListLengthPropertyInfo = DOMMediaListK type AttrGetType DOMMediaListLengthPropertyInfo = Word64 type AttrLabel DOMMediaListLengthPropertyInfo = "DOMMediaList::length" attrGet _ = getDOMMediaListLength attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "media-text" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMMediaListMediaText :: (MonadIO m, DOMMediaListK o) => o -> m T.Text getDOMMediaListMediaText obj = liftIO $ getObjectPropertyString obj "media-text" setDOMMediaListMediaText :: (MonadIO m, DOMMediaListK o) => o -> T.Text -> m () setDOMMediaListMediaText obj val = liftIO $ setObjectPropertyString obj "media-text" val constructDOMMediaListMediaText :: T.Text -> IO ([Char], GValue) constructDOMMediaListMediaText val = constructObjectPropertyString "media-text" val data DOMMediaListMediaTextPropertyInfo instance AttrInfo DOMMediaListMediaTextPropertyInfo where type AttrAllowedOps DOMMediaListMediaTextPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMMediaListMediaTextPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMMediaListMediaTextPropertyInfo = DOMMediaListK type AttrGetType DOMMediaListMediaTextPropertyInfo = T.Text type AttrLabel DOMMediaListMediaTextPropertyInfo = "DOMMediaList::media-text" attrGet _ = getDOMMediaListMediaText attrSet _ = setDOMMediaListMediaText attrConstruct _ = constructDOMMediaListMediaText type instance AttributeList DOMMediaList = '[ '("core-object", DOMObjectCoreObjectPropertyInfo), '("length", DOMMediaListLengthPropertyInfo), '("media-text", DOMMediaListMediaTextPropertyInfo)] -- VVV Prop "matches" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMMediaQueryListMatches :: (MonadIO m, DOMMediaQueryListK o) => o -> m Bool getDOMMediaQueryListMatches obj = liftIO $ getObjectPropertyBool obj "matches" data DOMMediaQueryListMatchesPropertyInfo instance AttrInfo DOMMediaQueryListMatchesPropertyInfo where type AttrAllowedOps DOMMediaQueryListMatchesPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMMediaQueryListMatchesPropertyInfo = (~) () type AttrBaseTypeConstraint DOMMediaQueryListMatchesPropertyInfo = DOMMediaQueryListK type AttrGetType DOMMediaQueryListMatchesPropertyInfo = Bool type AttrLabel DOMMediaQueryListMatchesPropertyInfo = "DOMMediaQueryList::matches" attrGet _ = getDOMMediaQueryListMatches attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "media" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMMediaQueryListMedia :: (MonadIO m, DOMMediaQueryListK o) => o -> m T.Text getDOMMediaQueryListMedia obj = liftIO $ getObjectPropertyString obj "media" data DOMMediaQueryListMediaPropertyInfo instance AttrInfo DOMMediaQueryListMediaPropertyInfo where type AttrAllowedOps DOMMediaQueryListMediaPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMMediaQueryListMediaPropertyInfo = (~) () type AttrBaseTypeConstraint DOMMediaQueryListMediaPropertyInfo = DOMMediaQueryListK type AttrGetType DOMMediaQueryListMediaPropertyInfo = T.Text type AttrLabel DOMMediaQueryListMediaPropertyInfo = "DOMMediaQueryList::media" attrGet _ = getDOMMediaQueryListMedia attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMMediaQueryList = '[ '("core-object", DOMObjectCoreObjectPropertyInfo), '("matches", DOMMediaQueryListMatchesPropertyInfo), '("media", DOMMediaQueryListMediaPropertyInfo)] -- VVV Prop "js-heap-size-limit" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMMemoryInfoJsHeapSizeLimit :: (MonadIO m, DOMMemoryInfoK o) => o -> m Word64 getDOMMemoryInfoJsHeapSizeLimit obj = liftIO $ getObjectPropertyUInt64 obj "js-heap-size-limit" data DOMMemoryInfoJsHeapSizeLimitPropertyInfo instance AttrInfo DOMMemoryInfoJsHeapSizeLimitPropertyInfo where type AttrAllowedOps DOMMemoryInfoJsHeapSizeLimitPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMMemoryInfoJsHeapSizeLimitPropertyInfo = (~) () type AttrBaseTypeConstraint DOMMemoryInfoJsHeapSizeLimitPropertyInfo = DOMMemoryInfoK type AttrGetType DOMMemoryInfoJsHeapSizeLimitPropertyInfo = Word64 type AttrLabel DOMMemoryInfoJsHeapSizeLimitPropertyInfo = "DOMMemoryInfo::js-heap-size-limit" attrGet _ = getDOMMemoryInfoJsHeapSizeLimit attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "total-js-heap-size" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMMemoryInfoTotalJsHeapSize :: (MonadIO m, DOMMemoryInfoK o) => o -> m Word64 getDOMMemoryInfoTotalJsHeapSize obj = liftIO $ getObjectPropertyUInt64 obj "total-js-heap-size" data DOMMemoryInfoTotalJsHeapSizePropertyInfo instance AttrInfo DOMMemoryInfoTotalJsHeapSizePropertyInfo where type AttrAllowedOps DOMMemoryInfoTotalJsHeapSizePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMMemoryInfoTotalJsHeapSizePropertyInfo = (~) () type AttrBaseTypeConstraint DOMMemoryInfoTotalJsHeapSizePropertyInfo = DOMMemoryInfoK type AttrGetType DOMMemoryInfoTotalJsHeapSizePropertyInfo = Word64 type AttrLabel DOMMemoryInfoTotalJsHeapSizePropertyInfo = "DOMMemoryInfo::total-js-heap-size" attrGet _ = getDOMMemoryInfoTotalJsHeapSize attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "used-js-heap-size" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMMemoryInfoUsedJsHeapSize :: (MonadIO m, DOMMemoryInfoK o) => o -> m Word64 getDOMMemoryInfoUsedJsHeapSize obj = liftIO $ getObjectPropertyUInt64 obj "used-js-heap-size" data DOMMemoryInfoUsedJsHeapSizePropertyInfo instance AttrInfo DOMMemoryInfoUsedJsHeapSizePropertyInfo where type AttrAllowedOps DOMMemoryInfoUsedJsHeapSizePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMMemoryInfoUsedJsHeapSizePropertyInfo = (~) () type AttrBaseTypeConstraint DOMMemoryInfoUsedJsHeapSizePropertyInfo = DOMMemoryInfoK type AttrGetType DOMMemoryInfoUsedJsHeapSizePropertyInfo = Word64 type AttrLabel DOMMemoryInfoUsedJsHeapSizePropertyInfo = "DOMMemoryInfo::used-js-heap-size" attrGet _ = getDOMMemoryInfoUsedJsHeapSize attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMMemoryInfo = '[ '("core-object", DOMObjectCoreObjectPropertyInfo), '("js-heap-size-limit", DOMMemoryInfoJsHeapSizeLimitPropertyInfo), '("total-js-heap-size", DOMMemoryInfoTotalJsHeapSizePropertyInfo), '("used-js-heap-size", DOMMemoryInfoUsedJsHeapSizePropertyInfo)] type instance AttributeList DOMMessagePort = '[ '("core-object", DOMObjectCoreObjectPropertyInfo)] type instance AttributeList DOMMicroDataItemValue = '[ '("core-object", DOMObjectCoreObjectPropertyInfo)] -- VVV Prop "alt-key" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMMouseEventAltKey :: (MonadIO m, DOMMouseEventK o) => o -> m Bool getDOMMouseEventAltKey obj = liftIO $ getObjectPropertyBool obj "alt-key" data DOMMouseEventAltKeyPropertyInfo instance AttrInfo DOMMouseEventAltKeyPropertyInfo where type AttrAllowedOps DOMMouseEventAltKeyPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMMouseEventAltKeyPropertyInfo = (~) () type AttrBaseTypeConstraint DOMMouseEventAltKeyPropertyInfo = DOMMouseEventK type AttrGetType DOMMouseEventAltKeyPropertyInfo = Bool type AttrLabel DOMMouseEventAltKeyPropertyInfo = "DOMMouseEvent::alt-key" attrGet _ = getDOMMouseEventAltKey attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "button" -- Type: TBasicType TUInt32 -- Flags: [PropertyReadable] getDOMMouseEventButton :: (MonadIO m, DOMMouseEventK o) => o -> m Word32 getDOMMouseEventButton obj = liftIO $ getObjectPropertyCUInt obj "button" data DOMMouseEventButtonPropertyInfo instance AttrInfo DOMMouseEventButtonPropertyInfo where type AttrAllowedOps DOMMouseEventButtonPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMMouseEventButtonPropertyInfo = (~) () type AttrBaseTypeConstraint DOMMouseEventButtonPropertyInfo = DOMMouseEventK type AttrGetType DOMMouseEventButtonPropertyInfo = Word32 type AttrLabel DOMMouseEventButtonPropertyInfo = "DOMMouseEvent::button" attrGet _ = getDOMMouseEventButton attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "client-x" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMMouseEventClientX :: (MonadIO m, DOMMouseEventK o) => o -> m Int64 getDOMMouseEventClientX obj = liftIO $ getObjectPropertyInt64 obj "client-x" data DOMMouseEventClientXPropertyInfo instance AttrInfo DOMMouseEventClientXPropertyInfo where type AttrAllowedOps DOMMouseEventClientXPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMMouseEventClientXPropertyInfo = (~) () type AttrBaseTypeConstraint DOMMouseEventClientXPropertyInfo = DOMMouseEventK type AttrGetType DOMMouseEventClientXPropertyInfo = Int64 type AttrLabel DOMMouseEventClientXPropertyInfo = "DOMMouseEvent::client-x" attrGet _ = getDOMMouseEventClientX attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "client-y" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMMouseEventClientY :: (MonadIO m, DOMMouseEventK o) => o -> m Int64 getDOMMouseEventClientY obj = liftIO $ getObjectPropertyInt64 obj "client-y" data DOMMouseEventClientYPropertyInfo instance AttrInfo DOMMouseEventClientYPropertyInfo where type AttrAllowedOps DOMMouseEventClientYPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMMouseEventClientYPropertyInfo = (~) () type AttrBaseTypeConstraint DOMMouseEventClientYPropertyInfo = DOMMouseEventK type AttrGetType DOMMouseEventClientYPropertyInfo = Int64 type AttrLabel DOMMouseEventClientYPropertyInfo = "DOMMouseEvent::client-y" attrGet _ = getDOMMouseEventClientY attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "ctrl-key" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMMouseEventCtrlKey :: (MonadIO m, DOMMouseEventK o) => o -> m Bool getDOMMouseEventCtrlKey obj = liftIO $ getObjectPropertyBool obj "ctrl-key" data DOMMouseEventCtrlKeyPropertyInfo instance AttrInfo DOMMouseEventCtrlKeyPropertyInfo where type AttrAllowedOps DOMMouseEventCtrlKeyPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMMouseEventCtrlKeyPropertyInfo = (~) () type AttrBaseTypeConstraint DOMMouseEventCtrlKeyPropertyInfo = DOMMouseEventK type AttrGetType DOMMouseEventCtrlKeyPropertyInfo = Bool type AttrLabel DOMMouseEventCtrlKeyPropertyInfo = "DOMMouseEvent::ctrl-key" attrGet _ = getDOMMouseEventCtrlKey attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "from-element" -- Type: TInterface "WebKit" "DOMNode" -- Flags: [PropertyReadable] getDOMMouseEventFromElement :: (MonadIO m, DOMMouseEventK o) => o -> m DOMNode getDOMMouseEventFromElement obj = liftIO $ getObjectPropertyObject obj "from-element" DOMNode data DOMMouseEventFromElementPropertyInfo instance AttrInfo DOMMouseEventFromElementPropertyInfo where type AttrAllowedOps DOMMouseEventFromElementPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMMouseEventFromElementPropertyInfo = (~) () type AttrBaseTypeConstraint DOMMouseEventFromElementPropertyInfo = DOMMouseEventK type AttrGetType DOMMouseEventFromElementPropertyInfo = DOMNode type AttrLabel DOMMouseEventFromElementPropertyInfo = "DOMMouseEvent::from-element" attrGet _ = getDOMMouseEventFromElement attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "meta-key" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMMouseEventMetaKey :: (MonadIO m, DOMMouseEventK o) => o -> m Bool getDOMMouseEventMetaKey obj = liftIO $ getObjectPropertyBool obj "meta-key" data DOMMouseEventMetaKeyPropertyInfo instance AttrInfo DOMMouseEventMetaKeyPropertyInfo where type AttrAllowedOps DOMMouseEventMetaKeyPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMMouseEventMetaKeyPropertyInfo = (~) () type AttrBaseTypeConstraint DOMMouseEventMetaKeyPropertyInfo = DOMMouseEventK type AttrGetType DOMMouseEventMetaKeyPropertyInfo = Bool type AttrLabel DOMMouseEventMetaKeyPropertyInfo = "DOMMouseEvent::meta-key" attrGet _ = getDOMMouseEventMetaKey attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "offset-x" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMMouseEventOffsetX :: (MonadIO m, DOMMouseEventK o) => o -> m Int64 getDOMMouseEventOffsetX obj = liftIO $ getObjectPropertyInt64 obj "offset-x" data DOMMouseEventOffsetXPropertyInfo instance AttrInfo DOMMouseEventOffsetXPropertyInfo where type AttrAllowedOps DOMMouseEventOffsetXPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMMouseEventOffsetXPropertyInfo = (~) () type AttrBaseTypeConstraint DOMMouseEventOffsetXPropertyInfo = DOMMouseEventK type AttrGetType DOMMouseEventOffsetXPropertyInfo = Int64 type AttrLabel DOMMouseEventOffsetXPropertyInfo = "DOMMouseEvent::offset-x" attrGet _ = getDOMMouseEventOffsetX attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "offset-y" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMMouseEventOffsetY :: (MonadIO m, DOMMouseEventK o) => o -> m Int64 getDOMMouseEventOffsetY obj = liftIO $ getObjectPropertyInt64 obj "offset-y" data DOMMouseEventOffsetYPropertyInfo instance AttrInfo DOMMouseEventOffsetYPropertyInfo where type AttrAllowedOps DOMMouseEventOffsetYPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMMouseEventOffsetYPropertyInfo = (~) () type AttrBaseTypeConstraint DOMMouseEventOffsetYPropertyInfo = DOMMouseEventK type AttrGetType DOMMouseEventOffsetYPropertyInfo = Int64 type AttrLabel DOMMouseEventOffsetYPropertyInfo = "DOMMouseEvent::offset-y" attrGet _ = getDOMMouseEventOffsetY attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "related-target" -- Type: TInterface "WebKit" "DOMEventTarget" -- Flags: [PropertyReadable] getDOMMouseEventRelatedTarget :: (MonadIO m, DOMMouseEventK o) => o -> m DOMEventTarget getDOMMouseEventRelatedTarget obj = liftIO $ getObjectPropertyObject obj "related-target" DOMEventTarget data DOMMouseEventRelatedTargetPropertyInfo instance AttrInfo DOMMouseEventRelatedTargetPropertyInfo where type AttrAllowedOps DOMMouseEventRelatedTargetPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMMouseEventRelatedTargetPropertyInfo = (~) () type AttrBaseTypeConstraint DOMMouseEventRelatedTargetPropertyInfo = DOMMouseEventK type AttrGetType DOMMouseEventRelatedTargetPropertyInfo = DOMEventTarget type AttrLabel DOMMouseEventRelatedTargetPropertyInfo = "DOMMouseEvent::related-target" attrGet _ = getDOMMouseEventRelatedTarget attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "screen-x" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMMouseEventScreenX :: (MonadIO m, DOMMouseEventK o) => o -> m Int64 getDOMMouseEventScreenX obj = liftIO $ getObjectPropertyInt64 obj "screen-x" data DOMMouseEventScreenXPropertyInfo instance AttrInfo DOMMouseEventScreenXPropertyInfo where type AttrAllowedOps DOMMouseEventScreenXPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMMouseEventScreenXPropertyInfo = (~) () type AttrBaseTypeConstraint DOMMouseEventScreenXPropertyInfo = DOMMouseEventK type AttrGetType DOMMouseEventScreenXPropertyInfo = Int64 type AttrLabel DOMMouseEventScreenXPropertyInfo = "DOMMouseEvent::screen-x" attrGet _ = getDOMMouseEventScreenX attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "screen-y" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMMouseEventScreenY :: (MonadIO m, DOMMouseEventK o) => o -> m Int64 getDOMMouseEventScreenY obj = liftIO $ getObjectPropertyInt64 obj "screen-y" data DOMMouseEventScreenYPropertyInfo instance AttrInfo DOMMouseEventScreenYPropertyInfo where type AttrAllowedOps DOMMouseEventScreenYPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMMouseEventScreenYPropertyInfo = (~) () type AttrBaseTypeConstraint DOMMouseEventScreenYPropertyInfo = DOMMouseEventK type AttrGetType DOMMouseEventScreenYPropertyInfo = Int64 type AttrLabel DOMMouseEventScreenYPropertyInfo = "DOMMouseEvent::screen-y" attrGet _ = getDOMMouseEventScreenY attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "shift-key" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMMouseEventShiftKey :: (MonadIO m, DOMMouseEventK o) => o -> m Bool getDOMMouseEventShiftKey obj = liftIO $ getObjectPropertyBool obj "shift-key" data DOMMouseEventShiftKeyPropertyInfo instance AttrInfo DOMMouseEventShiftKeyPropertyInfo where type AttrAllowedOps DOMMouseEventShiftKeyPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMMouseEventShiftKeyPropertyInfo = (~) () type AttrBaseTypeConstraint DOMMouseEventShiftKeyPropertyInfo = DOMMouseEventK type AttrGetType DOMMouseEventShiftKeyPropertyInfo = Bool type AttrLabel DOMMouseEventShiftKeyPropertyInfo = "DOMMouseEvent::shift-key" attrGet _ = getDOMMouseEventShiftKey attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "to-element" -- Type: TInterface "WebKit" "DOMNode" -- Flags: [PropertyReadable] getDOMMouseEventToElement :: (MonadIO m, DOMMouseEventK o) => o -> m DOMNode getDOMMouseEventToElement obj = liftIO $ getObjectPropertyObject obj "to-element" DOMNode data DOMMouseEventToElementPropertyInfo instance AttrInfo DOMMouseEventToElementPropertyInfo where type AttrAllowedOps DOMMouseEventToElementPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMMouseEventToElementPropertyInfo = (~) () type AttrBaseTypeConstraint DOMMouseEventToElementPropertyInfo = DOMMouseEventK type AttrGetType DOMMouseEventToElementPropertyInfo = DOMNode type AttrLabel DOMMouseEventToElementPropertyInfo = "DOMMouseEvent::to-element" attrGet _ = getDOMMouseEventToElement attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "webkit-movement-x" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMMouseEventWebkitMovementX :: (MonadIO m, DOMMouseEventK o) => o -> m Int64 getDOMMouseEventWebkitMovementX obj = liftIO $ getObjectPropertyInt64 obj "webkit-movement-x" data DOMMouseEventWebkitMovementXPropertyInfo instance AttrInfo DOMMouseEventWebkitMovementXPropertyInfo where type AttrAllowedOps DOMMouseEventWebkitMovementXPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMMouseEventWebkitMovementXPropertyInfo = (~) () type AttrBaseTypeConstraint DOMMouseEventWebkitMovementXPropertyInfo = DOMMouseEventK type AttrGetType DOMMouseEventWebkitMovementXPropertyInfo = Int64 type AttrLabel DOMMouseEventWebkitMovementXPropertyInfo = "DOMMouseEvent::webkit-movement-x" attrGet _ = getDOMMouseEventWebkitMovementX attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "webkit-movement-y" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMMouseEventWebkitMovementY :: (MonadIO m, DOMMouseEventK o) => o -> m Int64 getDOMMouseEventWebkitMovementY obj = liftIO $ getObjectPropertyInt64 obj "webkit-movement-y" data DOMMouseEventWebkitMovementYPropertyInfo instance AttrInfo DOMMouseEventWebkitMovementYPropertyInfo where type AttrAllowedOps DOMMouseEventWebkitMovementYPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMMouseEventWebkitMovementYPropertyInfo = (~) () type AttrBaseTypeConstraint DOMMouseEventWebkitMovementYPropertyInfo = DOMMouseEventK type AttrGetType DOMMouseEventWebkitMovementYPropertyInfo = Int64 type AttrLabel DOMMouseEventWebkitMovementYPropertyInfo = "DOMMouseEvent::webkit-movement-y" attrGet _ = getDOMMouseEventWebkitMovementY attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "x" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMMouseEventX :: (MonadIO m, DOMMouseEventK o) => o -> m Int64 getDOMMouseEventX obj = liftIO $ getObjectPropertyInt64 obj "x" data DOMMouseEventXPropertyInfo instance AttrInfo DOMMouseEventXPropertyInfo where type AttrAllowedOps DOMMouseEventXPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMMouseEventXPropertyInfo = (~) () type AttrBaseTypeConstraint DOMMouseEventXPropertyInfo = DOMMouseEventK type AttrGetType DOMMouseEventXPropertyInfo = Int64 type AttrLabel DOMMouseEventXPropertyInfo = "DOMMouseEvent::x" attrGet _ = getDOMMouseEventX attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "y" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMMouseEventY :: (MonadIO m, DOMMouseEventK o) => o -> m Int64 getDOMMouseEventY obj = liftIO $ getObjectPropertyInt64 obj "y" data DOMMouseEventYPropertyInfo instance AttrInfo DOMMouseEventYPropertyInfo where type AttrAllowedOps DOMMouseEventYPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMMouseEventYPropertyInfo = (~) () type AttrBaseTypeConstraint DOMMouseEventYPropertyInfo = DOMMouseEventK type AttrGetType DOMMouseEventYPropertyInfo = Int64 type AttrLabel DOMMouseEventYPropertyInfo = "DOMMouseEvent::y" attrGet _ = getDOMMouseEventY attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMMouseEvent = '[ '("alt-key", DOMMouseEventAltKeyPropertyInfo), '("bubbles", DOMEventBubblesPropertyInfo), '("button", DOMMouseEventButtonPropertyInfo), '("cancel-bubble", DOMEventCancelBubblePropertyInfo), '("cancelable", DOMEventCancelablePropertyInfo), '("char-code", DOMUIEventCharCodePropertyInfo), '("client-x", DOMMouseEventClientXPropertyInfo), '("client-y", DOMMouseEventClientYPropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("ctrl-key", DOMMouseEventCtrlKeyPropertyInfo), '("current-target", DOMEventCurrentTargetPropertyInfo), '("default-prevented", DOMEventDefaultPreventedPropertyInfo), '("detail", DOMUIEventDetailPropertyInfo), '("event-phase", DOMEventEventPhasePropertyInfo), '("from-element", DOMMouseEventFromElementPropertyInfo), '("key-code", DOMUIEventKeyCodePropertyInfo), '("layer-x", DOMUIEventLayerXPropertyInfo), '("layer-y", DOMUIEventLayerYPropertyInfo), '("meta-key", DOMMouseEventMetaKeyPropertyInfo), '("offset-x", DOMMouseEventOffsetXPropertyInfo), '("offset-y", DOMMouseEventOffsetYPropertyInfo), '("page-x", DOMUIEventPageXPropertyInfo), '("page-y", DOMUIEventPageYPropertyInfo), '("related-target", DOMMouseEventRelatedTargetPropertyInfo), '("return-value", DOMEventReturnValuePropertyInfo), '("screen-x", DOMMouseEventScreenXPropertyInfo), '("screen-y", DOMMouseEventScreenYPropertyInfo), '("shift-key", DOMMouseEventShiftKeyPropertyInfo), '("src-element", DOMEventSrcElementPropertyInfo), '("target", DOMEventTargetPropertyInfo), '("time-stamp", DOMEventTimeStampPropertyInfo), '("to-element", DOMMouseEventToElementPropertyInfo), '("type", DOMEventTypePropertyInfo), '("view", DOMUIEventViewPropertyInfo), '("webkit-movement-x", DOMMouseEventWebkitMovementXPropertyInfo), '("webkit-movement-y", DOMMouseEventWebkitMovementYPropertyInfo), '("which", DOMUIEventWhichPropertyInfo), '("x", DOMMouseEventXPropertyInfo), '("y", DOMMouseEventYPropertyInfo)] -- VVV Prop "length" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMNamedNodeMapLength :: (MonadIO m, DOMNamedNodeMapK o) => o -> m Word64 getDOMNamedNodeMapLength obj = liftIO $ getObjectPropertyUInt64 obj "length" data DOMNamedNodeMapLengthPropertyInfo instance AttrInfo DOMNamedNodeMapLengthPropertyInfo where type AttrAllowedOps DOMNamedNodeMapLengthPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMNamedNodeMapLengthPropertyInfo = (~) () type AttrBaseTypeConstraint DOMNamedNodeMapLengthPropertyInfo = DOMNamedNodeMapK type AttrGetType DOMNamedNodeMapLengthPropertyInfo = Word64 type AttrLabel DOMNamedNodeMapLengthPropertyInfo = "DOMNamedNodeMap::length" attrGet _ = getDOMNamedNodeMapLength attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMNamedNodeMap = '[ '("core-object", DOMObjectCoreObjectPropertyInfo), '("length", DOMNamedNodeMapLengthPropertyInfo)] -- VVV Prop "app-code-name" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMNavigatorAppCodeName :: (MonadIO m, DOMNavigatorK o) => o -> m T.Text getDOMNavigatorAppCodeName obj = liftIO $ getObjectPropertyString obj "app-code-name" data DOMNavigatorAppCodeNamePropertyInfo instance AttrInfo DOMNavigatorAppCodeNamePropertyInfo where type AttrAllowedOps DOMNavigatorAppCodeNamePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMNavigatorAppCodeNamePropertyInfo = (~) () type AttrBaseTypeConstraint DOMNavigatorAppCodeNamePropertyInfo = DOMNavigatorK type AttrGetType DOMNavigatorAppCodeNamePropertyInfo = T.Text type AttrLabel DOMNavigatorAppCodeNamePropertyInfo = "DOMNavigator::app-code-name" attrGet _ = getDOMNavigatorAppCodeName attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "app-name" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMNavigatorAppName :: (MonadIO m, DOMNavigatorK o) => o -> m T.Text getDOMNavigatorAppName obj = liftIO $ getObjectPropertyString obj "app-name" data DOMNavigatorAppNamePropertyInfo instance AttrInfo DOMNavigatorAppNamePropertyInfo where type AttrAllowedOps DOMNavigatorAppNamePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMNavigatorAppNamePropertyInfo = (~) () type AttrBaseTypeConstraint DOMNavigatorAppNamePropertyInfo = DOMNavigatorK type AttrGetType DOMNavigatorAppNamePropertyInfo = T.Text type AttrLabel DOMNavigatorAppNamePropertyInfo = "DOMNavigator::app-name" attrGet _ = getDOMNavigatorAppName attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "app-version" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMNavigatorAppVersion :: (MonadIO m, DOMNavigatorK o) => o -> m T.Text getDOMNavigatorAppVersion obj = liftIO $ getObjectPropertyString obj "app-version" data DOMNavigatorAppVersionPropertyInfo instance AttrInfo DOMNavigatorAppVersionPropertyInfo where type AttrAllowedOps DOMNavigatorAppVersionPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMNavigatorAppVersionPropertyInfo = (~) () type AttrBaseTypeConstraint DOMNavigatorAppVersionPropertyInfo = DOMNavigatorK type AttrGetType DOMNavigatorAppVersionPropertyInfo = T.Text type AttrLabel DOMNavigatorAppVersionPropertyInfo = "DOMNavigator::app-version" attrGet _ = getDOMNavigatorAppVersion attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "cookie-enabled" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMNavigatorCookieEnabled :: (MonadIO m, DOMNavigatorK o) => o -> m Bool getDOMNavigatorCookieEnabled obj = liftIO $ getObjectPropertyBool obj "cookie-enabled" data DOMNavigatorCookieEnabledPropertyInfo instance AttrInfo DOMNavigatorCookieEnabledPropertyInfo where type AttrAllowedOps DOMNavigatorCookieEnabledPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMNavigatorCookieEnabledPropertyInfo = (~) () type AttrBaseTypeConstraint DOMNavigatorCookieEnabledPropertyInfo = DOMNavigatorK type AttrGetType DOMNavigatorCookieEnabledPropertyInfo = Bool type AttrLabel DOMNavigatorCookieEnabledPropertyInfo = "DOMNavigator::cookie-enabled" attrGet _ = getDOMNavigatorCookieEnabled attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "geolocation" -- Type: TInterface "WebKit" "DOMGeolocation" -- Flags: [PropertyReadable] getDOMNavigatorGeolocation :: (MonadIO m, DOMNavigatorK o) => o -> m DOMGeolocation getDOMNavigatorGeolocation obj = liftIO $ getObjectPropertyObject obj "geolocation" DOMGeolocation data DOMNavigatorGeolocationPropertyInfo instance AttrInfo DOMNavigatorGeolocationPropertyInfo where type AttrAllowedOps DOMNavigatorGeolocationPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMNavigatorGeolocationPropertyInfo = (~) () type AttrBaseTypeConstraint DOMNavigatorGeolocationPropertyInfo = DOMNavigatorK type AttrGetType DOMNavigatorGeolocationPropertyInfo = DOMGeolocation type AttrLabel DOMNavigatorGeolocationPropertyInfo = "DOMNavigator::geolocation" attrGet _ = getDOMNavigatorGeolocation attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "language" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMNavigatorLanguage :: (MonadIO m, DOMNavigatorK o) => o -> m T.Text getDOMNavigatorLanguage obj = liftIO $ getObjectPropertyString obj "language" data DOMNavigatorLanguagePropertyInfo instance AttrInfo DOMNavigatorLanguagePropertyInfo where type AttrAllowedOps DOMNavigatorLanguagePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMNavigatorLanguagePropertyInfo = (~) () type AttrBaseTypeConstraint DOMNavigatorLanguagePropertyInfo = DOMNavigatorK type AttrGetType DOMNavigatorLanguagePropertyInfo = T.Text type AttrLabel DOMNavigatorLanguagePropertyInfo = "DOMNavigator::language" attrGet _ = getDOMNavigatorLanguage attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "mime-types" -- Type: TInterface "WebKit" "DOMDOMMimeTypeArray" -- Flags: [PropertyReadable] getDOMNavigatorMimeTypes :: (MonadIO m, DOMNavigatorK o) => o -> m DOMDOMMimeTypeArray getDOMNavigatorMimeTypes obj = liftIO $ getObjectPropertyObject obj "mime-types" DOMDOMMimeTypeArray data DOMNavigatorMimeTypesPropertyInfo instance AttrInfo DOMNavigatorMimeTypesPropertyInfo where type AttrAllowedOps DOMNavigatorMimeTypesPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMNavigatorMimeTypesPropertyInfo = (~) () type AttrBaseTypeConstraint DOMNavigatorMimeTypesPropertyInfo = DOMNavigatorK type AttrGetType DOMNavigatorMimeTypesPropertyInfo = DOMDOMMimeTypeArray type AttrLabel DOMNavigatorMimeTypesPropertyInfo = "DOMNavigator::mime-types" attrGet _ = getDOMNavigatorMimeTypes attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "on-line" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMNavigatorOnLine :: (MonadIO m, DOMNavigatorK o) => o -> m Bool getDOMNavigatorOnLine obj = liftIO $ getObjectPropertyBool obj "on-line" data DOMNavigatorOnLinePropertyInfo instance AttrInfo DOMNavigatorOnLinePropertyInfo where type AttrAllowedOps DOMNavigatorOnLinePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMNavigatorOnLinePropertyInfo = (~) () type AttrBaseTypeConstraint DOMNavigatorOnLinePropertyInfo = DOMNavigatorK type AttrGetType DOMNavigatorOnLinePropertyInfo = Bool type AttrLabel DOMNavigatorOnLinePropertyInfo = "DOMNavigator::on-line" attrGet _ = getDOMNavigatorOnLine attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "platform" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMNavigatorPlatform :: (MonadIO m, DOMNavigatorK o) => o -> m T.Text getDOMNavigatorPlatform obj = liftIO $ getObjectPropertyString obj "platform" data DOMNavigatorPlatformPropertyInfo instance AttrInfo DOMNavigatorPlatformPropertyInfo where type AttrAllowedOps DOMNavigatorPlatformPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMNavigatorPlatformPropertyInfo = (~) () type AttrBaseTypeConstraint DOMNavigatorPlatformPropertyInfo = DOMNavigatorK type AttrGetType DOMNavigatorPlatformPropertyInfo = T.Text type AttrLabel DOMNavigatorPlatformPropertyInfo = "DOMNavigator::platform" attrGet _ = getDOMNavigatorPlatform attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "plugins" -- Type: TInterface "WebKit" "DOMDOMPluginArray" -- Flags: [PropertyReadable] getDOMNavigatorPlugins :: (MonadIO m, DOMNavigatorK o) => o -> m DOMDOMPluginArray getDOMNavigatorPlugins obj = liftIO $ getObjectPropertyObject obj "plugins" DOMDOMPluginArray data DOMNavigatorPluginsPropertyInfo instance AttrInfo DOMNavigatorPluginsPropertyInfo where type AttrAllowedOps DOMNavigatorPluginsPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMNavigatorPluginsPropertyInfo = (~) () type AttrBaseTypeConstraint DOMNavigatorPluginsPropertyInfo = DOMNavigatorK type AttrGetType DOMNavigatorPluginsPropertyInfo = DOMDOMPluginArray type AttrLabel DOMNavigatorPluginsPropertyInfo = "DOMNavigator::plugins" attrGet _ = getDOMNavigatorPlugins attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "product" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMNavigatorProduct :: (MonadIO m, DOMNavigatorK o) => o -> m T.Text getDOMNavigatorProduct obj = liftIO $ getObjectPropertyString obj "product" data DOMNavigatorProductPropertyInfo instance AttrInfo DOMNavigatorProductPropertyInfo where type AttrAllowedOps DOMNavigatorProductPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMNavigatorProductPropertyInfo = (~) () type AttrBaseTypeConstraint DOMNavigatorProductPropertyInfo = DOMNavigatorK type AttrGetType DOMNavigatorProductPropertyInfo = T.Text type AttrLabel DOMNavigatorProductPropertyInfo = "DOMNavigator::product" attrGet _ = getDOMNavigatorProduct attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "product-sub" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMNavigatorProductSub :: (MonadIO m, DOMNavigatorK o) => o -> m T.Text getDOMNavigatorProductSub obj = liftIO $ getObjectPropertyString obj "product-sub" data DOMNavigatorProductSubPropertyInfo instance AttrInfo DOMNavigatorProductSubPropertyInfo where type AttrAllowedOps DOMNavigatorProductSubPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMNavigatorProductSubPropertyInfo = (~) () type AttrBaseTypeConstraint DOMNavigatorProductSubPropertyInfo = DOMNavigatorK type AttrGetType DOMNavigatorProductSubPropertyInfo = T.Text type AttrLabel DOMNavigatorProductSubPropertyInfo = "DOMNavigator::product-sub" attrGet _ = getDOMNavigatorProductSub attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "user-agent" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMNavigatorUserAgent :: (MonadIO m, DOMNavigatorK o) => o -> m T.Text getDOMNavigatorUserAgent obj = liftIO $ getObjectPropertyString obj "user-agent" data DOMNavigatorUserAgentPropertyInfo instance AttrInfo DOMNavigatorUserAgentPropertyInfo where type AttrAllowedOps DOMNavigatorUserAgentPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMNavigatorUserAgentPropertyInfo = (~) () type AttrBaseTypeConstraint DOMNavigatorUserAgentPropertyInfo = DOMNavigatorK type AttrGetType DOMNavigatorUserAgentPropertyInfo = T.Text type AttrLabel DOMNavigatorUserAgentPropertyInfo = "DOMNavigator::user-agent" attrGet _ = getDOMNavigatorUserAgent attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "vendor" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMNavigatorVendor :: (MonadIO m, DOMNavigatorK o) => o -> m T.Text getDOMNavigatorVendor obj = liftIO $ getObjectPropertyString obj "vendor" data DOMNavigatorVendorPropertyInfo instance AttrInfo DOMNavigatorVendorPropertyInfo where type AttrAllowedOps DOMNavigatorVendorPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMNavigatorVendorPropertyInfo = (~) () type AttrBaseTypeConstraint DOMNavigatorVendorPropertyInfo = DOMNavigatorK type AttrGetType DOMNavigatorVendorPropertyInfo = T.Text type AttrLabel DOMNavigatorVendorPropertyInfo = "DOMNavigator::vendor" attrGet _ = getDOMNavigatorVendor attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "vendor-sub" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMNavigatorVendorSub :: (MonadIO m, DOMNavigatorK o) => o -> m T.Text getDOMNavigatorVendorSub obj = liftIO $ getObjectPropertyString obj "vendor-sub" data DOMNavigatorVendorSubPropertyInfo instance AttrInfo DOMNavigatorVendorSubPropertyInfo where type AttrAllowedOps DOMNavigatorVendorSubPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMNavigatorVendorSubPropertyInfo = (~) () type AttrBaseTypeConstraint DOMNavigatorVendorSubPropertyInfo = DOMNavigatorK type AttrGetType DOMNavigatorVendorSubPropertyInfo = T.Text type AttrLabel DOMNavigatorVendorSubPropertyInfo = "DOMNavigator::vendor-sub" attrGet _ = getDOMNavigatorVendorSub attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "webkit-battery" -- Type: TInterface "WebKit" "DOMBatteryManager" -- Flags: [PropertyReadable] getDOMNavigatorWebkitBattery :: (MonadIO m, DOMNavigatorK o) => o -> m DOMBatteryManager getDOMNavigatorWebkitBattery obj = liftIO $ getObjectPropertyObject obj "webkit-battery" DOMBatteryManager data DOMNavigatorWebkitBatteryPropertyInfo instance AttrInfo DOMNavigatorWebkitBatteryPropertyInfo where type AttrAllowedOps DOMNavigatorWebkitBatteryPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMNavigatorWebkitBatteryPropertyInfo = (~) () type AttrBaseTypeConstraint DOMNavigatorWebkitBatteryPropertyInfo = DOMNavigatorK type AttrGetType DOMNavigatorWebkitBatteryPropertyInfo = DOMBatteryManager type AttrLabel DOMNavigatorWebkitBatteryPropertyInfo = "DOMNavigator::webkit-battery" attrGet _ = getDOMNavigatorWebkitBattery attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "webkit-persistent-storage" -- Type: TInterface "WebKit" "DOMStorageQuota" -- Flags: [PropertyReadable] getDOMNavigatorWebkitPersistentStorage :: (MonadIO m, DOMNavigatorK o) => o -> m DOMStorageQuota getDOMNavigatorWebkitPersistentStorage obj = liftIO $ getObjectPropertyObject obj "webkit-persistent-storage" DOMStorageQuota data DOMNavigatorWebkitPersistentStoragePropertyInfo instance AttrInfo DOMNavigatorWebkitPersistentStoragePropertyInfo where type AttrAllowedOps DOMNavigatorWebkitPersistentStoragePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMNavigatorWebkitPersistentStoragePropertyInfo = (~) () type AttrBaseTypeConstraint DOMNavigatorWebkitPersistentStoragePropertyInfo = DOMNavigatorK type AttrGetType DOMNavigatorWebkitPersistentStoragePropertyInfo = DOMStorageQuota type AttrLabel DOMNavigatorWebkitPersistentStoragePropertyInfo = "DOMNavigator::webkit-persistent-storage" attrGet _ = getDOMNavigatorWebkitPersistentStorage attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "webkit-temporary-storage" -- Type: TInterface "WebKit" "DOMStorageQuota" -- Flags: [PropertyReadable] getDOMNavigatorWebkitTemporaryStorage :: (MonadIO m, DOMNavigatorK o) => o -> m DOMStorageQuota getDOMNavigatorWebkitTemporaryStorage obj = liftIO $ getObjectPropertyObject obj "webkit-temporary-storage" DOMStorageQuota data DOMNavigatorWebkitTemporaryStoragePropertyInfo instance AttrInfo DOMNavigatorWebkitTemporaryStoragePropertyInfo where type AttrAllowedOps DOMNavigatorWebkitTemporaryStoragePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMNavigatorWebkitTemporaryStoragePropertyInfo = (~) () type AttrBaseTypeConstraint DOMNavigatorWebkitTemporaryStoragePropertyInfo = DOMNavigatorK type AttrGetType DOMNavigatorWebkitTemporaryStoragePropertyInfo = DOMStorageQuota type AttrLabel DOMNavigatorWebkitTemporaryStoragePropertyInfo = "DOMNavigator::webkit-temporary-storage" attrGet _ = getDOMNavigatorWebkitTemporaryStorage attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMNavigator = '[ '("app-code-name", DOMNavigatorAppCodeNamePropertyInfo), '("app-name", DOMNavigatorAppNamePropertyInfo), '("app-version", DOMNavigatorAppVersionPropertyInfo), '("cookie-enabled", DOMNavigatorCookieEnabledPropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("geolocation", DOMNavigatorGeolocationPropertyInfo), '("language", DOMNavigatorLanguagePropertyInfo), '("mime-types", DOMNavigatorMimeTypesPropertyInfo), '("on-line", DOMNavigatorOnLinePropertyInfo), '("platform", DOMNavigatorPlatformPropertyInfo), '("plugins", DOMNavigatorPluginsPropertyInfo), '("product", DOMNavigatorProductPropertyInfo), '("product-sub", DOMNavigatorProductSubPropertyInfo), '("user-agent", DOMNavigatorUserAgentPropertyInfo), '("vendor", DOMNavigatorVendorPropertyInfo), '("vendor-sub", DOMNavigatorVendorSubPropertyInfo), '("webkit-battery", DOMNavigatorWebkitBatteryPropertyInfo), '("webkit-persistent-storage", DOMNavigatorWebkitPersistentStoragePropertyInfo), '("webkit-temporary-storage", DOMNavigatorWebkitTemporaryStoragePropertyInfo)] -- VVV Prop "base-uri" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMNodeBaseUri :: (MonadIO m, DOMNodeK o) => o -> m T.Text getDOMNodeBaseUri obj = liftIO $ getObjectPropertyString obj "base-uri" data DOMNodeBaseUriPropertyInfo instance AttrInfo DOMNodeBaseUriPropertyInfo where type AttrAllowedOps DOMNodeBaseUriPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMNodeBaseUriPropertyInfo = (~) () type AttrBaseTypeConstraint DOMNodeBaseUriPropertyInfo = DOMNodeK type AttrGetType DOMNodeBaseUriPropertyInfo = T.Text type AttrLabel DOMNodeBaseUriPropertyInfo = "DOMNode::base-uri" attrGet _ = getDOMNodeBaseUri attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "child-nodes" -- Type: TInterface "WebKit" "DOMNodeList" -- Flags: [PropertyReadable] getDOMNodeChildNodes :: (MonadIO m, DOMNodeK o) => o -> m DOMNodeList getDOMNodeChildNodes obj = liftIO $ getObjectPropertyObject obj "child-nodes" DOMNodeList data DOMNodeChildNodesPropertyInfo instance AttrInfo DOMNodeChildNodesPropertyInfo where type AttrAllowedOps DOMNodeChildNodesPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMNodeChildNodesPropertyInfo = (~) () type AttrBaseTypeConstraint DOMNodeChildNodesPropertyInfo = DOMNodeK type AttrGetType DOMNodeChildNodesPropertyInfo = DOMNodeList type AttrLabel DOMNodeChildNodesPropertyInfo = "DOMNode::child-nodes" attrGet _ = getDOMNodeChildNodes attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "first-child" -- Type: TInterface "WebKit" "DOMNode" -- Flags: [PropertyReadable] getDOMNodeFirstChild :: (MonadIO m, DOMNodeK o) => o -> m DOMNode getDOMNodeFirstChild obj = liftIO $ getObjectPropertyObject obj "first-child" DOMNode data DOMNodeFirstChildPropertyInfo instance AttrInfo DOMNodeFirstChildPropertyInfo where type AttrAllowedOps DOMNodeFirstChildPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMNodeFirstChildPropertyInfo = (~) () type AttrBaseTypeConstraint DOMNodeFirstChildPropertyInfo = DOMNodeK type AttrGetType DOMNodeFirstChildPropertyInfo = DOMNode type AttrLabel DOMNodeFirstChildPropertyInfo = "DOMNode::first-child" attrGet _ = getDOMNodeFirstChild attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "last-child" -- Type: TInterface "WebKit" "DOMNode" -- Flags: [PropertyReadable] getDOMNodeLastChild :: (MonadIO m, DOMNodeK o) => o -> m DOMNode getDOMNodeLastChild obj = liftIO $ getObjectPropertyObject obj "last-child" DOMNode data DOMNodeLastChildPropertyInfo instance AttrInfo DOMNodeLastChildPropertyInfo where type AttrAllowedOps DOMNodeLastChildPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMNodeLastChildPropertyInfo = (~) () type AttrBaseTypeConstraint DOMNodeLastChildPropertyInfo = DOMNodeK type AttrGetType DOMNodeLastChildPropertyInfo = DOMNode type AttrLabel DOMNodeLastChildPropertyInfo = "DOMNode::last-child" attrGet _ = getDOMNodeLastChild attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "local-name" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMNodeLocalName :: (MonadIO m, DOMNodeK o) => o -> m T.Text getDOMNodeLocalName obj = liftIO $ getObjectPropertyString obj "local-name" data DOMNodeLocalNamePropertyInfo instance AttrInfo DOMNodeLocalNamePropertyInfo where type AttrAllowedOps DOMNodeLocalNamePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMNodeLocalNamePropertyInfo = (~) () type AttrBaseTypeConstraint DOMNodeLocalNamePropertyInfo = DOMNodeK type AttrGetType DOMNodeLocalNamePropertyInfo = T.Text type AttrLabel DOMNodeLocalNamePropertyInfo = "DOMNode::local-name" attrGet _ = getDOMNodeLocalName attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "namespace-uri" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMNodeNamespaceUri :: (MonadIO m, DOMNodeK o) => o -> m T.Text getDOMNodeNamespaceUri obj = liftIO $ getObjectPropertyString obj "namespace-uri" data DOMNodeNamespaceUriPropertyInfo instance AttrInfo DOMNodeNamespaceUriPropertyInfo where type AttrAllowedOps DOMNodeNamespaceUriPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMNodeNamespaceUriPropertyInfo = (~) () type AttrBaseTypeConstraint DOMNodeNamespaceUriPropertyInfo = DOMNodeK type AttrGetType DOMNodeNamespaceUriPropertyInfo = T.Text type AttrLabel DOMNodeNamespaceUriPropertyInfo = "DOMNode::namespace-uri" attrGet _ = getDOMNodeNamespaceUri attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "next-sibling" -- Type: TInterface "WebKit" "DOMNode" -- Flags: [PropertyReadable] getDOMNodeNextSibling :: (MonadIO m, DOMNodeK o) => o -> m DOMNode getDOMNodeNextSibling obj = liftIO $ getObjectPropertyObject obj "next-sibling" DOMNode data DOMNodeNextSiblingPropertyInfo instance AttrInfo DOMNodeNextSiblingPropertyInfo where type AttrAllowedOps DOMNodeNextSiblingPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMNodeNextSiblingPropertyInfo = (~) () type AttrBaseTypeConstraint DOMNodeNextSiblingPropertyInfo = DOMNodeK type AttrGetType DOMNodeNextSiblingPropertyInfo = DOMNode type AttrLabel DOMNodeNextSiblingPropertyInfo = "DOMNode::next-sibling" attrGet _ = getDOMNodeNextSibling attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "node-name" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMNodeNodeName :: (MonadIO m, DOMNodeK o) => o -> m T.Text getDOMNodeNodeName obj = liftIO $ getObjectPropertyString obj "node-name" data DOMNodeNodeNamePropertyInfo instance AttrInfo DOMNodeNodeNamePropertyInfo where type AttrAllowedOps DOMNodeNodeNamePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMNodeNodeNamePropertyInfo = (~) () type AttrBaseTypeConstraint DOMNodeNodeNamePropertyInfo = DOMNodeK type AttrGetType DOMNodeNodeNamePropertyInfo = T.Text type AttrLabel DOMNodeNodeNamePropertyInfo = "DOMNode::node-name" attrGet _ = getDOMNodeNodeName attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "node-type" -- Type: TBasicType TUInt32 -- Flags: [PropertyReadable] getDOMNodeNodeType :: (MonadIO m, DOMNodeK o) => o -> m Word32 getDOMNodeNodeType obj = liftIO $ getObjectPropertyCUInt obj "node-type" data DOMNodeNodeTypePropertyInfo instance AttrInfo DOMNodeNodeTypePropertyInfo where type AttrAllowedOps DOMNodeNodeTypePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMNodeNodeTypePropertyInfo = (~) () type AttrBaseTypeConstraint DOMNodeNodeTypePropertyInfo = DOMNodeK type AttrGetType DOMNodeNodeTypePropertyInfo = Word32 type AttrLabel DOMNodeNodeTypePropertyInfo = "DOMNode::node-type" attrGet _ = getDOMNodeNodeType attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "node-value" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMNodeNodeValue :: (MonadIO m, DOMNodeK o) => o -> m T.Text getDOMNodeNodeValue obj = liftIO $ getObjectPropertyString obj "node-value" setDOMNodeNodeValue :: (MonadIO m, DOMNodeK o) => o -> T.Text -> m () setDOMNodeNodeValue obj val = liftIO $ setObjectPropertyString obj "node-value" val constructDOMNodeNodeValue :: T.Text -> IO ([Char], GValue) constructDOMNodeNodeValue val = constructObjectPropertyString "node-value" val data DOMNodeNodeValuePropertyInfo instance AttrInfo DOMNodeNodeValuePropertyInfo where type AttrAllowedOps DOMNodeNodeValuePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMNodeNodeValuePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMNodeNodeValuePropertyInfo = DOMNodeK type AttrGetType DOMNodeNodeValuePropertyInfo = T.Text type AttrLabel DOMNodeNodeValuePropertyInfo = "DOMNode::node-value" attrGet _ = getDOMNodeNodeValue attrSet _ = setDOMNodeNodeValue attrConstruct _ = constructDOMNodeNodeValue -- VVV Prop "owner-document" -- Type: TInterface "WebKit" "DOMDocument" -- Flags: [PropertyReadable] getDOMNodeOwnerDocument :: (MonadIO m, DOMNodeK o) => o -> m DOMDocument getDOMNodeOwnerDocument obj = liftIO $ getObjectPropertyObject obj "owner-document" DOMDocument data DOMNodeOwnerDocumentPropertyInfo instance AttrInfo DOMNodeOwnerDocumentPropertyInfo where type AttrAllowedOps DOMNodeOwnerDocumentPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMNodeOwnerDocumentPropertyInfo = (~) () type AttrBaseTypeConstraint DOMNodeOwnerDocumentPropertyInfo = DOMNodeK type AttrGetType DOMNodeOwnerDocumentPropertyInfo = DOMDocument type AttrLabel DOMNodeOwnerDocumentPropertyInfo = "DOMNode::owner-document" attrGet _ = getDOMNodeOwnerDocument attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "parent-element" -- Type: TInterface "WebKit" "DOMElement" -- Flags: [PropertyReadable] getDOMNodeParentElement :: (MonadIO m, DOMNodeK o) => o -> m DOMElement getDOMNodeParentElement obj = liftIO $ getObjectPropertyObject obj "parent-element" DOMElement data DOMNodeParentElementPropertyInfo instance AttrInfo DOMNodeParentElementPropertyInfo where type AttrAllowedOps DOMNodeParentElementPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMNodeParentElementPropertyInfo = (~) () type AttrBaseTypeConstraint DOMNodeParentElementPropertyInfo = DOMNodeK type AttrGetType DOMNodeParentElementPropertyInfo = DOMElement type AttrLabel DOMNodeParentElementPropertyInfo = "DOMNode::parent-element" attrGet _ = getDOMNodeParentElement attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "parent-node" -- Type: TInterface "WebKit" "DOMNode" -- Flags: [PropertyReadable] getDOMNodeParentNode :: (MonadIO m, DOMNodeK o) => o -> m DOMNode getDOMNodeParentNode obj = liftIO $ getObjectPropertyObject obj "parent-node" DOMNode data DOMNodeParentNodePropertyInfo instance AttrInfo DOMNodeParentNodePropertyInfo where type AttrAllowedOps DOMNodeParentNodePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMNodeParentNodePropertyInfo = (~) () type AttrBaseTypeConstraint DOMNodeParentNodePropertyInfo = DOMNodeK type AttrGetType DOMNodeParentNodePropertyInfo = DOMNode type AttrLabel DOMNodeParentNodePropertyInfo = "DOMNode::parent-node" attrGet _ = getDOMNodeParentNode attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "prefix" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMNodePrefix :: (MonadIO m, DOMNodeK o) => o -> m T.Text getDOMNodePrefix obj = liftIO $ getObjectPropertyString obj "prefix" setDOMNodePrefix :: (MonadIO m, DOMNodeK o) => o -> T.Text -> m () setDOMNodePrefix obj val = liftIO $ setObjectPropertyString obj "prefix" val constructDOMNodePrefix :: T.Text -> IO ([Char], GValue) constructDOMNodePrefix val = constructObjectPropertyString "prefix" val data DOMNodePrefixPropertyInfo instance AttrInfo DOMNodePrefixPropertyInfo where type AttrAllowedOps DOMNodePrefixPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMNodePrefixPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMNodePrefixPropertyInfo = DOMNodeK type AttrGetType DOMNodePrefixPropertyInfo = T.Text type AttrLabel DOMNodePrefixPropertyInfo = "DOMNode::prefix" attrGet _ = getDOMNodePrefix attrSet _ = setDOMNodePrefix attrConstruct _ = constructDOMNodePrefix -- VVV Prop "previous-sibling" -- Type: TInterface "WebKit" "DOMNode" -- Flags: [PropertyReadable] getDOMNodePreviousSibling :: (MonadIO m, DOMNodeK o) => o -> m DOMNode getDOMNodePreviousSibling obj = liftIO $ getObjectPropertyObject obj "previous-sibling" DOMNode data DOMNodePreviousSiblingPropertyInfo instance AttrInfo DOMNodePreviousSiblingPropertyInfo where type AttrAllowedOps DOMNodePreviousSiblingPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMNodePreviousSiblingPropertyInfo = (~) () type AttrBaseTypeConstraint DOMNodePreviousSiblingPropertyInfo = DOMNodeK type AttrGetType DOMNodePreviousSiblingPropertyInfo = DOMNode type AttrLabel DOMNodePreviousSiblingPropertyInfo = "DOMNode::previous-sibling" attrGet _ = getDOMNodePreviousSibling attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "text-content" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMNodeTextContent :: (MonadIO m, DOMNodeK o) => o -> m T.Text getDOMNodeTextContent obj = liftIO $ getObjectPropertyString obj "text-content" setDOMNodeTextContent :: (MonadIO m, DOMNodeK o) => o -> T.Text -> m () setDOMNodeTextContent obj val = liftIO $ setObjectPropertyString obj "text-content" val constructDOMNodeTextContent :: T.Text -> IO ([Char], GValue) constructDOMNodeTextContent val = constructObjectPropertyString "text-content" val data DOMNodeTextContentPropertyInfo instance AttrInfo DOMNodeTextContentPropertyInfo where type AttrAllowedOps DOMNodeTextContentPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMNodeTextContentPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMNodeTextContentPropertyInfo = DOMNodeK type AttrGetType DOMNodeTextContentPropertyInfo = T.Text type AttrLabel DOMNodeTextContentPropertyInfo = "DOMNode::text-content" attrGet _ = getDOMNodeTextContent attrSet _ = setDOMNodeTextContent attrConstruct _ = constructDOMNodeTextContent type instance AttributeList DOMNode = '[ '("base-uri", DOMNodeBaseUriPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo)] type instance AttributeList DOMNodeFilter = '[ '("core-object", DOMObjectCoreObjectPropertyInfo)] -- VVV Prop "expand-entity-references" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMNodeIteratorExpandEntityReferences :: (MonadIO m, DOMNodeIteratorK o) => o -> m Bool getDOMNodeIteratorExpandEntityReferences obj = liftIO $ getObjectPropertyBool obj "expand-entity-references" data DOMNodeIteratorExpandEntityReferencesPropertyInfo instance AttrInfo DOMNodeIteratorExpandEntityReferencesPropertyInfo where type AttrAllowedOps DOMNodeIteratorExpandEntityReferencesPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMNodeIteratorExpandEntityReferencesPropertyInfo = (~) () type AttrBaseTypeConstraint DOMNodeIteratorExpandEntityReferencesPropertyInfo = DOMNodeIteratorK type AttrGetType DOMNodeIteratorExpandEntityReferencesPropertyInfo = Bool type AttrLabel DOMNodeIteratorExpandEntityReferencesPropertyInfo = "DOMNodeIterator::expand-entity-references" attrGet _ = getDOMNodeIteratorExpandEntityReferences attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "filter" -- Type: TInterface "WebKit" "DOMNodeFilter" -- Flags: [PropertyReadable] getDOMNodeIteratorFilter :: (MonadIO m, DOMNodeIteratorK o) => o -> m DOMNodeFilter getDOMNodeIteratorFilter obj = liftIO $ getObjectPropertyObject obj "filter" DOMNodeFilter data DOMNodeIteratorFilterPropertyInfo instance AttrInfo DOMNodeIteratorFilterPropertyInfo where type AttrAllowedOps DOMNodeIteratorFilterPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMNodeIteratorFilterPropertyInfo = (~) () type AttrBaseTypeConstraint DOMNodeIteratorFilterPropertyInfo = DOMNodeIteratorK type AttrGetType DOMNodeIteratorFilterPropertyInfo = DOMNodeFilter type AttrLabel DOMNodeIteratorFilterPropertyInfo = "DOMNodeIterator::filter" attrGet _ = getDOMNodeIteratorFilter attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "pointer-before-reference-node" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMNodeIteratorPointerBeforeReferenceNode :: (MonadIO m, DOMNodeIteratorK o) => o -> m Bool getDOMNodeIteratorPointerBeforeReferenceNode obj = liftIO $ getObjectPropertyBool obj "pointer-before-reference-node" data DOMNodeIteratorPointerBeforeReferenceNodePropertyInfo instance AttrInfo DOMNodeIteratorPointerBeforeReferenceNodePropertyInfo where type AttrAllowedOps DOMNodeIteratorPointerBeforeReferenceNodePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMNodeIteratorPointerBeforeReferenceNodePropertyInfo = (~) () type AttrBaseTypeConstraint DOMNodeIteratorPointerBeforeReferenceNodePropertyInfo = DOMNodeIteratorK type AttrGetType DOMNodeIteratorPointerBeforeReferenceNodePropertyInfo = Bool type AttrLabel DOMNodeIteratorPointerBeforeReferenceNodePropertyInfo = "DOMNodeIterator::pointer-before-reference-node" attrGet _ = getDOMNodeIteratorPointerBeforeReferenceNode attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "reference-node" -- Type: TInterface "WebKit" "DOMNode" -- Flags: [PropertyReadable] getDOMNodeIteratorReferenceNode :: (MonadIO m, DOMNodeIteratorK o) => o -> m DOMNode getDOMNodeIteratorReferenceNode obj = liftIO $ getObjectPropertyObject obj "reference-node" DOMNode data DOMNodeIteratorReferenceNodePropertyInfo instance AttrInfo DOMNodeIteratorReferenceNodePropertyInfo where type AttrAllowedOps DOMNodeIteratorReferenceNodePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMNodeIteratorReferenceNodePropertyInfo = (~) () type AttrBaseTypeConstraint DOMNodeIteratorReferenceNodePropertyInfo = DOMNodeIteratorK type AttrGetType DOMNodeIteratorReferenceNodePropertyInfo = DOMNode type AttrLabel DOMNodeIteratorReferenceNodePropertyInfo = "DOMNodeIterator::reference-node" attrGet _ = getDOMNodeIteratorReferenceNode attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "root" -- Type: TInterface "WebKit" "DOMNode" -- Flags: [PropertyReadable] getDOMNodeIteratorRoot :: (MonadIO m, DOMNodeIteratorK o) => o -> m DOMNode getDOMNodeIteratorRoot obj = liftIO $ getObjectPropertyObject obj "root" DOMNode data DOMNodeIteratorRootPropertyInfo instance AttrInfo DOMNodeIteratorRootPropertyInfo where type AttrAllowedOps DOMNodeIteratorRootPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMNodeIteratorRootPropertyInfo = (~) () type AttrBaseTypeConstraint DOMNodeIteratorRootPropertyInfo = DOMNodeIteratorK type AttrGetType DOMNodeIteratorRootPropertyInfo = DOMNode type AttrLabel DOMNodeIteratorRootPropertyInfo = "DOMNodeIterator::root" attrGet _ = getDOMNodeIteratorRoot attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "what-to-show" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMNodeIteratorWhatToShow :: (MonadIO m, DOMNodeIteratorK o) => o -> m Word64 getDOMNodeIteratorWhatToShow obj = liftIO $ getObjectPropertyUInt64 obj "what-to-show" data DOMNodeIteratorWhatToShowPropertyInfo instance AttrInfo DOMNodeIteratorWhatToShowPropertyInfo where type AttrAllowedOps DOMNodeIteratorWhatToShowPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMNodeIteratorWhatToShowPropertyInfo = (~) () type AttrBaseTypeConstraint DOMNodeIteratorWhatToShowPropertyInfo = DOMNodeIteratorK type AttrGetType DOMNodeIteratorWhatToShowPropertyInfo = Word64 type AttrLabel DOMNodeIteratorWhatToShowPropertyInfo = "DOMNodeIterator::what-to-show" attrGet _ = getDOMNodeIteratorWhatToShow attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMNodeIterator = '[ '("core-object", DOMObjectCoreObjectPropertyInfo), '("expand-entity-references", DOMNodeIteratorExpandEntityReferencesPropertyInfo), '("filter", DOMNodeIteratorFilterPropertyInfo), '("pointer-before-reference-node", DOMNodeIteratorPointerBeforeReferenceNodePropertyInfo), '("reference-node", DOMNodeIteratorReferenceNodePropertyInfo), '("root", DOMNodeIteratorRootPropertyInfo), '("what-to-show", DOMNodeIteratorWhatToShowPropertyInfo)] -- VVV Prop "length" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMNodeListLength :: (MonadIO m, DOMNodeListK o) => o -> m Word64 getDOMNodeListLength obj = liftIO $ getObjectPropertyUInt64 obj "length" data DOMNodeListLengthPropertyInfo instance AttrInfo DOMNodeListLengthPropertyInfo where type AttrAllowedOps DOMNodeListLengthPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMNodeListLengthPropertyInfo = (~) () type AttrBaseTypeConstraint DOMNodeListLengthPropertyInfo = DOMNodeListK type AttrGetType DOMNodeListLengthPropertyInfo = Word64 type AttrLabel DOMNodeListLengthPropertyInfo = "DOMNodeList::length" attrGet _ = getDOMNodeListLength attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMNodeList = '[ '("core-object", DOMObjectCoreObjectPropertyInfo), '("length", DOMNodeListLengthPropertyInfo)] -- VVV Prop "core-object" -- Type: TBasicType TVoid -- Flags: [PropertyWritable,PropertyConstructOnly] constructDOMObjectCoreObject :: (Ptr ()) -> IO ([Char], GValue) constructDOMObjectCoreObject val = constructObjectPropertyPtr "core-object" val data DOMObjectCoreObjectPropertyInfo instance AttrInfo DOMObjectCoreObjectPropertyInfo where type AttrAllowedOps DOMObjectCoreObjectPropertyInfo = '[ 'AttrConstruct] type AttrSetTypeConstraint DOMObjectCoreObjectPropertyInfo = (~) (Ptr ()) type AttrBaseTypeConstraint DOMObjectCoreObjectPropertyInfo = DOMObjectK type AttrGetType DOMObjectCoreObjectPropertyInfo = () type AttrLabel DOMObjectCoreObjectPropertyInfo = "DOMObject::core-object" attrGet _ = undefined attrSet _ = undefined attrConstruct _ = constructDOMObjectCoreObject type instance AttributeList DOMObject = '[ '("core-object", DOMObjectCoreObjectPropertyInfo)] -- VVV Prop "navigation" -- Type: TInterface "WebKit" "DOMPerformanceNavigation" -- Flags: [PropertyReadable] getDOMPerformanceNavigation :: (MonadIO m, DOMPerformanceK o) => o -> m DOMPerformanceNavigation getDOMPerformanceNavigation obj = liftIO $ getObjectPropertyObject obj "navigation" DOMPerformanceNavigation data DOMPerformanceNavigationPropertyInfo instance AttrInfo DOMPerformanceNavigationPropertyInfo where type AttrAllowedOps DOMPerformanceNavigationPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMPerformanceNavigationPropertyInfo = (~) () type AttrBaseTypeConstraint DOMPerformanceNavigationPropertyInfo = DOMPerformanceK type AttrGetType DOMPerformanceNavigationPropertyInfo = DOMPerformanceNavigation type AttrLabel DOMPerformanceNavigationPropertyInfo = "DOMPerformance::navigation" attrGet _ = getDOMPerformanceNavigation attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "timing" -- Type: TInterface "WebKit" "DOMPerformanceTiming" -- Flags: [PropertyReadable] getDOMPerformanceTiming :: (MonadIO m, DOMPerformanceK o) => o -> m DOMPerformanceTiming getDOMPerformanceTiming obj = liftIO $ getObjectPropertyObject obj "timing" DOMPerformanceTiming data DOMPerformanceTimingPropertyInfo instance AttrInfo DOMPerformanceTimingPropertyInfo where type AttrAllowedOps DOMPerformanceTimingPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMPerformanceTimingPropertyInfo = (~) () type AttrBaseTypeConstraint DOMPerformanceTimingPropertyInfo = DOMPerformanceK type AttrGetType DOMPerformanceTimingPropertyInfo = DOMPerformanceTiming type AttrLabel DOMPerformanceTimingPropertyInfo = "DOMPerformance::timing" attrGet _ = getDOMPerformanceTiming attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMPerformance = '[ '("core-object", DOMObjectCoreObjectPropertyInfo), '("navigation", DOMPerformanceNavigationPropertyInfo), '("timing", DOMPerformanceTimingPropertyInfo)] -- VVV Prop "duration" -- Type: TBasicType TDouble -- Flags: [PropertyReadable] getDOMPerformanceEntryDuration :: (MonadIO m, DOMPerformanceEntryK o) => o -> m Double getDOMPerformanceEntryDuration obj = liftIO $ getObjectPropertyDouble obj "duration" data DOMPerformanceEntryDurationPropertyInfo instance AttrInfo DOMPerformanceEntryDurationPropertyInfo where type AttrAllowedOps DOMPerformanceEntryDurationPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMPerformanceEntryDurationPropertyInfo = (~) () type AttrBaseTypeConstraint DOMPerformanceEntryDurationPropertyInfo = DOMPerformanceEntryK type AttrGetType DOMPerformanceEntryDurationPropertyInfo = Double type AttrLabel DOMPerformanceEntryDurationPropertyInfo = "DOMPerformanceEntry::duration" attrGet _ = getDOMPerformanceEntryDuration attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "entry-type" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMPerformanceEntryEntryType :: (MonadIO m, DOMPerformanceEntryK o) => o -> m T.Text getDOMPerformanceEntryEntryType obj = liftIO $ getObjectPropertyString obj "entry-type" data DOMPerformanceEntryEntryTypePropertyInfo instance AttrInfo DOMPerformanceEntryEntryTypePropertyInfo where type AttrAllowedOps DOMPerformanceEntryEntryTypePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMPerformanceEntryEntryTypePropertyInfo = (~) () type AttrBaseTypeConstraint DOMPerformanceEntryEntryTypePropertyInfo = DOMPerformanceEntryK type AttrGetType DOMPerformanceEntryEntryTypePropertyInfo = T.Text type AttrLabel DOMPerformanceEntryEntryTypePropertyInfo = "DOMPerformanceEntry::entry-type" attrGet _ = getDOMPerformanceEntryEntryType attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "name" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMPerformanceEntryName :: (MonadIO m, DOMPerformanceEntryK o) => o -> m T.Text getDOMPerformanceEntryName obj = liftIO $ getObjectPropertyString obj "name" data DOMPerformanceEntryNamePropertyInfo instance AttrInfo DOMPerformanceEntryNamePropertyInfo where type AttrAllowedOps DOMPerformanceEntryNamePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMPerformanceEntryNamePropertyInfo = (~) () type AttrBaseTypeConstraint DOMPerformanceEntryNamePropertyInfo = DOMPerformanceEntryK type AttrGetType DOMPerformanceEntryNamePropertyInfo = T.Text type AttrLabel DOMPerformanceEntryNamePropertyInfo = "DOMPerformanceEntry::name" attrGet _ = getDOMPerformanceEntryName attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "start-time" -- Type: TBasicType TDouble -- Flags: [PropertyReadable] getDOMPerformanceEntryStartTime :: (MonadIO m, DOMPerformanceEntryK o) => o -> m Double getDOMPerformanceEntryStartTime obj = liftIO $ getObjectPropertyDouble obj "start-time" data DOMPerformanceEntryStartTimePropertyInfo instance AttrInfo DOMPerformanceEntryStartTimePropertyInfo where type AttrAllowedOps DOMPerformanceEntryStartTimePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMPerformanceEntryStartTimePropertyInfo = (~) () type AttrBaseTypeConstraint DOMPerformanceEntryStartTimePropertyInfo = DOMPerformanceEntryK type AttrGetType DOMPerformanceEntryStartTimePropertyInfo = Double type AttrLabel DOMPerformanceEntryStartTimePropertyInfo = "DOMPerformanceEntry::start-time" attrGet _ = getDOMPerformanceEntryStartTime attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMPerformanceEntry = '[ '("core-object", DOMObjectCoreObjectPropertyInfo), '("duration", DOMPerformanceEntryDurationPropertyInfo), '("entry-type", DOMPerformanceEntryEntryTypePropertyInfo), '("name", DOMPerformanceEntryNamePropertyInfo), '("start-time", DOMPerformanceEntryStartTimePropertyInfo)] -- VVV Prop "length" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMPerformanceEntryListLength :: (MonadIO m, DOMPerformanceEntryListK o) => o -> m Word64 getDOMPerformanceEntryListLength obj = liftIO $ getObjectPropertyUInt64 obj "length" data DOMPerformanceEntryListLengthPropertyInfo instance AttrInfo DOMPerformanceEntryListLengthPropertyInfo where type AttrAllowedOps DOMPerformanceEntryListLengthPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMPerformanceEntryListLengthPropertyInfo = (~) () type AttrBaseTypeConstraint DOMPerformanceEntryListLengthPropertyInfo = DOMPerformanceEntryListK type AttrGetType DOMPerformanceEntryListLengthPropertyInfo = Word64 type AttrLabel DOMPerformanceEntryListLengthPropertyInfo = "DOMPerformanceEntryList::length" attrGet _ = getDOMPerformanceEntryListLength attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMPerformanceEntryList = '[ '("core-object", DOMObjectCoreObjectPropertyInfo), '("length", DOMPerformanceEntryListLengthPropertyInfo)] -- VVV Prop "redirect-count" -- Type: TBasicType TUInt32 -- Flags: [PropertyReadable] getDOMPerformanceNavigationRedirectCount :: (MonadIO m, DOMPerformanceNavigationK o) => o -> m Word32 getDOMPerformanceNavigationRedirectCount obj = liftIO $ getObjectPropertyCUInt obj "redirect-count" data DOMPerformanceNavigationRedirectCountPropertyInfo instance AttrInfo DOMPerformanceNavigationRedirectCountPropertyInfo where type AttrAllowedOps DOMPerformanceNavigationRedirectCountPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMPerformanceNavigationRedirectCountPropertyInfo = (~) () type AttrBaseTypeConstraint DOMPerformanceNavigationRedirectCountPropertyInfo = DOMPerformanceNavigationK type AttrGetType DOMPerformanceNavigationRedirectCountPropertyInfo = Word32 type AttrLabel DOMPerformanceNavigationRedirectCountPropertyInfo = "DOMPerformanceNavigation::redirect-count" attrGet _ = getDOMPerformanceNavigationRedirectCount attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "type" -- Type: TBasicType TUInt32 -- Flags: [PropertyReadable] getDOMPerformanceNavigationType :: (MonadIO m, DOMPerformanceNavigationK o) => o -> m Word32 getDOMPerformanceNavigationType obj = liftIO $ getObjectPropertyCUInt obj "type" data DOMPerformanceNavigationTypePropertyInfo instance AttrInfo DOMPerformanceNavigationTypePropertyInfo where type AttrAllowedOps DOMPerformanceNavigationTypePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMPerformanceNavigationTypePropertyInfo = (~) () type AttrBaseTypeConstraint DOMPerformanceNavigationTypePropertyInfo = DOMPerformanceNavigationK type AttrGetType DOMPerformanceNavigationTypePropertyInfo = Word32 type AttrLabel DOMPerformanceNavigationTypePropertyInfo = "DOMPerformanceNavigation::type" attrGet _ = getDOMPerformanceNavigationType attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMPerformanceNavigation = '[ '("core-object", DOMObjectCoreObjectPropertyInfo), '("redirect-count", DOMPerformanceNavigationRedirectCountPropertyInfo), '("type", DOMPerformanceNavigationTypePropertyInfo)] -- VVV Prop "connect-end" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMPerformanceTimingConnectEnd :: (MonadIO m, DOMPerformanceTimingK o) => o -> m Word64 getDOMPerformanceTimingConnectEnd obj = liftIO $ getObjectPropertyUInt64 obj "connect-end" data DOMPerformanceTimingConnectEndPropertyInfo instance AttrInfo DOMPerformanceTimingConnectEndPropertyInfo where type AttrAllowedOps DOMPerformanceTimingConnectEndPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMPerformanceTimingConnectEndPropertyInfo = (~) () type AttrBaseTypeConstraint DOMPerformanceTimingConnectEndPropertyInfo = DOMPerformanceTimingK type AttrGetType DOMPerformanceTimingConnectEndPropertyInfo = Word64 type AttrLabel DOMPerformanceTimingConnectEndPropertyInfo = "DOMPerformanceTiming::connect-end" attrGet _ = getDOMPerformanceTimingConnectEnd attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "connect-start" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMPerformanceTimingConnectStart :: (MonadIO m, DOMPerformanceTimingK o) => o -> m Word64 getDOMPerformanceTimingConnectStart obj = liftIO $ getObjectPropertyUInt64 obj "connect-start" data DOMPerformanceTimingConnectStartPropertyInfo instance AttrInfo DOMPerformanceTimingConnectStartPropertyInfo where type AttrAllowedOps DOMPerformanceTimingConnectStartPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMPerformanceTimingConnectStartPropertyInfo = (~) () type AttrBaseTypeConstraint DOMPerformanceTimingConnectStartPropertyInfo = DOMPerformanceTimingK type AttrGetType DOMPerformanceTimingConnectStartPropertyInfo = Word64 type AttrLabel DOMPerformanceTimingConnectStartPropertyInfo = "DOMPerformanceTiming::connect-start" attrGet _ = getDOMPerformanceTimingConnectStart attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "dom-complete" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMPerformanceTimingDomComplete :: (MonadIO m, DOMPerformanceTimingK o) => o -> m Word64 getDOMPerformanceTimingDomComplete obj = liftIO $ getObjectPropertyUInt64 obj "dom-complete" data DOMPerformanceTimingDomCompletePropertyInfo instance AttrInfo DOMPerformanceTimingDomCompletePropertyInfo where type AttrAllowedOps DOMPerformanceTimingDomCompletePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMPerformanceTimingDomCompletePropertyInfo = (~) () type AttrBaseTypeConstraint DOMPerformanceTimingDomCompletePropertyInfo = DOMPerformanceTimingK type AttrGetType DOMPerformanceTimingDomCompletePropertyInfo = Word64 type AttrLabel DOMPerformanceTimingDomCompletePropertyInfo = "DOMPerformanceTiming::dom-complete" attrGet _ = getDOMPerformanceTimingDomComplete attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "dom-content-loaded-event-end" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMPerformanceTimingDomContentLoadedEventEnd :: (MonadIO m, DOMPerformanceTimingK o) => o -> m Word64 getDOMPerformanceTimingDomContentLoadedEventEnd obj = liftIO $ getObjectPropertyUInt64 obj "dom-content-loaded-event-end" data DOMPerformanceTimingDomContentLoadedEventEndPropertyInfo instance AttrInfo DOMPerformanceTimingDomContentLoadedEventEndPropertyInfo where type AttrAllowedOps DOMPerformanceTimingDomContentLoadedEventEndPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMPerformanceTimingDomContentLoadedEventEndPropertyInfo = (~) () type AttrBaseTypeConstraint DOMPerformanceTimingDomContentLoadedEventEndPropertyInfo = DOMPerformanceTimingK type AttrGetType DOMPerformanceTimingDomContentLoadedEventEndPropertyInfo = Word64 type AttrLabel DOMPerformanceTimingDomContentLoadedEventEndPropertyInfo = "DOMPerformanceTiming::dom-content-loaded-event-end" attrGet _ = getDOMPerformanceTimingDomContentLoadedEventEnd attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "dom-content-loaded-event-start" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMPerformanceTimingDomContentLoadedEventStart :: (MonadIO m, DOMPerformanceTimingK o) => o -> m Word64 getDOMPerformanceTimingDomContentLoadedEventStart obj = liftIO $ getObjectPropertyUInt64 obj "dom-content-loaded-event-start" data DOMPerformanceTimingDomContentLoadedEventStartPropertyInfo instance AttrInfo DOMPerformanceTimingDomContentLoadedEventStartPropertyInfo where type AttrAllowedOps DOMPerformanceTimingDomContentLoadedEventStartPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMPerformanceTimingDomContentLoadedEventStartPropertyInfo = (~) () type AttrBaseTypeConstraint DOMPerformanceTimingDomContentLoadedEventStartPropertyInfo = DOMPerformanceTimingK type AttrGetType DOMPerformanceTimingDomContentLoadedEventStartPropertyInfo = Word64 type AttrLabel DOMPerformanceTimingDomContentLoadedEventStartPropertyInfo = "DOMPerformanceTiming::dom-content-loaded-event-start" attrGet _ = getDOMPerformanceTimingDomContentLoadedEventStart attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "dom-interactive" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMPerformanceTimingDomInteractive :: (MonadIO m, DOMPerformanceTimingK o) => o -> m Word64 getDOMPerformanceTimingDomInteractive obj = liftIO $ getObjectPropertyUInt64 obj "dom-interactive" data DOMPerformanceTimingDomInteractivePropertyInfo instance AttrInfo DOMPerformanceTimingDomInteractivePropertyInfo where type AttrAllowedOps DOMPerformanceTimingDomInteractivePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMPerformanceTimingDomInteractivePropertyInfo = (~) () type AttrBaseTypeConstraint DOMPerformanceTimingDomInteractivePropertyInfo = DOMPerformanceTimingK type AttrGetType DOMPerformanceTimingDomInteractivePropertyInfo = Word64 type AttrLabel DOMPerformanceTimingDomInteractivePropertyInfo = "DOMPerformanceTiming::dom-interactive" attrGet _ = getDOMPerformanceTimingDomInteractive attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "dom-loading" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMPerformanceTimingDomLoading :: (MonadIO m, DOMPerformanceTimingK o) => o -> m Word64 getDOMPerformanceTimingDomLoading obj = liftIO $ getObjectPropertyUInt64 obj "dom-loading" data DOMPerformanceTimingDomLoadingPropertyInfo instance AttrInfo DOMPerformanceTimingDomLoadingPropertyInfo where type AttrAllowedOps DOMPerformanceTimingDomLoadingPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMPerformanceTimingDomLoadingPropertyInfo = (~) () type AttrBaseTypeConstraint DOMPerformanceTimingDomLoadingPropertyInfo = DOMPerformanceTimingK type AttrGetType DOMPerformanceTimingDomLoadingPropertyInfo = Word64 type AttrLabel DOMPerformanceTimingDomLoadingPropertyInfo = "DOMPerformanceTiming::dom-loading" attrGet _ = getDOMPerformanceTimingDomLoading attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "domain-lookup-end" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMPerformanceTimingDomainLookupEnd :: (MonadIO m, DOMPerformanceTimingK o) => o -> m Word64 getDOMPerformanceTimingDomainLookupEnd obj = liftIO $ getObjectPropertyUInt64 obj "domain-lookup-end" data DOMPerformanceTimingDomainLookupEndPropertyInfo instance AttrInfo DOMPerformanceTimingDomainLookupEndPropertyInfo where type AttrAllowedOps DOMPerformanceTimingDomainLookupEndPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMPerformanceTimingDomainLookupEndPropertyInfo = (~) () type AttrBaseTypeConstraint DOMPerformanceTimingDomainLookupEndPropertyInfo = DOMPerformanceTimingK type AttrGetType DOMPerformanceTimingDomainLookupEndPropertyInfo = Word64 type AttrLabel DOMPerformanceTimingDomainLookupEndPropertyInfo = "DOMPerformanceTiming::domain-lookup-end" attrGet _ = getDOMPerformanceTimingDomainLookupEnd attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "domain-lookup-start" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMPerformanceTimingDomainLookupStart :: (MonadIO m, DOMPerformanceTimingK o) => o -> m Word64 getDOMPerformanceTimingDomainLookupStart obj = liftIO $ getObjectPropertyUInt64 obj "domain-lookup-start" data DOMPerformanceTimingDomainLookupStartPropertyInfo instance AttrInfo DOMPerformanceTimingDomainLookupStartPropertyInfo where type AttrAllowedOps DOMPerformanceTimingDomainLookupStartPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMPerformanceTimingDomainLookupStartPropertyInfo = (~) () type AttrBaseTypeConstraint DOMPerformanceTimingDomainLookupStartPropertyInfo = DOMPerformanceTimingK type AttrGetType DOMPerformanceTimingDomainLookupStartPropertyInfo = Word64 type AttrLabel DOMPerformanceTimingDomainLookupStartPropertyInfo = "DOMPerformanceTiming::domain-lookup-start" attrGet _ = getDOMPerformanceTimingDomainLookupStart attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "fetch-start" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMPerformanceTimingFetchStart :: (MonadIO m, DOMPerformanceTimingK o) => o -> m Word64 getDOMPerformanceTimingFetchStart obj = liftIO $ getObjectPropertyUInt64 obj "fetch-start" data DOMPerformanceTimingFetchStartPropertyInfo instance AttrInfo DOMPerformanceTimingFetchStartPropertyInfo where type AttrAllowedOps DOMPerformanceTimingFetchStartPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMPerformanceTimingFetchStartPropertyInfo = (~) () type AttrBaseTypeConstraint DOMPerformanceTimingFetchStartPropertyInfo = DOMPerformanceTimingK type AttrGetType DOMPerformanceTimingFetchStartPropertyInfo = Word64 type AttrLabel DOMPerformanceTimingFetchStartPropertyInfo = "DOMPerformanceTiming::fetch-start" attrGet _ = getDOMPerformanceTimingFetchStart attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "load-event-end" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMPerformanceTimingLoadEventEnd :: (MonadIO m, DOMPerformanceTimingK o) => o -> m Word64 getDOMPerformanceTimingLoadEventEnd obj = liftIO $ getObjectPropertyUInt64 obj "load-event-end" data DOMPerformanceTimingLoadEventEndPropertyInfo instance AttrInfo DOMPerformanceTimingLoadEventEndPropertyInfo where type AttrAllowedOps DOMPerformanceTimingLoadEventEndPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMPerformanceTimingLoadEventEndPropertyInfo = (~) () type AttrBaseTypeConstraint DOMPerformanceTimingLoadEventEndPropertyInfo = DOMPerformanceTimingK type AttrGetType DOMPerformanceTimingLoadEventEndPropertyInfo = Word64 type AttrLabel DOMPerformanceTimingLoadEventEndPropertyInfo = "DOMPerformanceTiming::load-event-end" attrGet _ = getDOMPerformanceTimingLoadEventEnd attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "load-event-start" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMPerformanceTimingLoadEventStart :: (MonadIO m, DOMPerformanceTimingK o) => o -> m Word64 getDOMPerformanceTimingLoadEventStart obj = liftIO $ getObjectPropertyUInt64 obj "load-event-start" data DOMPerformanceTimingLoadEventStartPropertyInfo instance AttrInfo DOMPerformanceTimingLoadEventStartPropertyInfo where type AttrAllowedOps DOMPerformanceTimingLoadEventStartPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMPerformanceTimingLoadEventStartPropertyInfo = (~) () type AttrBaseTypeConstraint DOMPerformanceTimingLoadEventStartPropertyInfo = DOMPerformanceTimingK type AttrGetType DOMPerformanceTimingLoadEventStartPropertyInfo = Word64 type AttrLabel DOMPerformanceTimingLoadEventStartPropertyInfo = "DOMPerformanceTiming::load-event-start" attrGet _ = getDOMPerformanceTimingLoadEventStart attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "navigation-start" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMPerformanceTimingNavigationStart :: (MonadIO m, DOMPerformanceTimingK o) => o -> m Word64 getDOMPerformanceTimingNavigationStart obj = liftIO $ getObjectPropertyUInt64 obj "navigation-start" data DOMPerformanceTimingNavigationStartPropertyInfo instance AttrInfo DOMPerformanceTimingNavigationStartPropertyInfo where type AttrAllowedOps DOMPerformanceTimingNavigationStartPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMPerformanceTimingNavigationStartPropertyInfo = (~) () type AttrBaseTypeConstraint DOMPerformanceTimingNavigationStartPropertyInfo = DOMPerformanceTimingK type AttrGetType DOMPerformanceTimingNavigationStartPropertyInfo = Word64 type AttrLabel DOMPerformanceTimingNavigationStartPropertyInfo = "DOMPerformanceTiming::navigation-start" attrGet _ = getDOMPerformanceTimingNavigationStart attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "redirect-end" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMPerformanceTimingRedirectEnd :: (MonadIO m, DOMPerformanceTimingK o) => o -> m Word64 getDOMPerformanceTimingRedirectEnd obj = liftIO $ getObjectPropertyUInt64 obj "redirect-end" data DOMPerformanceTimingRedirectEndPropertyInfo instance AttrInfo DOMPerformanceTimingRedirectEndPropertyInfo where type AttrAllowedOps DOMPerformanceTimingRedirectEndPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMPerformanceTimingRedirectEndPropertyInfo = (~) () type AttrBaseTypeConstraint DOMPerformanceTimingRedirectEndPropertyInfo = DOMPerformanceTimingK type AttrGetType DOMPerformanceTimingRedirectEndPropertyInfo = Word64 type AttrLabel DOMPerformanceTimingRedirectEndPropertyInfo = "DOMPerformanceTiming::redirect-end" attrGet _ = getDOMPerformanceTimingRedirectEnd attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "redirect-start" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMPerformanceTimingRedirectStart :: (MonadIO m, DOMPerformanceTimingK o) => o -> m Word64 getDOMPerformanceTimingRedirectStart obj = liftIO $ getObjectPropertyUInt64 obj "redirect-start" data DOMPerformanceTimingRedirectStartPropertyInfo instance AttrInfo DOMPerformanceTimingRedirectStartPropertyInfo where type AttrAllowedOps DOMPerformanceTimingRedirectStartPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMPerformanceTimingRedirectStartPropertyInfo = (~) () type AttrBaseTypeConstraint DOMPerformanceTimingRedirectStartPropertyInfo = DOMPerformanceTimingK type AttrGetType DOMPerformanceTimingRedirectStartPropertyInfo = Word64 type AttrLabel DOMPerformanceTimingRedirectStartPropertyInfo = "DOMPerformanceTiming::redirect-start" attrGet _ = getDOMPerformanceTimingRedirectStart attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "request-start" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMPerformanceTimingRequestStart :: (MonadIO m, DOMPerformanceTimingK o) => o -> m Word64 getDOMPerformanceTimingRequestStart obj = liftIO $ getObjectPropertyUInt64 obj "request-start" data DOMPerformanceTimingRequestStartPropertyInfo instance AttrInfo DOMPerformanceTimingRequestStartPropertyInfo where type AttrAllowedOps DOMPerformanceTimingRequestStartPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMPerformanceTimingRequestStartPropertyInfo = (~) () type AttrBaseTypeConstraint DOMPerformanceTimingRequestStartPropertyInfo = DOMPerformanceTimingK type AttrGetType DOMPerformanceTimingRequestStartPropertyInfo = Word64 type AttrLabel DOMPerformanceTimingRequestStartPropertyInfo = "DOMPerformanceTiming::request-start" attrGet _ = getDOMPerformanceTimingRequestStart attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "response-end" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMPerformanceTimingResponseEnd :: (MonadIO m, DOMPerformanceTimingK o) => o -> m Word64 getDOMPerformanceTimingResponseEnd obj = liftIO $ getObjectPropertyUInt64 obj "response-end" data DOMPerformanceTimingResponseEndPropertyInfo instance AttrInfo DOMPerformanceTimingResponseEndPropertyInfo where type AttrAllowedOps DOMPerformanceTimingResponseEndPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMPerformanceTimingResponseEndPropertyInfo = (~) () type AttrBaseTypeConstraint DOMPerformanceTimingResponseEndPropertyInfo = DOMPerformanceTimingK type AttrGetType DOMPerformanceTimingResponseEndPropertyInfo = Word64 type AttrLabel DOMPerformanceTimingResponseEndPropertyInfo = "DOMPerformanceTiming::response-end" attrGet _ = getDOMPerformanceTimingResponseEnd attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "response-start" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMPerformanceTimingResponseStart :: (MonadIO m, DOMPerformanceTimingK o) => o -> m Word64 getDOMPerformanceTimingResponseStart obj = liftIO $ getObjectPropertyUInt64 obj "response-start" data DOMPerformanceTimingResponseStartPropertyInfo instance AttrInfo DOMPerformanceTimingResponseStartPropertyInfo where type AttrAllowedOps DOMPerformanceTimingResponseStartPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMPerformanceTimingResponseStartPropertyInfo = (~) () type AttrBaseTypeConstraint DOMPerformanceTimingResponseStartPropertyInfo = DOMPerformanceTimingK type AttrGetType DOMPerformanceTimingResponseStartPropertyInfo = Word64 type AttrLabel DOMPerformanceTimingResponseStartPropertyInfo = "DOMPerformanceTiming::response-start" attrGet _ = getDOMPerformanceTimingResponseStart attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "secure-connection-start" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMPerformanceTimingSecureConnectionStart :: (MonadIO m, DOMPerformanceTimingK o) => o -> m Word64 getDOMPerformanceTimingSecureConnectionStart obj = liftIO $ getObjectPropertyUInt64 obj "secure-connection-start" data DOMPerformanceTimingSecureConnectionStartPropertyInfo instance AttrInfo DOMPerformanceTimingSecureConnectionStartPropertyInfo where type AttrAllowedOps DOMPerformanceTimingSecureConnectionStartPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMPerformanceTimingSecureConnectionStartPropertyInfo = (~) () type AttrBaseTypeConstraint DOMPerformanceTimingSecureConnectionStartPropertyInfo = DOMPerformanceTimingK type AttrGetType DOMPerformanceTimingSecureConnectionStartPropertyInfo = Word64 type AttrLabel DOMPerformanceTimingSecureConnectionStartPropertyInfo = "DOMPerformanceTiming::secure-connection-start" attrGet _ = getDOMPerformanceTimingSecureConnectionStart attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "unload-event-end" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMPerformanceTimingUnloadEventEnd :: (MonadIO m, DOMPerformanceTimingK o) => o -> m Word64 getDOMPerformanceTimingUnloadEventEnd obj = liftIO $ getObjectPropertyUInt64 obj "unload-event-end" data DOMPerformanceTimingUnloadEventEndPropertyInfo instance AttrInfo DOMPerformanceTimingUnloadEventEndPropertyInfo where type AttrAllowedOps DOMPerformanceTimingUnloadEventEndPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMPerformanceTimingUnloadEventEndPropertyInfo = (~) () type AttrBaseTypeConstraint DOMPerformanceTimingUnloadEventEndPropertyInfo = DOMPerformanceTimingK type AttrGetType DOMPerformanceTimingUnloadEventEndPropertyInfo = Word64 type AttrLabel DOMPerformanceTimingUnloadEventEndPropertyInfo = "DOMPerformanceTiming::unload-event-end" attrGet _ = getDOMPerformanceTimingUnloadEventEnd attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "unload-event-start" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMPerformanceTimingUnloadEventStart :: (MonadIO m, DOMPerformanceTimingK o) => o -> m Word64 getDOMPerformanceTimingUnloadEventStart obj = liftIO $ getObjectPropertyUInt64 obj "unload-event-start" data DOMPerformanceTimingUnloadEventStartPropertyInfo instance AttrInfo DOMPerformanceTimingUnloadEventStartPropertyInfo where type AttrAllowedOps DOMPerformanceTimingUnloadEventStartPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMPerformanceTimingUnloadEventStartPropertyInfo = (~) () type AttrBaseTypeConstraint DOMPerformanceTimingUnloadEventStartPropertyInfo = DOMPerformanceTimingK type AttrGetType DOMPerformanceTimingUnloadEventStartPropertyInfo = Word64 type AttrLabel DOMPerformanceTimingUnloadEventStartPropertyInfo = "DOMPerformanceTiming::unload-event-start" attrGet _ = getDOMPerformanceTimingUnloadEventStart attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMPerformanceTiming = '[ '("connect-end", DOMPerformanceTimingConnectEndPropertyInfo), '("connect-start", DOMPerformanceTimingConnectStartPropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("dom-complete", DOMPerformanceTimingDomCompletePropertyInfo), '("dom-content-loaded-event-end", DOMPerformanceTimingDomContentLoadedEventEndPropertyInfo), '("dom-content-loaded-event-start", DOMPerformanceTimingDomContentLoadedEventStartPropertyInfo), '("dom-interactive", DOMPerformanceTimingDomInteractivePropertyInfo), '("dom-loading", DOMPerformanceTimingDomLoadingPropertyInfo), '("domain-lookup-end", DOMPerformanceTimingDomainLookupEndPropertyInfo), '("domain-lookup-start", DOMPerformanceTimingDomainLookupStartPropertyInfo), '("fetch-start", DOMPerformanceTimingFetchStartPropertyInfo), '("load-event-end", DOMPerformanceTimingLoadEventEndPropertyInfo), '("load-event-start", DOMPerformanceTimingLoadEventStartPropertyInfo), '("navigation-start", DOMPerformanceTimingNavigationStartPropertyInfo), '("redirect-end", DOMPerformanceTimingRedirectEndPropertyInfo), '("redirect-start", DOMPerformanceTimingRedirectStartPropertyInfo), '("request-start", DOMPerformanceTimingRequestStartPropertyInfo), '("response-end", DOMPerformanceTimingResponseEndPropertyInfo), '("response-start", DOMPerformanceTimingResponseStartPropertyInfo), '("secure-connection-start", DOMPerformanceTimingSecureConnectionStartPropertyInfo), '("unload-event-end", DOMPerformanceTimingUnloadEventEndPropertyInfo), '("unload-event-start", DOMPerformanceTimingUnloadEventStartPropertyInfo)] -- VVV Prop "sheet" -- Type: TInterface "WebKit" "DOMStyleSheet" -- Flags: [PropertyReadable] getDOMProcessingInstructionSheet :: (MonadIO m, DOMProcessingInstructionK o) => o -> m DOMStyleSheet getDOMProcessingInstructionSheet obj = liftIO $ getObjectPropertyObject obj "sheet" DOMStyleSheet data DOMProcessingInstructionSheetPropertyInfo instance AttrInfo DOMProcessingInstructionSheetPropertyInfo where type AttrAllowedOps DOMProcessingInstructionSheetPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMProcessingInstructionSheetPropertyInfo = (~) () type AttrBaseTypeConstraint DOMProcessingInstructionSheetPropertyInfo = DOMProcessingInstructionK type AttrGetType DOMProcessingInstructionSheetPropertyInfo = DOMStyleSheet type AttrLabel DOMProcessingInstructionSheetPropertyInfo = "DOMProcessingInstruction::sheet" attrGet _ = getDOMProcessingInstructionSheet attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "target" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMProcessingInstructionTarget :: (MonadIO m, DOMProcessingInstructionK o) => o -> m T.Text getDOMProcessingInstructionTarget obj = liftIO $ getObjectPropertyString obj "target" data DOMProcessingInstructionTargetPropertyInfo instance AttrInfo DOMProcessingInstructionTargetPropertyInfo where type AttrAllowedOps DOMProcessingInstructionTargetPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMProcessingInstructionTargetPropertyInfo = (~) () type AttrBaseTypeConstraint DOMProcessingInstructionTargetPropertyInfo = DOMProcessingInstructionK type AttrGetType DOMProcessingInstructionTargetPropertyInfo = T.Text type AttrLabel DOMProcessingInstructionTargetPropertyInfo = "DOMProcessingInstruction::target" attrGet _ = getDOMProcessingInstructionTarget attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMProcessingInstruction = '[ '("base-uri", DOMNodeBaseUriPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("data", DOMCharacterDataDataPropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("length", DOMCharacterDataLengthPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("sheet", DOMProcessingInstructionSheetPropertyInfo), '("target", DOMProcessingInstructionTargetPropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo)] -- VVV Prop "length" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMPropertyNodeListLength :: (MonadIO m, DOMPropertyNodeListK o) => o -> m Word64 getDOMPropertyNodeListLength obj = liftIO $ getObjectPropertyUInt64 obj "length" data DOMPropertyNodeListLengthPropertyInfo instance AttrInfo DOMPropertyNodeListLengthPropertyInfo where type AttrAllowedOps DOMPropertyNodeListLengthPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMPropertyNodeListLengthPropertyInfo = (~) () type AttrBaseTypeConstraint DOMPropertyNodeListLengthPropertyInfo = DOMPropertyNodeListK type AttrGetType DOMPropertyNodeListLengthPropertyInfo = Word64 type AttrLabel DOMPropertyNodeListLengthPropertyInfo = "DOMPropertyNodeList::length" attrGet _ = getDOMPropertyNodeListLength attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMPropertyNodeList = '[ '("core-object", DOMObjectCoreObjectPropertyInfo), '("length", DOMPropertyNodeListLengthPropertyInfo)] -- VVV Prop "collapsed" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMRangeCollapsed :: (MonadIO m, DOMRangeK o) => o -> m Bool getDOMRangeCollapsed obj = liftIO $ getObjectPropertyBool obj "collapsed" data DOMRangeCollapsedPropertyInfo instance AttrInfo DOMRangeCollapsedPropertyInfo where type AttrAllowedOps DOMRangeCollapsedPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMRangeCollapsedPropertyInfo = (~) () type AttrBaseTypeConstraint DOMRangeCollapsedPropertyInfo = DOMRangeK type AttrGetType DOMRangeCollapsedPropertyInfo = Bool type AttrLabel DOMRangeCollapsedPropertyInfo = "DOMRange::collapsed" attrGet _ = getDOMRangeCollapsed attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "common-ancestor-container" -- Type: TInterface "WebKit" "DOMNode" -- Flags: [PropertyReadable] getDOMRangeCommonAncestorContainer :: (MonadIO m, DOMRangeK o) => o -> m DOMNode getDOMRangeCommonAncestorContainer obj = liftIO $ getObjectPropertyObject obj "common-ancestor-container" DOMNode data DOMRangeCommonAncestorContainerPropertyInfo instance AttrInfo DOMRangeCommonAncestorContainerPropertyInfo where type AttrAllowedOps DOMRangeCommonAncestorContainerPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMRangeCommonAncestorContainerPropertyInfo = (~) () type AttrBaseTypeConstraint DOMRangeCommonAncestorContainerPropertyInfo = DOMRangeK type AttrGetType DOMRangeCommonAncestorContainerPropertyInfo = DOMNode type AttrLabel DOMRangeCommonAncestorContainerPropertyInfo = "DOMRange::common-ancestor-container" attrGet _ = getDOMRangeCommonAncestorContainer attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "end-container" -- Type: TInterface "WebKit" "DOMNode" -- Flags: [PropertyReadable] getDOMRangeEndContainer :: (MonadIO m, DOMRangeK o) => o -> m DOMNode getDOMRangeEndContainer obj = liftIO $ getObjectPropertyObject obj "end-container" DOMNode data DOMRangeEndContainerPropertyInfo instance AttrInfo DOMRangeEndContainerPropertyInfo where type AttrAllowedOps DOMRangeEndContainerPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMRangeEndContainerPropertyInfo = (~) () type AttrBaseTypeConstraint DOMRangeEndContainerPropertyInfo = DOMRangeK type AttrGetType DOMRangeEndContainerPropertyInfo = DOMNode type AttrLabel DOMRangeEndContainerPropertyInfo = "DOMRange::end-container" attrGet _ = getDOMRangeEndContainer attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "end-offset" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMRangeEndOffset :: (MonadIO m, DOMRangeK o) => o -> m Int64 getDOMRangeEndOffset obj = liftIO $ getObjectPropertyInt64 obj "end-offset" data DOMRangeEndOffsetPropertyInfo instance AttrInfo DOMRangeEndOffsetPropertyInfo where type AttrAllowedOps DOMRangeEndOffsetPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMRangeEndOffsetPropertyInfo = (~) () type AttrBaseTypeConstraint DOMRangeEndOffsetPropertyInfo = DOMRangeK type AttrGetType DOMRangeEndOffsetPropertyInfo = Int64 type AttrLabel DOMRangeEndOffsetPropertyInfo = "DOMRange::end-offset" attrGet _ = getDOMRangeEndOffset attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "start-container" -- Type: TInterface "WebKit" "DOMNode" -- Flags: [PropertyReadable] getDOMRangeStartContainer :: (MonadIO m, DOMRangeK o) => o -> m DOMNode getDOMRangeStartContainer obj = liftIO $ getObjectPropertyObject obj "start-container" DOMNode data DOMRangeStartContainerPropertyInfo instance AttrInfo DOMRangeStartContainerPropertyInfo where type AttrAllowedOps DOMRangeStartContainerPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMRangeStartContainerPropertyInfo = (~) () type AttrBaseTypeConstraint DOMRangeStartContainerPropertyInfo = DOMRangeK type AttrGetType DOMRangeStartContainerPropertyInfo = DOMNode type AttrLabel DOMRangeStartContainerPropertyInfo = "DOMRange::start-container" attrGet _ = getDOMRangeStartContainer attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "start-offset" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMRangeStartOffset :: (MonadIO m, DOMRangeK o) => o -> m Int64 getDOMRangeStartOffset obj = liftIO $ getObjectPropertyInt64 obj "start-offset" data DOMRangeStartOffsetPropertyInfo instance AttrInfo DOMRangeStartOffsetPropertyInfo where type AttrAllowedOps DOMRangeStartOffsetPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMRangeStartOffsetPropertyInfo = (~) () type AttrBaseTypeConstraint DOMRangeStartOffsetPropertyInfo = DOMRangeK type AttrGetType DOMRangeStartOffsetPropertyInfo = Int64 type AttrLabel DOMRangeStartOffsetPropertyInfo = "DOMRange::start-offset" attrGet _ = getDOMRangeStartOffset attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "text" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMRangeText :: (MonadIO m, DOMRangeK o) => o -> m T.Text getDOMRangeText obj = liftIO $ getObjectPropertyString obj "text" data DOMRangeTextPropertyInfo instance AttrInfo DOMRangeTextPropertyInfo where type AttrAllowedOps DOMRangeTextPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMRangeTextPropertyInfo = (~) () type AttrBaseTypeConstraint DOMRangeTextPropertyInfo = DOMRangeK type AttrGetType DOMRangeTextPropertyInfo = T.Text type AttrLabel DOMRangeTextPropertyInfo = "DOMRange::text" attrGet _ = getDOMRangeText attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMRange = '[ '("collapsed", DOMRangeCollapsedPropertyInfo), '("common-ancestor-container", DOMRangeCommonAncestorContainerPropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("end-container", DOMRangeEndContainerPropertyInfo), '("end-offset", DOMRangeEndOffsetPropertyInfo), '("start-container", DOMRangeStartContainerPropertyInfo), '("start-offset", DOMRangeStartOffsetPropertyInfo), '("text", DOMRangeTextPropertyInfo)] -- VVV Prop "avail-height" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMScreenAvailHeight :: (MonadIO m, DOMScreenK o) => o -> m Word64 getDOMScreenAvailHeight obj = liftIO $ getObjectPropertyUInt64 obj "avail-height" data DOMScreenAvailHeightPropertyInfo instance AttrInfo DOMScreenAvailHeightPropertyInfo where type AttrAllowedOps DOMScreenAvailHeightPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMScreenAvailHeightPropertyInfo = (~) () type AttrBaseTypeConstraint DOMScreenAvailHeightPropertyInfo = DOMScreenK type AttrGetType DOMScreenAvailHeightPropertyInfo = Word64 type AttrLabel DOMScreenAvailHeightPropertyInfo = "DOMScreen::avail-height" attrGet _ = getDOMScreenAvailHeight attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "avail-left" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMScreenAvailLeft :: (MonadIO m, DOMScreenK o) => o -> m Int64 getDOMScreenAvailLeft obj = liftIO $ getObjectPropertyInt64 obj "avail-left" data DOMScreenAvailLeftPropertyInfo instance AttrInfo DOMScreenAvailLeftPropertyInfo where type AttrAllowedOps DOMScreenAvailLeftPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMScreenAvailLeftPropertyInfo = (~) () type AttrBaseTypeConstraint DOMScreenAvailLeftPropertyInfo = DOMScreenK type AttrGetType DOMScreenAvailLeftPropertyInfo = Int64 type AttrLabel DOMScreenAvailLeftPropertyInfo = "DOMScreen::avail-left" attrGet _ = getDOMScreenAvailLeft attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "avail-top" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMScreenAvailTop :: (MonadIO m, DOMScreenK o) => o -> m Int64 getDOMScreenAvailTop obj = liftIO $ getObjectPropertyInt64 obj "avail-top" data DOMScreenAvailTopPropertyInfo instance AttrInfo DOMScreenAvailTopPropertyInfo where type AttrAllowedOps DOMScreenAvailTopPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMScreenAvailTopPropertyInfo = (~) () type AttrBaseTypeConstraint DOMScreenAvailTopPropertyInfo = DOMScreenK type AttrGetType DOMScreenAvailTopPropertyInfo = Int64 type AttrLabel DOMScreenAvailTopPropertyInfo = "DOMScreen::avail-top" attrGet _ = getDOMScreenAvailTop attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "avail-width" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMScreenAvailWidth :: (MonadIO m, DOMScreenK o) => o -> m Word64 getDOMScreenAvailWidth obj = liftIO $ getObjectPropertyUInt64 obj "avail-width" data DOMScreenAvailWidthPropertyInfo instance AttrInfo DOMScreenAvailWidthPropertyInfo where type AttrAllowedOps DOMScreenAvailWidthPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMScreenAvailWidthPropertyInfo = (~) () type AttrBaseTypeConstraint DOMScreenAvailWidthPropertyInfo = DOMScreenK type AttrGetType DOMScreenAvailWidthPropertyInfo = Word64 type AttrLabel DOMScreenAvailWidthPropertyInfo = "DOMScreen::avail-width" attrGet _ = getDOMScreenAvailWidth attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "color-depth" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMScreenColorDepth :: (MonadIO m, DOMScreenK o) => o -> m Word64 getDOMScreenColorDepth obj = liftIO $ getObjectPropertyUInt64 obj "color-depth" data DOMScreenColorDepthPropertyInfo instance AttrInfo DOMScreenColorDepthPropertyInfo where type AttrAllowedOps DOMScreenColorDepthPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMScreenColorDepthPropertyInfo = (~) () type AttrBaseTypeConstraint DOMScreenColorDepthPropertyInfo = DOMScreenK type AttrGetType DOMScreenColorDepthPropertyInfo = Word64 type AttrLabel DOMScreenColorDepthPropertyInfo = "DOMScreen::color-depth" attrGet _ = getDOMScreenColorDepth attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "height" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMScreenHeight :: (MonadIO m, DOMScreenK o) => o -> m Word64 getDOMScreenHeight obj = liftIO $ getObjectPropertyUInt64 obj "height" data DOMScreenHeightPropertyInfo instance AttrInfo DOMScreenHeightPropertyInfo where type AttrAllowedOps DOMScreenHeightPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMScreenHeightPropertyInfo = (~) () type AttrBaseTypeConstraint DOMScreenHeightPropertyInfo = DOMScreenK type AttrGetType DOMScreenHeightPropertyInfo = Word64 type AttrLabel DOMScreenHeightPropertyInfo = "DOMScreen::height" attrGet _ = getDOMScreenHeight attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "pixel-depth" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMScreenPixelDepth :: (MonadIO m, DOMScreenK o) => o -> m Word64 getDOMScreenPixelDepth obj = liftIO $ getObjectPropertyUInt64 obj "pixel-depth" data DOMScreenPixelDepthPropertyInfo instance AttrInfo DOMScreenPixelDepthPropertyInfo where type AttrAllowedOps DOMScreenPixelDepthPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMScreenPixelDepthPropertyInfo = (~) () type AttrBaseTypeConstraint DOMScreenPixelDepthPropertyInfo = DOMScreenK type AttrGetType DOMScreenPixelDepthPropertyInfo = Word64 type AttrLabel DOMScreenPixelDepthPropertyInfo = "DOMScreen::pixel-depth" attrGet _ = getDOMScreenPixelDepth attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "width" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMScreenWidth :: (MonadIO m, DOMScreenK o) => o -> m Word64 getDOMScreenWidth obj = liftIO $ getObjectPropertyUInt64 obj "width" data DOMScreenWidthPropertyInfo instance AttrInfo DOMScreenWidthPropertyInfo where type AttrAllowedOps DOMScreenWidthPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMScreenWidthPropertyInfo = (~) () type AttrBaseTypeConstraint DOMScreenWidthPropertyInfo = DOMScreenK type AttrGetType DOMScreenWidthPropertyInfo = Word64 type AttrLabel DOMScreenWidthPropertyInfo = "DOMScreen::width" attrGet _ = getDOMScreenWidth attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMScreen = '[ '("avail-height", DOMScreenAvailHeightPropertyInfo), '("avail-left", DOMScreenAvailLeftPropertyInfo), '("avail-top", DOMScreenAvailTopPropertyInfo), '("avail-width", DOMScreenAvailWidthPropertyInfo), '("color-depth", DOMScreenColorDepthPropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("height", DOMScreenHeightPropertyInfo), '("pixel-depth", DOMScreenPixelDepthPropertyInfo), '("width", DOMScreenWidthPropertyInfo)] -- VVV Prop "active-element" -- Type: TInterface "WebKit" "DOMElement" -- Flags: [PropertyReadable] getDOMShadowRootActiveElement :: (MonadIO m, DOMShadowRootK o) => o -> m DOMElement getDOMShadowRootActiveElement obj = liftIO $ getObjectPropertyObject obj "active-element" DOMElement data DOMShadowRootActiveElementPropertyInfo instance AttrInfo DOMShadowRootActiveElementPropertyInfo where type AttrAllowedOps DOMShadowRootActiveElementPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMShadowRootActiveElementPropertyInfo = (~) () type AttrBaseTypeConstraint DOMShadowRootActiveElementPropertyInfo = DOMShadowRootK type AttrGetType DOMShadowRootActiveElementPropertyInfo = DOMElement type AttrLabel DOMShadowRootActiveElementPropertyInfo = "DOMShadowRoot::active-element" attrGet _ = getDOMShadowRootActiveElement attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "apply-author-styles" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMShadowRootApplyAuthorStyles :: (MonadIO m, DOMShadowRootK o) => o -> m Bool getDOMShadowRootApplyAuthorStyles obj = liftIO $ getObjectPropertyBool obj "apply-author-styles" setDOMShadowRootApplyAuthorStyles :: (MonadIO m, DOMShadowRootK o) => o -> Bool -> m () setDOMShadowRootApplyAuthorStyles obj val = liftIO $ setObjectPropertyBool obj "apply-author-styles" val constructDOMShadowRootApplyAuthorStyles :: Bool -> IO ([Char], GValue) constructDOMShadowRootApplyAuthorStyles val = constructObjectPropertyBool "apply-author-styles" val data DOMShadowRootApplyAuthorStylesPropertyInfo instance AttrInfo DOMShadowRootApplyAuthorStylesPropertyInfo where type AttrAllowedOps DOMShadowRootApplyAuthorStylesPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMShadowRootApplyAuthorStylesPropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMShadowRootApplyAuthorStylesPropertyInfo = DOMShadowRootK type AttrGetType DOMShadowRootApplyAuthorStylesPropertyInfo = Bool type AttrLabel DOMShadowRootApplyAuthorStylesPropertyInfo = "DOMShadowRoot::apply-author-styles" attrGet _ = getDOMShadowRootApplyAuthorStyles attrSet _ = setDOMShadowRootApplyAuthorStyles attrConstruct _ = constructDOMShadowRootApplyAuthorStyles -- VVV Prop "inner-html" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMShadowRootInnerHtml :: (MonadIO m, DOMShadowRootK o) => o -> m T.Text getDOMShadowRootInnerHtml obj = liftIO $ getObjectPropertyString obj "inner-html" setDOMShadowRootInnerHtml :: (MonadIO m, DOMShadowRootK o) => o -> T.Text -> m () setDOMShadowRootInnerHtml obj val = liftIO $ setObjectPropertyString obj "inner-html" val constructDOMShadowRootInnerHtml :: T.Text -> IO ([Char], GValue) constructDOMShadowRootInnerHtml val = constructObjectPropertyString "inner-html" val data DOMShadowRootInnerHtmlPropertyInfo instance AttrInfo DOMShadowRootInnerHtmlPropertyInfo where type AttrAllowedOps DOMShadowRootInnerHtmlPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMShadowRootInnerHtmlPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMShadowRootInnerHtmlPropertyInfo = DOMShadowRootK type AttrGetType DOMShadowRootInnerHtmlPropertyInfo = T.Text type AttrLabel DOMShadowRootInnerHtmlPropertyInfo = "DOMShadowRoot::inner-html" attrGet _ = getDOMShadowRootInnerHtml attrSet _ = setDOMShadowRootInnerHtml attrConstruct _ = constructDOMShadowRootInnerHtml -- VVV Prop "reset-style-inheritance" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMShadowRootResetStyleInheritance :: (MonadIO m, DOMShadowRootK o) => o -> m Bool getDOMShadowRootResetStyleInheritance obj = liftIO $ getObjectPropertyBool obj "reset-style-inheritance" setDOMShadowRootResetStyleInheritance :: (MonadIO m, DOMShadowRootK o) => o -> Bool -> m () setDOMShadowRootResetStyleInheritance obj val = liftIO $ setObjectPropertyBool obj "reset-style-inheritance" val constructDOMShadowRootResetStyleInheritance :: Bool -> IO ([Char], GValue) constructDOMShadowRootResetStyleInheritance val = constructObjectPropertyBool "reset-style-inheritance" val data DOMShadowRootResetStyleInheritancePropertyInfo instance AttrInfo DOMShadowRootResetStyleInheritancePropertyInfo where type AttrAllowedOps DOMShadowRootResetStyleInheritancePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMShadowRootResetStyleInheritancePropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMShadowRootResetStyleInheritancePropertyInfo = DOMShadowRootK type AttrGetType DOMShadowRootResetStyleInheritancePropertyInfo = Bool type AttrLabel DOMShadowRootResetStyleInheritancePropertyInfo = "DOMShadowRoot::reset-style-inheritance" attrGet _ = getDOMShadowRootResetStyleInheritance attrSet _ = setDOMShadowRootResetStyleInheritance attrConstruct _ = constructDOMShadowRootResetStyleInheritance type instance AttributeList DOMShadowRoot = '[ '("active-element", DOMShadowRootActiveElementPropertyInfo), '("apply-author-styles", DOMShadowRootApplyAuthorStylesPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("inner-html", DOMShadowRootInnerHtmlPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("reset-style-inheritance", DOMShadowRootResetStyleInheritancePropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo)] -- VVV Prop "length" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMStorageLength :: (MonadIO m, DOMStorageK o) => o -> m Word64 getDOMStorageLength obj = liftIO $ getObjectPropertyUInt64 obj "length" data DOMStorageLengthPropertyInfo instance AttrInfo DOMStorageLengthPropertyInfo where type AttrAllowedOps DOMStorageLengthPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMStorageLengthPropertyInfo = (~) () type AttrBaseTypeConstraint DOMStorageLengthPropertyInfo = DOMStorageK type AttrGetType DOMStorageLengthPropertyInfo = Word64 type AttrLabel DOMStorageLengthPropertyInfo = "DOMStorage::length" attrGet _ = getDOMStorageLength attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMStorage = '[ '("core-object", DOMObjectCoreObjectPropertyInfo), '("length", DOMStorageLengthPropertyInfo)] type instance AttributeList DOMStorageInfo = '[ '("core-object", DOMObjectCoreObjectPropertyInfo)] type instance AttributeList DOMStorageQuota = '[ '("core-object", DOMObjectCoreObjectPropertyInfo)] -- VVV Prop "type" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMStyleMediaType :: (MonadIO m, DOMStyleMediaK o) => o -> m T.Text getDOMStyleMediaType obj = liftIO $ getObjectPropertyString obj "type" data DOMStyleMediaTypePropertyInfo instance AttrInfo DOMStyleMediaTypePropertyInfo where type AttrAllowedOps DOMStyleMediaTypePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMStyleMediaTypePropertyInfo = (~) () type AttrBaseTypeConstraint DOMStyleMediaTypePropertyInfo = DOMStyleMediaK type AttrGetType DOMStyleMediaTypePropertyInfo = T.Text type AttrLabel DOMStyleMediaTypePropertyInfo = "DOMStyleMedia::type" attrGet _ = getDOMStyleMediaType attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMStyleMedia = '[ '("core-object", DOMObjectCoreObjectPropertyInfo), '("type", DOMStyleMediaTypePropertyInfo)] -- VVV Prop "disabled" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMStyleSheetDisabled :: (MonadIO m, DOMStyleSheetK o) => o -> m Bool getDOMStyleSheetDisabled obj = liftIO $ getObjectPropertyBool obj "disabled" setDOMStyleSheetDisabled :: (MonadIO m, DOMStyleSheetK o) => o -> Bool -> m () setDOMStyleSheetDisabled obj val = liftIO $ setObjectPropertyBool obj "disabled" val constructDOMStyleSheetDisabled :: Bool -> IO ([Char], GValue) constructDOMStyleSheetDisabled val = constructObjectPropertyBool "disabled" val data DOMStyleSheetDisabledPropertyInfo instance AttrInfo DOMStyleSheetDisabledPropertyInfo where type AttrAllowedOps DOMStyleSheetDisabledPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMStyleSheetDisabledPropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMStyleSheetDisabledPropertyInfo = DOMStyleSheetK type AttrGetType DOMStyleSheetDisabledPropertyInfo = Bool type AttrLabel DOMStyleSheetDisabledPropertyInfo = "DOMStyleSheet::disabled" attrGet _ = getDOMStyleSheetDisabled attrSet _ = setDOMStyleSheetDisabled attrConstruct _ = constructDOMStyleSheetDisabled -- VVV Prop "href" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMStyleSheetHref :: (MonadIO m, DOMStyleSheetK o) => o -> m T.Text getDOMStyleSheetHref obj = liftIO $ getObjectPropertyString obj "href" data DOMStyleSheetHrefPropertyInfo instance AttrInfo DOMStyleSheetHrefPropertyInfo where type AttrAllowedOps DOMStyleSheetHrefPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMStyleSheetHrefPropertyInfo = (~) () type AttrBaseTypeConstraint DOMStyleSheetHrefPropertyInfo = DOMStyleSheetK type AttrGetType DOMStyleSheetHrefPropertyInfo = T.Text type AttrLabel DOMStyleSheetHrefPropertyInfo = "DOMStyleSheet::href" attrGet _ = getDOMStyleSheetHref attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "media" -- Type: TInterface "WebKit" "DOMMediaList" -- Flags: [PropertyReadable] getDOMStyleSheetMedia :: (MonadIO m, DOMStyleSheetK o) => o -> m DOMMediaList getDOMStyleSheetMedia obj = liftIO $ getObjectPropertyObject obj "media" DOMMediaList data DOMStyleSheetMediaPropertyInfo instance AttrInfo DOMStyleSheetMediaPropertyInfo where type AttrAllowedOps DOMStyleSheetMediaPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMStyleSheetMediaPropertyInfo = (~) () type AttrBaseTypeConstraint DOMStyleSheetMediaPropertyInfo = DOMStyleSheetK type AttrGetType DOMStyleSheetMediaPropertyInfo = DOMMediaList type AttrLabel DOMStyleSheetMediaPropertyInfo = "DOMStyleSheet::media" attrGet _ = getDOMStyleSheetMedia attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "owner-node" -- Type: TInterface "WebKit" "DOMNode" -- Flags: [PropertyReadable] getDOMStyleSheetOwnerNode :: (MonadIO m, DOMStyleSheetK o) => o -> m DOMNode getDOMStyleSheetOwnerNode obj = liftIO $ getObjectPropertyObject obj "owner-node" DOMNode data DOMStyleSheetOwnerNodePropertyInfo instance AttrInfo DOMStyleSheetOwnerNodePropertyInfo where type AttrAllowedOps DOMStyleSheetOwnerNodePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMStyleSheetOwnerNodePropertyInfo = (~) () type AttrBaseTypeConstraint DOMStyleSheetOwnerNodePropertyInfo = DOMStyleSheetK type AttrGetType DOMStyleSheetOwnerNodePropertyInfo = DOMNode type AttrLabel DOMStyleSheetOwnerNodePropertyInfo = "DOMStyleSheet::owner-node" attrGet _ = getDOMStyleSheetOwnerNode attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "parent-style-sheet" -- Type: TInterface "WebKit" "DOMStyleSheet" -- Flags: [PropertyReadable] getDOMStyleSheetParentStyleSheet :: (MonadIO m, DOMStyleSheetK o) => o -> m DOMStyleSheet getDOMStyleSheetParentStyleSheet obj = liftIO $ getObjectPropertyObject obj "parent-style-sheet" DOMStyleSheet data DOMStyleSheetParentStyleSheetPropertyInfo instance AttrInfo DOMStyleSheetParentStyleSheetPropertyInfo where type AttrAllowedOps DOMStyleSheetParentStyleSheetPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMStyleSheetParentStyleSheetPropertyInfo = (~) () type AttrBaseTypeConstraint DOMStyleSheetParentStyleSheetPropertyInfo = DOMStyleSheetK type AttrGetType DOMStyleSheetParentStyleSheetPropertyInfo = DOMStyleSheet type AttrLabel DOMStyleSheetParentStyleSheetPropertyInfo = "DOMStyleSheet::parent-style-sheet" attrGet _ = getDOMStyleSheetParentStyleSheet attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "title" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMStyleSheetTitle :: (MonadIO m, DOMStyleSheetK o) => o -> m T.Text getDOMStyleSheetTitle obj = liftIO $ getObjectPropertyString obj "title" data DOMStyleSheetTitlePropertyInfo instance AttrInfo DOMStyleSheetTitlePropertyInfo where type AttrAllowedOps DOMStyleSheetTitlePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMStyleSheetTitlePropertyInfo = (~) () type AttrBaseTypeConstraint DOMStyleSheetTitlePropertyInfo = DOMStyleSheetK type AttrGetType DOMStyleSheetTitlePropertyInfo = T.Text type AttrLabel DOMStyleSheetTitlePropertyInfo = "DOMStyleSheet::title" attrGet _ = getDOMStyleSheetTitle attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "type" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMStyleSheetType :: (MonadIO m, DOMStyleSheetK o) => o -> m T.Text getDOMStyleSheetType obj = liftIO $ getObjectPropertyString obj "type" data DOMStyleSheetTypePropertyInfo instance AttrInfo DOMStyleSheetTypePropertyInfo where type AttrAllowedOps DOMStyleSheetTypePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMStyleSheetTypePropertyInfo = (~) () type AttrBaseTypeConstraint DOMStyleSheetTypePropertyInfo = DOMStyleSheetK type AttrGetType DOMStyleSheetTypePropertyInfo = T.Text type AttrLabel DOMStyleSheetTypePropertyInfo = "DOMStyleSheet::type" attrGet _ = getDOMStyleSheetType attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMStyleSheet = '[ '("core-object", DOMObjectCoreObjectPropertyInfo), '("disabled", DOMStyleSheetDisabledPropertyInfo), '("href", DOMStyleSheetHrefPropertyInfo), '("media", DOMStyleSheetMediaPropertyInfo), '("owner-node", DOMStyleSheetOwnerNodePropertyInfo), '("parent-style-sheet", DOMStyleSheetParentStyleSheetPropertyInfo), '("title", DOMStyleSheetTitlePropertyInfo), '("type", DOMStyleSheetTypePropertyInfo)] -- VVV Prop "length" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMStyleSheetListLength :: (MonadIO m, DOMStyleSheetListK o) => o -> m Word64 getDOMStyleSheetListLength obj = liftIO $ getObjectPropertyUInt64 obj "length" data DOMStyleSheetListLengthPropertyInfo instance AttrInfo DOMStyleSheetListLengthPropertyInfo where type AttrAllowedOps DOMStyleSheetListLengthPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMStyleSheetListLengthPropertyInfo = (~) () type AttrBaseTypeConstraint DOMStyleSheetListLengthPropertyInfo = DOMStyleSheetListK type AttrGetType DOMStyleSheetListLengthPropertyInfo = Word64 type AttrLabel DOMStyleSheetListLengthPropertyInfo = "DOMStyleSheetList::length" attrGet _ = getDOMStyleSheetListLength attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMStyleSheetList = '[ '("core-object", DOMObjectCoreObjectPropertyInfo), '("length", DOMStyleSheetListLengthPropertyInfo)] -- VVV Prop "whole-text" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMTextWholeText :: (MonadIO m, DOMTextK o) => o -> m T.Text getDOMTextWholeText obj = liftIO $ getObjectPropertyString obj "whole-text" data DOMTextWholeTextPropertyInfo instance AttrInfo DOMTextWholeTextPropertyInfo where type AttrAllowedOps DOMTextWholeTextPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMTextWholeTextPropertyInfo = (~) () type AttrBaseTypeConstraint DOMTextWholeTextPropertyInfo = DOMTextK type AttrGetType DOMTextWholeTextPropertyInfo = T.Text type AttrLabel DOMTextWholeTextPropertyInfo = "DOMText::whole-text" attrGet _ = getDOMTextWholeText attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMText = '[ '("base-uri", DOMNodeBaseUriPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("data", DOMCharacterDataDataPropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("length", DOMCharacterDataLengthPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("whole-text", DOMTextWholeTextPropertyInfo)] -- VVV Prop "active-cues" -- Type: TInterface "WebKit" "DOMTextTrackCueList" -- Flags: [PropertyReadable] getDOMTextTrackActiveCues :: (MonadIO m, DOMTextTrackK o) => o -> m DOMTextTrackCueList getDOMTextTrackActiveCues obj = liftIO $ getObjectPropertyObject obj "active-cues" DOMTextTrackCueList data DOMTextTrackActiveCuesPropertyInfo instance AttrInfo DOMTextTrackActiveCuesPropertyInfo where type AttrAllowedOps DOMTextTrackActiveCuesPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMTextTrackActiveCuesPropertyInfo = (~) () type AttrBaseTypeConstraint DOMTextTrackActiveCuesPropertyInfo = DOMTextTrackK type AttrGetType DOMTextTrackActiveCuesPropertyInfo = DOMTextTrackCueList type AttrLabel DOMTextTrackActiveCuesPropertyInfo = "DOMTextTrack::active-cues" attrGet _ = getDOMTextTrackActiveCues attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "cues" -- Type: TInterface "WebKit" "DOMTextTrackCueList" -- Flags: [PropertyReadable] getDOMTextTrackCues :: (MonadIO m, DOMTextTrackK o) => o -> m DOMTextTrackCueList getDOMTextTrackCues obj = liftIO $ getObjectPropertyObject obj "cues" DOMTextTrackCueList data DOMTextTrackCuesPropertyInfo instance AttrInfo DOMTextTrackCuesPropertyInfo where type AttrAllowedOps DOMTextTrackCuesPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMTextTrackCuesPropertyInfo = (~) () type AttrBaseTypeConstraint DOMTextTrackCuesPropertyInfo = DOMTextTrackK type AttrGetType DOMTextTrackCuesPropertyInfo = DOMTextTrackCueList type AttrLabel DOMTextTrackCuesPropertyInfo = "DOMTextTrack::cues" attrGet _ = getDOMTextTrackCues attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "id" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMTextTrackId :: (MonadIO m, DOMTextTrackK o) => o -> m T.Text getDOMTextTrackId obj = liftIO $ getObjectPropertyString obj "id" data DOMTextTrackIdPropertyInfo instance AttrInfo DOMTextTrackIdPropertyInfo where type AttrAllowedOps DOMTextTrackIdPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMTextTrackIdPropertyInfo = (~) () type AttrBaseTypeConstraint DOMTextTrackIdPropertyInfo = DOMTextTrackK type AttrGetType DOMTextTrackIdPropertyInfo = T.Text type AttrLabel DOMTextTrackIdPropertyInfo = "DOMTextTrack::id" attrGet _ = getDOMTextTrackId attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "kind" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMTextTrackKind :: (MonadIO m, DOMTextTrackK o) => o -> m T.Text getDOMTextTrackKind obj = liftIO $ getObjectPropertyString obj "kind" data DOMTextTrackKindPropertyInfo instance AttrInfo DOMTextTrackKindPropertyInfo where type AttrAllowedOps DOMTextTrackKindPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMTextTrackKindPropertyInfo = (~) () type AttrBaseTypeConstraint DOMTextTrackKindPropertyInfo = DOMTextTrackK type AttrGetType DOMTextTrackKindPropertyInfo = T.Text type AttrLabel DOMTextTrackKindPropertyInfo = "DOMTextTrack::kind" attrGet _ = getDOMTextTrackKind attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "label" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMTextTrackLabel :: (MonadIO m, DOMTextTrackK o) => o -> m T.Text getDOMTextTrackLabel obj = liftIO $ getObjectPropertyString obj "label" data DOMTextTrackLabelPropertyInfo instance AttrInfo DOMTextTrackLabelPropertyInfo where type AttrAllowedOps DOMTextTrackLabelPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMTextTrackLabelPropertyInfo = (~) () type AttrBaseTypeConstraint DOMTextTrackLabelPropertyInfo = DOMTextTrackK type AttrGetType DOMTextTrackLabelPropertyInfo = T.Text type AttrLabel DOMTextTrackLabelPropertyInfo = "DOMTextTrack::label" attrGet _ = getDOMTextTrackLabel attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "language" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMTextTrackLanguage :: (MonadIO m, DOMTextTrackK o) => o -> m T.Text getDOMTextTrackLanguage obj = liftIO $ getObjectPropertyString obj "language" data DOMTextTrackLanguagePropertyInfo instance AttrInfo DOMTextTrackLanguagePropertyInfo where type AttrAllowedOps DOMTextTrackLanguagePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMTextTrackLanguagePropertyInfo = (~) () type AttrBaseTypeConstraint DOMTextTrackLanguagePropertyInfo = DOMTextTrackK type AttrGetType DOMTextTrackLanguagePropertyInfo = T.Text type AttrLabel DOMTextTrackLanguagePropertyInfo = "DOMTextTrack::language" attrGet _ = getDOMTextTrackLanguage attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "mode" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMTextTrackMode :: (MonadIO m, DOMTextTrackK o) => o -> m T.Text getDOMTextTrackMode obj = liftIO $ getObjectPropertyString obj "mode" setDOMTextTrackMode :: (MonadIO m, DOMTextTrackK o) => o -> T.Text -> m () setDOMTextTrackMode obj val = liftIO $ setObjectPropertyString obj "mode" val constructDOMTextTrackMode :: T.Text -> IO ([Char], GValue) constructDOMTextTrackMode val = constructObjectPropertyString "mode" val data DOMTextTrackModePropertyInfo instance AttrInfo DOMTextTrackModePropertyInfo where type AttrAllowedOps DOMTextTrackModePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMTextTrackModePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMTextTrackModePropertyInfo = DOMTextTrackK type AttrGetType DOMTextTrackModePropertyInfo = T.Text type AttrLabel DOMTextTrackModePropertyInfo = "DOMTextTrack::mode" attrGet _ = getDOMTextTrackMode attrSet _ = setDOMTextTrackMode attrConstruct _ = constructDOMTextTrackMode type instance AttributeList DOMTextTrack = '[ '("active-cues", DOMTextTrackActiveCuesPropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("cues", DOMTextTrackCuesPropertyInfo), '("id", DOMTextTrackIdPropertyInfo), '("kind", DOMTextTrackKindPropertyInfo), '("label", DOMTextTrackLabelPropertyInfo), '("language", DOMTextTrackLanguagePropertyInfo), '("mode", DOMTextTrackModePropertyInfo)] -- VVV Prop "align" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMTextTrackCueAlign :: (MonadIO m, DOMTextTrackCueK o) => o -> m T.Text getDOMTextTrackCueAlign obj = liftIO $ getObjectPropertyString obj "align" setDOMTextTrackCueAlign :: (MonadIO m, DOMTextTrackCueK o) => o -> T.Text -> m () setDOMTextTrackCueAlign obj val = liftIO $ setObjectPropertyString obj "align" val constructDOMTextTrackCueAlign :: T.Text -> IO ([Char], GValue) constructDOMTextTrackCueAlign val = constructObjectPropertyString "align" val data DOMTextTrackCueAlignPropertyInfo instance AttrInfo DOMTextTrackCueAlignPropertyInfo where type AttrAllowedOps DOMTextTrackCueAlignPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMTextTrackCueAlignPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMTextTrackCueAlignPropertyInfo = DOMTextTrackCueK type AttrGetType DOMTextTrackCueAlignPropertyInfo = T.Text type AttrLabel DOMTextTrackCueAlignPropertyInfo = "DOMTextTrackCue::align" attrGet _ = getDOMTextTrackCueAlign attrSet _ = setDOMTextTrackCueAlign attrConstruct _ = constructDOMTextTrackCueAlign -- VVV Prop "end-time" -- Type: TBasicType TDouble -- Flags: [PropertyReadable,PropertyWritable] getDOMTextTrackCueEndTime :: (MonadIO m, DOMTextTrackCueK o) => o -> m Double getDOMTextTrackCueEndTime obj = liftIO $ getObjectPropertyDouble obj "end-time" setDOMTextTrackCueEndTime :: (MonadIO m, DOMTextTrackCueK o) => o -> Double -> m () setDOMTextTrackCueEndTime obj val = liftIO $ setObjectPropertyDouble obj "end-time" val constructDOMTextTrackCueEndTime :: Double -> IO ([Char], GValue) constructDOMTextTrackCueEndTime val = constructObjectPropertyDouble "end-time" val data DOMTextTrackCueEndTimePropertyInfo instance AttrInfo DOMTextTrackCueEndTimePropertyInfo where type AttrAllowedOps DOMTextTrackCueEndTimePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMTextTrackCueEndTimePropertyInfo = (~) Double type AttrBaseTypeConstraint DOMTextTrackCueEndTimePropertyInfo = DOMTextTrackCueK type AttrGetType DOMTextTrackCueEndTimePropertyInfo = Double type AttrLabel DOMTextTrackCueEndTimePropertyInfo = "DOMTextTrackCue::end-time" attrGet _ = getDOMTextTrackCueEndTime attrSet _ = setDOMTextTrackCueEndTime attrConstruct _ = constructDOMTextTrackCueEndTime -- VVV Prop "id" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMTextTrackCueId :: (MonadIO m, DOMTextTrackCueK o) => o -> m T.Text getDOMTextTrackCueId obj = liftIO $ getObjectPropertyString obj "id" setDOMTextTrackCueId :: (MonadIO m, DOMTextTrackCueK o) => o -> T.Text -> m () setDOMTextTrackCueId obj val = liftIO $ setObjectPropertyString obj "id" val constructDOMTextTrackCueId :: T.Text -> IO ([Char], GValue) constructDOMTextTrackCueId val = constructObjectPropertyString "id" val data DOMTextTrackCueIdPropertyInfo instance AttrInfo DOMTextTrackCueIdPropertyInfo where type AttrAllowedOps DOMTextTrackCueIdPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMTextTrackCueIdPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMTextTrackCueIdPropertyInfo = DOMTextTrackCueK type AttrGetType DOMTextTrackCueIdPropertyInfo = T.Text type AttrLabel DOMTextTrackCueIdPropertyInfo = "DOMTextTrackCue::id" attrGet _ = getDOMTextTrackCueId attrSet _ = setDOMTextTrackCueId attrConstruct _ = constructDOMTextTrackCueId -- VVV Prop "line" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable,PropertyWritable] getDOMTextTrackCueLine :: (MonadIO m, DOMTextTrackCueK o) => o -> m Int64 getDOMTextTrackCueLine obj = liftIO $ getObjectPropertyInt64 obj "line" setDOMTextTrackCueLine :: (MonadIO m, DOMTextTrackCueK o) => o -> Int64 -> m () setDOMTextTrackCueLine obj val = liftIO $ setObjectPropertyInt64 obj "line" val constructDOMTextTrackCueLine :: Int64 -> IO ([Char], GValue) constructDOMTextTrackCueLine val = constructObjectPropertyInt64 "line" val data DOMTextTrackCueLinePropertyInfo instance AttrInfo DOMTextTrackCueLinePropertyInfo where type AttrAllowedOps DOMTextTrackCueLinePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMTextTrackCueLinePropertyInfo = (~) Int64 type AttrBaseTypeConstraint DOMTextTrackCueLinePropertyInfo = DOMTextTrackCueK type AttrGetType DOMTextTrackCueLinePropertyInfo = Int64 type AttrLabel DOMTextTrackCueLinePropertyInfo = "DOMTextTrackCue::line" attrGet _ = getDOMTextTrackCueLine attrSet _ = setDOMTextTrackCueLine attrConstruct _ = constructDOMTextTrackCueLine -- VVV Prop "pause-on-exit" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMTextTrackCuePauseOnExit :: (MonadIO m, DOMTextTrackCueK o) => o -> m Bool getDOMTextTrackCuePauseOnExit obj = liftIO $ getObjectPropertyBool obj "pause-on-exit" setDOMTextTrackCuePauseOnExit :: (MonadIO m, DOMTextTrackCueK o) => o -> Bool -> m () setDOMTextTrackCuePauseOnExit obj val = liftIO $ setObjectPropertyBool obj "pause-on-exit" val constructDOMTextTrackCuePauseOnExit :: Bool -> IO ([Char], GValue) constructDOMTextTrackCuePauseOnExit val = constructObjectPropertyBool "pause-on-exit" val data DOMTextTrackCuePauseOnExitPropertyInfo instance AttrInfo DOMTextTrackCuePauseOnExitPropertyInfo where type AttrAllowedOps DOMTextTrackCuePauseOnExitPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMTextTrackCuePauseOnExitPropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMTextTrackCuePauseOnExitPropertyInfo = DOMTextTrackCueK type AttrGetType DOMTextTrackCuePauseOnExitPropertyInfo = Bool type AttrLabel DOMTextTrackCuePauseOnExitPropertyInfo = "DOMTextTrackCue::pause-on-exit" attrGet _ = getDOMTextTrackCuePauseOnExit attrSet _ = setDOMTextTrackCuePauseOnExit attrConstruct _ = constructDOMTextTrackCuePauseOnExit -- VVV Prop "position" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable,PropertyWritable] getDOMTextTrackCuePosition :: (MonadIO m, DOMTextTrackCueK o) => o -> m Int64 getDOMTextTrackCuePosition obj = liftIO $ getObjectPropertyInt64 obj "position" setDOMTextTrackCuePosition :: (MonadIO m, DOMTextTrackCueK o) => o -> Int64 -> m () setDOMTextTrackCuePosition obj val = liftIO $ setObjectPropertyInt64 obj "position" val constructDOMTextTrackCuePosition :: Int64 -> IO ([Char], GValue) constructDOMTextTrackCuePosition val = constructObjectPropertyInt64 "position" val data DOMTextTrackCuePositionPropertyInfo instance AttrInfo DOMTextTrackCuePositionPropertyInfo where type AttrAllowedOps DOMTextTrackCuePositionPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMTextTrackCuePositionPropertyInfo = (~) Int64 type AttrBaseTypeConstraint DOMTextTrackCuePositionPropertyInfo = DOMTextTrackCueK type AttrGetType DOMTextTrackCuePositionPropertyInfo = Int64 type AttrLabel DOMTextTrackCuePositionPropertyInfo = "DOMTextTrackCue::position" attrGet _ = getDOMTextTrackCuePosition attrSet _ = setDOMTextTrackCuePosition attrConstruct _ = constructDOMTextTrackCuePosition -- VVV Prop "size" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable,PropertyWritable] getDOMTextTrackCueSize :: (MonadIO m, DOMTextTrackCueK o) => o -> m Int64 getDOMTextTrackCueSize obj = liftIO $ getObjectPropertyInt64 obj "size" setDOMTextTrackCueSize :: (MonadIO m, DOMTextTrackCueK o) => o -> Int64 -> m () setDOMTextTrackCueSize obj val = liftIO $ setObjectPropertyInt64 obj "size" val constructDOMTextTrackCueSize :: Int64 -> IO ([Char], GValue) constructDOMTextTrackCueSize val = constructObjectPropertyInt64 "size" val data DOMTextTrackCueSizePropertyInfo instance AttrInfo DOMTextTrackCueSizePropertyInfo where type AttrAllowedOps DOMTextTrackCueSizePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMTextTrackCueSizePropertyInfo = (~) Int64 type AttrBaseTypeConstraint DOMTextTrackCueSizePropertyInfo = DOMTextTrackCueK type AttrGetType DOMTextTrackCueSizePropertyInfo = Int64 type AttrLabel DOMTextTrackCueSizePropertyInfo = "DOMTextTrackCue::size" attrGet _ = getDOMTextTrackCueSize attrSet _ = setDOMTextTrackCueSize attrConstruct _ = constructDOMTextTrackCueSize -- VVV Prop "snap-to-lines" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMTextTrackCueSnapToLines :: (MonadIO m, DOMTextTrackCueK o) => o -> m Bool getDOMTextTrackCueSnapToLines obj = liftIO $ getObjectPropertyBool obj "snap-to-lines" setDOMTextTrackCueSnapToLines :: (MonadIO m, DOMTextTrackCueK o) => o -> Bool -> m () setDOMTextTrackCueSnapToLines obj val = liftIO $ setObjectPropertyBool obj "snap-to-lines" val constructDOMTextTrackCueSnapToLines :: Bool -> IO ([Char], GValue) constructDOMTextTrackCueSnapToLines val = constructObjectPropertyBool "snap-to-lines" val data DOMTextTrackCueSnapToLinesPropertyInfo instance AttrInfo DOMTextTrackCueSnapToLinesPropertyInfo where type AttrAllowedOps DOMTextTrackCueSnapToLinesPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMTextTrackCueSnapToLinesPropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMTextTrackCueSnapToLinesPropertyInfo = DOMTextTrackCueK type AttrGetType DOMTextTrackCueSnapToLinesPropertyInfo = Bool type AttrLabel DOMTextTrackCueSnapToLinesPropertyInfo = "DOMTextTrackCue::snap-to-lines" attrGet _ = getDOMTextTrackCueSnapToLines attrSet _ = setDOMTextTrackCueSnapToLines attrConstruct _ = constructDOMTextTrackCueSnapToLines -- VVV Prop "start-time" -- Type: TBasicType TDouble -- Flags: [PropertyReadable,PropertyWritable] getDOMTextTrackCueStartTime :: (MonadIO m, DOMTextTrackCueK o) => o -> m Double getDOMTextTrackCueStartTime obj = liftIO $ getObjectPropertyDouble obj "start-time" setDOMTextTrackCueStartTime :: (MonadIO m, DOMTextTrackCueK o) => o -> Double -> m () setDOMTextTrackCueStartTime obj val = liftIO $ setObjectPropertyDouble obj "start-time" val constructDOMTextTrackCueStartTime :: Double -> IO ([Char], GValue) constructDOMTextTrackCueStartTime val = constructObjectPropertyDouble "start-time" val data DOMTextTrackCueStartTimePropertyInfo instance AttrInfo DOMTextTrackCueStartTimePropertyInfo where type AttrAllowedOps DOMTextTrackCueStartTimePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMTextTrackCueStartTimePropertyInfo = (~) Double type AttrBaseTypeConstraint DOMTextTrackCueStartTimePropertyInfo = DOMTextTrackCueK type AttrGetType DOMTextTrackCueStartTimePropertyInfo = Double type AttrLabel DOMTextTrackCueStartTimePropertyInfo = "DOMTextTrackCue::start-time" attrGet _ = getDOMTextTrackCueStartTime attrSet _ = setDOMTextTrackCueStartTime attrConstruct _ = constructDOMTextTrackCueStartTime -- VVV Prop "text" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMTextTrackCueText :: (MonadIO m, DOMTextTrackCueK o) => o -> m T.Text getDOMTextTrackCueText obj = liftIO $ getObjectPropertyString obj "text" setDOMTextTrackCueText :: (MonadIO m, DOMTextTrackCueK o) => o -> T.Text -> m () setDOMTextTrackCueText obj val = liftIO $ setObjectPropertyString obj "text" val constructDOMTextTrackCueText :: T.Text -> IO ([Char], GValue) constructDOMTextTrackCueText val = constructObjectPropertyString "text" val data DOMTextTrackCueTextPropertyInfo instance AttrInfo DOMTextTrackCueTextPropertyInfo where type AttrAllowedOps DOMTextTrackCueTextPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMTextTrackCueTextPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMTextTrackCueTextPropertyInfo = DOMTextTrackCueK type AttrGetType DOMTextTrackCueTextPropertyInfo = T.Text type AttrLabel DOMTextTrackCueTextPropertyInfo = "DOMTextTrackCue::text" attrGet _ = getDOMTextTrackCueText attrSet _ = setDOMTextTrackCueText attrConstruct _ = constructDOMTextTrackCueText -- VVV Prop "track" -- Type: TInterface "WebKit" "DOMTextTrack" -- Flags: [PropertyReadable] getDOMTextTrackCueTrack :: (MonadIO m, DOMTextTrackCueK o) => o -> m DOMTextTrack getDOMTextTrackCueTrack obj = liftIO $ getObjectPropertyObject obj "track" DOMTextTrack data DOMTextTrackCueTrackPropertyInfo instance AttrInfo DOMTextTrackCueTrackPropertyInfo where type AttrAllowedOps DOMTextTrackCueTrackPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMTextTrackCueTrackPropertyInfo = (~) () type AttrBaseTypeConstraint DOMTextTrackCueTrackPropertyInfo = DOMTextTrackCueK type AttrGetType DOMTextTrackCueTrackPropertyInfo = DOMTextTrack type AttrLabel DOMTextTrackCueTrackPropertyInfo = "DOMTextTrackCue::track" attrGet _ = getDOMTextTrackCueTrack attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "vertical" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDOMTextTrackCueVertical :: (MonadIO m, DOMTextTrackCueK o) => o -> m T.Text getDOMTextTrackCueVertical obj = liftIO $ getObjectPropertyString obj "vertical" setDOMTextTrackCueVertical :: (MonadIO m, DOMTextTrackCueK o) => o -> T.Text -> m () setDOMTextTrackCueVertical obj val = liftIO $ setObjectPropertyString obj "vertical" val constructDOMTextTrackCueVertical :: T.Text -> IO ([Char], GValue) constructDOMTextTrackCueVertical val = constructObjectPropertyString "vertical" val data DOMTextTrackCueVerticalPropertyInfo instance AttrInfo DOMTextTrackCueVerticalPropertyInfo where type AttrAllowedOps DOMTextTrackCueVerticalPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMTextTrackCueVerticalPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DOMTextTrackCueVerticalPropertyInfo = DOMTextTrackCueK type AttrGetType DOMTextTrackCueVerticalPropertyInfo = T.Text type AttrLabel DOMTextTrackCueVerticalPropertyInfo = "DOMTextTrackCue::vertical" attrGet _ = getDOMTextTrackCueVertical attrSet _ = setDOMTextTrackCueVertical attrConstruct _ = constructDOMTextTrackCueVertical type instance AttributeList DOMTextTrackCue = '[ '("align", DOMTextTrackCueAlignPropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("end-time", DOMTextTrackCueEndTimePropertyInfo), '("id", DOMTextTrackCueIdPropertyInfo), '("line", DOMTextTrackCueLinePropertyInfo), '("pause-on-exit", DOMTextTrackCuePauseOnExitPropertyInfo), '("position", DOMTextTrackCuePositionPropertyInfo), '("size", DOMTextTrackCueSizePropertyInfo), '("snap-to-lines", DOMTextTrackCueSnapToLinesPropertyInfo), '("start-time", DOMTextTrackCueStartTimePropertyInfo), '("text", DOMTextTrackCueTextPropertyInfo), '("track", DOMTextTrackCueTrackPropertyInfo), '("vertical", DOMTextTrackCueVerticalPropertyInfo)] -- VVV Prop "length" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMTextTrackCueListLength :: (MonadIO m, DOMTextTrackCueListK o) => o -> m Word64 getDOMTextTrackCueListLength obj = liftIO $ getObjectPropertyUInt64 obj "length" data DOMTextTrackCueListLengthPropertyInfo instance AttrInfo DOMTextTrackCueListLengthPropertyInfo where type AttrAllowedOps DOMTextTrackCueListLengthPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMTextTrackCueListLengthPropertyInfo = (~) () type AttrBaseTypeConstraint DOMTextTrackCueListLengthPropertyInfo = DOMTextTrackCueListK type AttrGetType DOMTextTrackCueListLengthPropertyInfo = Word64 type AttrLabel DOMTextTrackCueListLengthPropertyInfo = "DOMTextTrackCueList::length" attrGet _ = getDOMTextTrackCueListLength attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMTextTrackCueList = '[ '("core-object", DOMObjectCoreObjectPropertyInfo), '("length", DOMTextTrackCueListLengthPropertyInfo)] -- VVV Prop "length" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMTextTrackListLength :: (MonadIO m, DOMTextTrackListK o) => o -> m Word64 getDOMTextTrackListLength obj = liftIO $ getObjectPropertyUInt64 obj "length" data DOMTextTrackListLengthPropertyInfo instance AttrInfo DOMTextTrackListLengthPropertyInfo where type AttrAllowedOps DOMTextTrackListLengthPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMTextTrackListLengthPropertyInfo = (~) () type AttrBaseTypeConstraint DOMTextTrackListLengthPropertyInfo = DOMTextTrackListK type AttrGetType DOMTextTrackListLengthPropertyInfo = Word64 type AttrLabel DOMTextTrackListLengthPropertyInfo = "DOMTextTrackList::length" attrGet _ = getDOMTextTrackListLength attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMTextTrackList = '[ '("core-object", DOMObjectCoreObjectPropertyInfo), '("length", DOMTextTrackListLengthPropertyInfo)] -- VVV Prop "length" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMTimeRangesLength :: (MonadIO m, DOMTimeRangesK o) => o -> m Word64 getDOMTimeRangesLength obj = liftIO $ getObjectPropertyUInt64 obj "length" data DOMTimeRangesLengthPropertyInfo instance AttrInfo DOMTimeRangesLengthPropertyInfo where type AttrAllowedOps DOMTimeRangesLengthPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMTimeRangesLengthPropertyInfo = (~) () type AttrBaseTypeConstraint DOMTimeRangesLengthPropertyInfo = DOMTimeRangesK type AttrGetType DOMTimeRangesLengthPropertyInfo = Word64 type AttrLabel DOMTimeRangesLengthPropertyInfo = "DOMTimeRanges::length" attrGet _ = getDOMTimeRangesLength attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMTimeRanges = '[ '("core-object", DOMObjectCoreObjectPropertyInfo), '("length", DOMTimeRangesLengthPropertyInfo)] -- VVV Prop "client-x" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMTouchClientX :: (MonadIO m, DOMTouchK o) => o -> m Int64 getDOMTouchClientX obj = liftIO $ getObjectPropertyInt64 obj "client-x" data DOMTouchClientXPropertyInfo instance AttrInfo DOMTouchClientXPropertyInfo where type AttrAllowedOps DOMTouchClientXPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMTouchClientXPropertyInfo = (~) () type AttrBaseTypeConstraint DOMTouchClientXPropertyInfo = DOMTouchK type AttrGetType DOMTouchClientXPropertyInfo = Int64 type AttrLabel DOMTouchClientXPropertyInfo = "DOMTouch::client-x" attrGet _ = getDOMTouchClientX attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "client-y" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMTouchClientY :: (MonadIO m, DOMTouchK o) => o -> m Int64 getDOMTouchClientY obj = liftIO $ getObjectPropertyInt64 obj "client-y" data DOMTouchClientYPropertyInfo instance AttrInfo DOMTouchClientYPropertyInfo where type AttrAllowedOps DOMTouchClientYPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMTouchClientYPropertyInfo = (~) () type AttrBaseTypeConstraint DOMTouchClientYPropertyInfo = DOMTouchK type AttrGetType DOMTouchClientYPropertyInfo = Int64 type AttrLabel DOMTouchClientYPropertyInfo = "DOMTouch::client-y" attrGet _ = getDOMTouchClientY attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "identifier" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMTouchIdentifier :: (MonadIO m, DOMTouchK o) => o -> m Word64 getDOMTouchIdentifier obj = liftIO $ getObjectPropertyUInt64 obj "identifier" data DOMTouchIdentifierPropertyInfo instance AttrInfo DOMTouchIdentifierPropertyInfo where type AttrAllowedOps DOMTouchIdentifierPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMTouchIdentifierPropertyInfo = (~) () type AttrBaseTypeConstraint DOMTouchIdentifierPropertyInfo = DOMTouchK type AttrGetType DOMTouchIdentifierPropertyInfo = Word64 type AttrLabel DOMTouchIdentifierPropertyInfo = "DOMTouch::identifier" attrGet _ = getDOMTouchIdentifier attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "page-x" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMTouchPageX :: (MonadIO m, DOMTouchK o) => o -> m Int64 getDOMTouchPageX obj = liftIO $ getObjectPropertyInt64 obj "page-x" data DOMTouchPageXPropertyInfo instance AttrInfo DOMTouchPageXPropertyInfo where type AttrAllowedOps DOMTouchPageXPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMTouchPageXPropertyInfo = (~) () type AttrBaseTypeConstraint DOMTouchPageXPropertyInfo = DOMTouchK type AttrGetType DOMTouchPageXPropertyInfo = Int64 type AttrLabel DOMTouchPageXPropertyInfo = "DOMTouch::page-x" attrGet _ = getDOMTouchPageX attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "page-y" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMTouchPageY :: (MonadIO m, DOMTouchK o) => o -> m Int64 getDOMTouchPageY obj = liftIO $ getObjectPropertyInt64 obj "page-y" data DOMTouchPageYPropertyInfo instance AttrInfo DOMTouchPageYPropertyInfo where type AttrAllowedOps DOMTouchPageYPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMTouchPageYPropertyInfo = (~) () type AttrBaseTypeConstraint DOMTouchPageYPropertyInfo = DOMTouchK type AttrGetType DOMTouchPageYPropertyInfo = Int64 type AttrLabel DOMTouchPageYPropertyInfo = "DOMTouch::page-y" attrGet _ = getDOMTouchPageY attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "screen-x" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMTouchScreenX :: (MonadIO m, DOMTouchK o) => o -> m Int64 getDOMTouchScreenX obj = liftIO $ getObjectPropertyInt64 obj "screen-x" data DOMTouchScreenXPropertyInfo instance AttrInfo DOMTouchScreenXPropertyInfo where type AttrAllowedOps DOMTouchScreenXPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMTouchScreenXPropertyInfo = (~) () type AttrBaseTypeConstraint DOMTouchScreenXPropertyInfo = DOMTouchK type AttrGetType DOMTouchScreenXPropertyInfo = Int64 type AttrLabel DOMTouchScreenXPropertyInfo = "DOMTouch::screen-x" attrGet _ = getDOMTouchScreenX attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "screen-y" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMTouchScreenY :: (MonadIO m, DOMTouchK o) => o -> m Int64 getDOMTouchScreenY obj = liftIO $ getObjectPropertyInt64 obj "screen-y" data DOMTouchScreenYPropertyInfo instance AttrInfo DOMTouchScreenYPropertyInfo where type AttrAllowedOps DOMTouchScreenYPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMTouchScreenYPropertyInfo = (~) () type AttrBaseTypeConstraint DOMTouchScreenYPropertyInfo = DOMTouchK type AttrGetType DOMTouchScreenYPropertyInfo = Int64 type AttrLabel DOMTouchScreenYPropertyInfo = "DOMTouch::screen-y" attrGet _ = getDOMTouchScreenY attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "target" -- Type: TInterface "WebKit" "DOMEventTarget" -- Flags: [PropertyReadable] getDOMTouchTarget :: (MonadIO m, DOMTouchK o) => o -> m DOMEventTarget getDOMTouchTarget obj = liftIO $ getObjectPropertyObject obj "target" DOMEventTarget data DOMTouchTargetPropertyInfo instance AttrInfo DOMTouchTargetPropertyInfo where type AttrAllowedOps DOMTouchTargetPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMTouchTargetPropertyInfo = (~) () type AttrBaseTypeConstraint DOMTouchTargetPropertyInfo = DOMTouchK type AttrGetType DOMTouchTargetPropertyInfo = DOMEventTarget type AttrLabel DOMTouchTargetPropertyInfo = "DOMTouch::target" attrGet _ = getDOMTouchTarget attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "webkit-force" -- Type: TBasicType TFloat -- Flags: [PropertyReadable] getDOMTouchWebkitForce :: (MonadIO m, DOMTouchK o) => o -> m Float getDOMTouchWebkitForce obj = liftIO $ getObjectPropertyFloat obj "webkit-force" data DOMTouchWebkitForcePropertyInfo instance AttrInfo DOMTouchWebkitForcePropertyInfo where type AttrAllowedOps DOMTouchWebkitForcePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMTouchWebkitForcePropertyInfo = (~) () type AttrBaseTypeConstraint DOMTouchWebkitForcePropertyInfo = DOMTouchK type AttrGetType DOMTouchWebkitForcePropertyInfo = Float type AttrLabel DOMTouchWebkitForcePropertyInfo = "DOMTouch::webkit-force" attrGet _ = getDOMTouchWebkitForce attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "webkit-radius-x" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMTouchWebkitRadiusX :: (MonadIO m, DOMTouchK o) => o -> m Int64 getDOMTouchWebkitRadiusX obj = liftIO $ getObjectPropertyInt64 obj "webkit-radius-x" data DOMTouchWebkitRadiusXPropertyInfo instance AttrInfo DOMTouchWebkitRadiusXPropertyInfo where type AttrAllowedOps DOMTouchWebkitRadiusXPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMTouchWebkitRadiusXPropertyInfo = (~) () type AttrBaseTypeConstraint DOMTouchWebkitRadiusXPropertyInfo = DOMTouchK type AttrGetType DOMTouchWebkitRadiusXPropertyInfo = Int64 type AttrLabel DOMTouchWebkitRadiusXPropertyInfo = "DOMTouch::webkit-radius-x" attrGet _ = getDOMTouchWebkitRadiusX attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "webkit-radius-y" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMTouchWebkitRadiusY :: (MonadIO m, DOMTouchK o) => o -> m Int64 getDOMTouchWebkitRadiusY obj = liftIO $ getObjectPropertyInt64 obj "webkit-radius-y" data DOMTouchWebkitRadiusYPropertyInfo instance AttrInfo DOMTouchWebkitRadiusYPropertyInfo where type AttrAllowedOps DOMTouchWebkitRadiusYPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMTouchWebkitRadiusYPropertyInfo = (~) () type AttrBaseTypeConstraint DOMTouchWebkitRadiusYPropertyInfo = DOMTouchK type AttrGetType DOMTouchWebkitRadiusYPropertyInfo = Int64 type AttrLabel DOMTouchWebkitRadiusYPropertyInfo = "DOMTouch::webkit-radius-y" attrGet _ = getDOMTouchWebkitRadiusY attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "webkit-rotation-angle" -- Type: TBasicType TFloat -- Flags: [PropertyReadable] getDOMTouchWebkitRotationAngle :: (MonadIO m, DOMTouchK o) => o -> m Float getDOMTouchWebkitRotationAngle obj = liftIO $ getObjectPropertyFloat obj "webkit-rotation-angle" data DOMTouchWebkitRotationAnglePropertyInfo instance AttrInfo DOMTouchWebkitRotationAnglePropertyInfo where type AttrAllowedOps DOMTouchWebkitRotationAnglePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMTouchWebkitRotationAnglePropertyInfo = (~) () type AttrBaseTypeConstraint DOMTouchWebkitRotationAnglePropertyInfo = DOMTouchK type AttrGetType DOMTouchWebkitRotationAnglePropertyInfo = Float type AttrLabel DOMTouchWebkitRotationAnglePropertyInfo = "DOMTouch::webkit-rotation-angle" attrGet _ = getDOMTouchWebkitRotationAngle attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMTouch = '[ '("client-x", DOMTouchClientXPropertyInfo), '("client-y", DOMTouchClientYPropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("identifier", DOMTouchIdentifierPropertyInfo), '("page-x", DOMTouchPageXPropertyInfo), '("page-y", DOMTouchPageYPropertyInfo), '("screen-x", DOMTouchScreenXPropertyInfo), '("screen-y", DOMTouchScreenYPropertyInfo), '("target", DOMTouchTargetPropertyInfo), '("webkit-force", DOMTouchWebkitForcePropertyInfo), '("webkit-radius-x", DOMTouchWebkitRadiusXPropertyInfo), '("webkit-radius-y", DOMTouchWebkitRadiusYPropertyInfo), '("webkit-rotation-angle", DOMTouchWebkitRotationAnglePropertyInfo)] type instance AttributeList DOMTrackEvent = '[ '("bubbles", DOMEventBubblesPropertyInfo), '("cancel-bubble", DOMEventCancelBubblePropertyInfo), '("cancelable", DOMEventCancelablePropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("current-target", DOMEventCurrentTargetPropertyInfo), '("default-prevented", DOMEventDefaultPreventedPropertyInfo), '("event-phase", DOMEventEventPhasePropertyInfo), '("return-value", DOMEventReturnValuePropertyInfo), '("src-element", DOMEventSrcElementPropertyInfo), '("target", DOMEventTargetPropertyInfo), '("time-stamp", DOMEventTimeStampPropertyInfo), '("type", DOMEventTypePropertyInfo)] -- VVV Prop "current-node" -- Type: TInterface "WebKit" "DOMNode" -- Flags: [PropertyReadable] getDOMTreeWalkerCurrentNode :: (MonadIO m, DOMTreeWalkerK o) => o -> m DOMNode getDOMTreeWalkerCurrentNode obj = liftIO $ getObjectPropertyObject obj "current-node" DOMNode data DOMTreeWalkerCurrentNodePropertyInfo instance AttrInfo DOMTreeWalkerCurrentNodePropertyInfo where type AttrAllowedOps DOMTreeWalkerCurrentNodePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMTreeWalkerCurrentNodePropertyInfo = (~) () type AttrBaseTypeConstraint DOMTreeWalkerCurrentNodePropertyInfo = DOMTreeWalkerK type AttrGetType DOMTreeWalkerCurrentNodePropertyInfo = DOMNode type AttrLabel DOMTreeWalkerCurrentNodePropertyInfo = "DOMTreeWalker::current-node" attrGet _ = getDOMTreeWalkerCurrentNode attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "expand-entity-references" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMTreeWalkerExpandEntityReferences :: (MonadIO m, DOMTreeWalkerK o) => o -> m Bool getDOMTreeWalkerExpandEntityReferences obj = liftIO $ getObjectPropertyBool obj "expand-entity-references" data DOMTreeWalkerExpandEntityReferencesPropertyInfo instance AttrInfo DOMTreeWalkerExpandEntityReferencesPropertyInfo where type AttrAllowedOps DOMTreeWalkerExpandEntityReferencesPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMTreeWalkerExpandEntityReferencesPropertyInfo = (~) () type AttrBaseTypeConstraint DOMTreeWalkerExpandEntityReferencesPropertyInfo = DOMTreeWalkerK type AttrGetType DOMTreeWalkerExpandEntityReferencesPropertyInfo = Bool type AttrLabel DOMTreeWalkerExpandEntityReferencesPropertyInfo = "DOMTreeWalker::expand-entity-references" attrGet _ = getDOMTreeWalkerExpandEntityReferences attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "filter" -- Type: TInterface "WebKit" "DOMNodeFilter" -- Flags: [PropertyReadable] getDOMTreeWalkerFilter :: (MonadIO m, DOMTreeWalkerK o) => o -> m DOMNodeFilter getDOMTreeWalkerFilter obj = liftIO $ getObjectPropertyObject obj "filter" DOMNodeFilter data DOMTreeWalkerFilterPropertyInfo instance AttrInfo DOMTreeWalkerFilterPropertyInfo where type AttrAllowedOps DOMTreeWalkerFilterPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMTreeWalkerFilterPropertyInfo = (~) () type AttrBaseTypeConstraint DOMTreeWalkerFilterPropertyInfo = DOMTreeWalkerK type AttrGetType DOMTreeWalkerFilterPropertyInfo = DOMNodeFilter type AttrLabel DOMTreeWalkerFilterPropertyInfo = "DOMTreeWalker::filter" attrGet _ = getDOMTreeWalkerFilter attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "root" -- Type: TInterface "WebKit" "DOMNode" -- Flags: [PropertyReadable] getDOMTreeWalkerRoot :: (MonadIO m, DOMTreeWalkerK o) => o -> m DOMNode getDOMTreeWalkerRoot obj = liftIO $ getObjectPropertyObject obj "root" DOMNode data DOMTreeWalkerRootPropertyInfo instance AttrInfo DOMTreeWalkerRootPropertyInfo where type AttrAllowedOps DOMTreeWalkerRootPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMTreeWalkerRootPropertyInfo = (~) () type AttrBaseTypeConstraint DOMTreeWalkerRootPropertyInfo = DOMTreeWalkerK type AttrGetType DOMTreeWalkerRootPropertyInfo = DOMNode type AttrLabel DOMTreeWalkerRootPropertyInfo = "DOMTreeWalker::root" attrGet _ = getDOMTreeWalkerRoot attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "what-to-show" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMTreeWalkerWhatToShow :: (MonadIO m, DOMTreeWalkerK o) => o -> m Word64 getDOMTreeWalkerWhatToShow obj = liftIO $ getObjectPropertyUInt64 obj "what-to-show" data DOMTreeWalkerWhatToShowPropertyInfo instance AttrInfo DOMTreeWalkerWhatToShowPropertyInfo where type AttrAllowedOps DOMTreeWalkerWhatToShowPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMTreeWalkerWhatToShowPropertyInfo = (~) () type AttrBaseTypeConstraint DOMTreeWalkerWhatToShowPropertyInfo = DOMTreeWalkerK type AttrGetType DOMTreeWalkerWhatToShowPropertyInfo = Word64 type AttrLabel DOMTreeWalkerWhatToShowPropertyInfo = "DOMTreeWalker::what-to-show" attrGet _ = getDOMTreeWalkerWhatToShow attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMTreeWalker = '[ '("core-object", DOMObjectCoreObjectPropertyInfo), '("current-node", DOMTreeWalkerCurrentNodePropertyInfo), '("expand-entity-references", DOMTreeWalkerExpandEntityReferencesPropertyInfo), '("filter", DOMTreeWalkerFilterPropertyInfo), '("root", DOMTreeWalkerRootPropertyInfo), '("what-to-show", DOMTreeWalkerWhatToShowPropertyInfo)] -- VVV Prop "char-code" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMUIEventCharCode :: (MonadIO m, DOMUIEventK o) => o -> m Int64 getDOMUIEventCharCode obj = liftIO $ getObjectPropertyInt64 obj "char-code" data DOMUIEventCharCodePropertyInfo instance AttrInfo DOMUIEventCharCodePropertyInfo where type AttrAllowedOps DOMUIEventCharCodePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMUIEventCharCodePropertyInfo = (~) () type AttrBaseTypeConstraint DOMUIEventCharCodePropertyInfo = DOMUIEventK type AttrGetType DOMUIEventCharCodePropertyInfo = Int64 type AttrLabel DOMUIEventCharCodePropertyInfo = "DOMUIEvent::char-code" attrGet _ = getDOMUIEventCharCode attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "detail" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMUIEventDetail :: (MonadIO m, DOMUIEventK o) => o -> m Int64 getDOMUIEventDetail obj = liftIO $ getObjectPropertyInt64 obj "detail" data DOMUIEventDetailPropertyInfo instance AttrInfo DOMUIEventDetailPropertyInfo where type AttrAllowedOps DOMUIEventDetailPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMUIEventDetailPropertyInfo = (~) () type AttrBaseTypeConstraint DOMUIEventDetailPropertyInfo = DOMUIEventK type AttrGetType DOMUIEventDetailPropertyInfo = Int64 type AttrLabel DOMUIEventDetailPropertyInfo = "DOMUIEvent::detail" attrGet _ = getDOMUIEventDetail attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "key-code" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMUIEventKeyCode :: (MonadIO m, DOMUIEventK o) => o -> m Int64 getDOMUIEventKeyCode obj = liftIO $ getObjectPropertyInt64 obj "key-code" data DOMUIEventKeyCodePropertyInfo instance AttrInfo DOMUIEventKeyCodePropertyInfo where type AttrAllowedOps DOMUIEventKeyCodePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMUIEventKeyCodePropertyInfo = (~) () type AttrBaseTypeConstraint DOMUIEventKeyCodePropertyInfo = DOMUIEventK type AttrGetType DOMUIEventKeyCodePropertyInfo = Int64 type AttrLabel DOMUIEventKeyCodePropertyInfo = "DOMUIEvent::key-code" attrGet _ = getDOMUIEventKeyCode attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "layer-x" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMUIEventLayerX :: (MonadIO m, DOMUIEventK o) => o -> m Int64 getDOMUIEventLayerX obj = liftIO $ getObjectPropertyInt64 obj "layer-x" data DOMUIEventLayerXPropertyInfo instance AttrInfo DOMUIEventLayerXPropertyInfo where type AttrAllowedOps DOMUIEventLayerXPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMUIEventLayerXPropertyInfo = (~) () type AttrBaseTypeConstraint DOMUIEventLayerXPropertyInfo = DOMUIEventK type AttrGetType DOMUIEventLayerXPropertyInfo = Int64 type AttrLabel DOMUIEventLayerXPropertyInfo = "DOMUIEvent::layer-x" attrGet _ = getDOMUIEventLayerX attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "layer-y" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMUIEventLayerY :: (MonadIO m, DOMUIEventK o) => o -> m Int64 getDOMUIEventLayerY obj = liftIO $ getObjectPropertyInt64 obj "layer-y" data DOMUIEventLayerYPropertyInfo instance AttrInfo DOMUIEventLayerYPropertyInfo where type AttrAllowedOps DOMUIEventLayerYPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMUIEventLayerYPropertyInfo = (~) () type AttrBaseTypeConstraint DOMUIEventLayerYPropertyInfo = DOMUIEventK type AttrGetType DOMUIEventLayerYPropertyInfo = Int64 type AttrLabel DOMUIEventLayerYPropertyInfo = "DOMUIEvent::layer-y" attrGet _ = getDOMUIEventLayerY attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "page-x" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMUIEventPageX :: (MonadIO m, DOMUIEventK o) => o -> m Int64 getDOMUIEventPageX obj = liftIO $ getObjectPropertyInt64 obj "page-x" data DOMUIEventPageXPropertyInfo instance AttrInfo DOMUIEventPageXPropertyInfo where type AttrAllowedOps DOMUIEventPageXPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMUIEventPageXPropertyInfo = (~) () type AttrBaseTypeConstraint DOMUIEventPageXPropertyInfo = DOMUIEventK type AttrGetType DOMUIEventPageXPropertyInfo = Int64 type AttrLabel DOMUIEventPageXPropertyInfo = "DOMUIEvent::page-x" attrGet _ = getDOMUIEventPageX attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "page-y" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMUIEventPageY :: (MonadIO m, DOMUIEventK o) => o -> m Int64 getDOMUIEventPageY obj = liftIO $ getObjectPropertyInt64 obj "page-y" data DOMUIEventPageYPropertyInfo instance AttrInfo DOMUIEventPageYPropertyInfo where type AttrAllowedOps DOMUIEventPageYPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMUIEventPageYPropertyInfo = (~) () type AttrBaseTypeConstraint DOMUIEventPageYPropertyInfo = DOMUIEventK type AttrGetType DOMUIEventPageYPropertyInfo = Int64 type AttrLabel DOMUIEventPageYPropertyInfo = "DOMUIEvent::page-y" attrGet _ = getDOMUIEventPageY attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "view" -- Type: TInterface "WebKit" "DOMDOMWindow" -- Flags: [PropertyReadable] getDOMUIEventView :: (MonadIO m, DOMUIEventK o) => o -> m DOMDOMWindow getDOMUIEventView obj = liftIO $ getObjectPropertyObject obj "view" DOMDOMWindow data DOMUIEventViewPropertyInfo instance AttrInfo DOMUIEventViewPropertyInfo where type AttrAllowedOps DOMUIEventViewPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMUIEventViewPropertyInfo = (~) () type AttrBaseTypeConstraint DOMUIEventViewPropertyInfo = DOMUIEventK type AttrGetType DOMUIEventViewPropertyInfo = DOMDOMWindow type AttrLabel DOMUIEventViewPropertyInfo = "DOMUIEvent::view" attrGet _ = getDOMUIEventView attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "which" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMUIEventWhich :: (MonadIO m, DOMUIEventK o) => o -> m Int64 getDOMUIEventWhich obj = liftIO $ getObjectPropertyInt64 obj "which" data DOMUIEventWhichPropertyInfo instance AttrInfo DOMUIEventWhichPropertyInfo where type AttrAllowedOps DOMUIEventWhichPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMUIEventWhichPropertyInfo = (~) () type AttrBaseTypeConstraint DOMUIEventWhichPropertyInfo = DOMUIEventK type AttrGetType DOMUIEventWhichPropertyInfo = Int64 type AttrLabel DOMUIEventWhichPropertyInfo = "DOMUIEvent::which" attrGet _ = getDOMUIEventWhich attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMUIEvent = '[ '("bubbles", DOMEventBubblesPropertyInfo), '("cancel-bubble", DOMEventCancelBubblePropertyInfo), '("cancelable", DOMEventCancelablePropertyInfo), '("char-code", DOMUIEventCharCodePropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("current-target", DOMEventCurrentTargetPropertyInfo), '("default-prevented", DOMEventDefaultPreventedPropertyInfo), '("detail", DOMUIEventDetailPropertyInfo), '("event-phase", DOMEventEventPhasePropertyInfo), '("key-code", DOMUIEventKeyCodePropertyInfo), '("layer-x", DOMUIEventLayerXPropertyInfo), '("layer-y", DOMUIEventLayerYPropertyInfo), '("page-x", DOMUIEventPageXPropertyInfo), '("page-y", DOMUIEventPageYPropertyInfo), '("return-value", DOMEventReturnValuePropertyInfo), '("src-element", DOMEventSrcElementPropertyInfo), '("target", DOMEventTargetPropertyInfo), '("time-stamp", DOMEventTimeStampPropertyInfo), '("type", DOMEventTypePropertyInfo), '("view", DOMUIEventViewPropertyInfo), '("which", DOMUIEventWhichPropertyInfo)] -- VVV Prop "bad-input" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMValidityStateBadInput :: (MonadIO m, DOMValidityStateK o) => o -> m Bool getDOMValidityStateBadInput obj = liftIO $ getObjectPropertyBool obj "bad-input" data DOMValidityStateBadInputPropertyInfo instance AttrInfo DOMValidityStateBadInputPropertyInfo where type AttrAllowedOps DOMValidityStateBadInputPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMValidityStateBadInputPropertyInfo = (~) () type AttrBaseTypeConstraint DOMValidityStateBadInputPropertyInfo = DOMValidityStateK type AttrGetType DOMValidityStateBadInputPropertyInfo = Bool type AttrLabel DOMValidityStateBadInputPropertyInfo = "DOMValidityState::bad-input" attrGet _ = getDOMValidityStateBadInput attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "custom-error" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMValidityStateCustomError :: (MonadIO m, DOMValidityStateK o) => o -> m Bool getDOMValidityStateCustomError obj = liftIO $ getObjectPropertyBool obj "custom-error" data DOMValidityStateCustomErrorPropertyInfo instance AttrInfo DOMValidityStateCustomErrorPropertyInfo where type AttrAllowedOps DOMValidityStateCustomErrorPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMValidityStateCustomErrorPropertyInfo = (~) () type AttrBaseTypeConstraint DOMValidityStateCustomErrorPropertyInfo = DOMValidityStateK type AttrGetType DOMValidityStateCustomErrorPropertyInfo = Bool type AttrLabel DOMValidityStateCustomErrorPropertyInfo = "DOMValidityState::custom-error" attrGet _ = getDOMValidityStateCustomError attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "pattern-mismatch" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMValidityStatePatternMismatch :: (MonadIO m, DOMValidityStateK o) => o -> m Bool getDOMValidityStatePatternMismatch obj = liftIO $ getObjectPropertyBool obj "pattern-mismatch" data DOMValidityStatePatternMismatchPropertyInfo instance AttrInfo DOMValidityStatePatternMismatchPropertyInfo where type AttrAllowedOps DOMValidityStatePatternMismatchPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMValidityStatePatternMismatchPropertyInfo = (~) () type AttrBaseTypeConstraint DOMValidityStatePatternMismatchPropertyInfo = DOMValidityStateK type AttrGetType DOMValidityStatePatternMismatchPropertyInfo = Bool type AttrLabel DOMValidityStatePatternMismatchPropertyInfo = "DOMValidityState::pattern-mismatch" attrGet _ = getDOMValidityStatePatternMismatch attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "range-overflow" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMValidityStateRangeOverflow :: (MonadIO m, DOMValidityStateK o) => o -> m Bool getDOMValidityStateRangeOverflow obj = liftIO $ getObjectPropertyBool obj "range-overflow" data DOMValidityStateRangeOverflowPropertyInfo instance AttrInfo DOMValidityStateRangeOverflowPropertyInfo where type AttrAllowedOps DOMValidityStateRangeOverflowPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMValidityStateRangeOverflowPropertyInfo = (~) () type AttrBaseTypeConstraint DOMValidityStateRangeOverflowPropertyInfo = DOMValidityStateK type AttrGetType DOMValidityStateRangeOverflowPropertyInfo = Bool type AttrLabel DOMValidityStateRangeOverflowPropertyInfo = "DOMValidityState::range-overflow" attrGet _ = getDOMValidityStateRangeOverflow attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "range-underflow" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMValidityStateRangeUnderflow :: (MonadIO m, DOMValidityStateK o) => o -> m Bool getDOMValidityStateRangeUnderflow obj = liftIO $ getObjectPropertyBool obj "range-underflow" data DOMValidityStateRangeUnderflowPropertyInfo instance AttrInfo DOMValidityStateRangeUnderflowPropertyInfo where type AttrAllowedOps DOMValidityStateRangeUnderflowPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMValidityStateRangeUnderflowPropertyInfo = (~) () type AttrBaseTypeConstraint DOMValidityStateRangeUnderflowPropertyInfo = DOMValidityStateK type AttrGetType DOMValidityStateRangeUnderflowPropertyInfo = Bool type AttrLabel DOMValidityStateRangeUnderflowPropertyInfo = "DOMValidityState::range-underflow" attrGet _ = getDOMValidityStateRangeUnderflow attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "step-mismatch" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMValidityStateStepMismatch :: (MonadIO m, DOMValidityStateK o) => o -> m Bool getDOMValidityStateStepMismatch obj = liftIO $ getObjectPropertyBool obj "step-mismatch" data DOMValidityStateStepMismatchPropertyInfo instance AttrInfo DOMValidityStateStepMismatchPropertyInfo where type AttrAllowedOps DOMValidityStateStepMismatchPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMValidityStateStepMismatchPropertyInfo = (~) () type AttrBaseTypeConstraint DOMValidityStateStepMismatchPropertyInfo = DOMValidityStateK type AttrGetType DOMValidityStateStepMismatchPropertyInfo = Bool type AttrLabel DOMValidityStateStepMismatchPropertyInfo = "DOMValidityState::step-mismatch" attrGet _ = getDOMValidityStateStepMismatch attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "too-long" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMValidityStateTooLong :: (MonadIO m, DOMValidityStateK o) => o -> m Bool getDOMValidityStateTooLong obj = liftIO $ getObjectPropertyBool obj "too-long" data DOMValidityStateTooLongPropertyInfo instance AttrInfo DOMValidityStateTooLongPropertyInfo where type AttrAllowedOps DOMValidityStateTooLongPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMValidityStateTooLongPropertyInfo = (~) () type AttrBaseTypeConstraint DOMValidityStateTooLongPropertyInfo = DOMValidityStateK type AttrGetType DOMValidityStateTooLongPropertyInfo = Bool type AttrLabel DOMValidityStateTooLongPropertyInfo = "DOMValidityState::too-long" attrGet _ = getDOMValidityStateTooLong attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "type-mismatch" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMValidityStateTypeMismatch :: (MonadIO m, DOMValidityStateK o) => o -> m Bool getDOMValidityStateTypeMismatch obj = liftIO $ getObjectPropertyBool obj "type-mismatch" data DOMValidityStateTypeMismatchPropertyInfo instance AttrInfo DOMValidityStateTypeMismatchPropertyInfo where type AttrAllowedOps DOMValidityStateTypeMismatchPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMValidityStateTypeMismatchPropertyInfo = (~) () type AttrBaseTypeConstraint DOMValidityStateTypeMismatchPropertyInfo = DOMValidityStateK type AttrGetType DOMValidityStateTypeMismatchPropertyInfo = Bool type AttrLabel DOMValidityStateTypeMismatchPropertyInfo = "DOMValidityState::type-mismatch" attrGet _ = getDOMValidityStateTypeMismatch attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "valid" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMValidityStateValid :: (MonadIO m, DOMValidityStateK o) => o -> m Bool getDOMValidityStateValid obj = liftIO $ getObjectPropertyBool obj "valid" data DOMValidityStateValidPropertyInfo instance AttrInfo DOMValidityStateValidPropertyInfo where type AttrAllowedOps DOMValidityStateValidPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMValidityStateValidPropertyInfo = (~) () type AttrBaseTypeConstraint DOMValidityStateValidPropertyInfo = DOMValidityStateK type AttrGetType DOMValidityStateValidPropertyInfo = Bool type AttrLabel DOMValidityStateValidPropertyInfo = "DOMValidityState::valid" attrGet _ = getDOMValidityStateValid attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "value-missing" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMValidityStateValueMissing :: (MonadIO m, DOMValidityStateK o) => o -> m Bool getDOMValidityStateValueMissing obj = liftIO $ getObjectPropertyBool obj "value-missing" data DOMValidityStateValueMissingPropertyInfo instance AttrInfo DOMValidityStateValueMissingPropertyInfo where type AttrAllowedOps DOMValidityStateValueMissingPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMValidityStateValueMissingPropertyInfo = (~) () type AttrBaseTypeConstraint DOMValidityStateValueMissingPropertyInfo = DOMValidityStateK type AttrGetType DOMValidityStateValueMissingPropertyInfo = Bool type AttrLabel DOMValidityStateValueMissingPropertyInfo = "DOMValidityState::value-missing" attrGet _ = getDOMValidityStateValueMissing attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMValidityState = '[ '("bad-input", DOMValidityStateBadInputPropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("custom-error", DOMValidityStateCustomErrorPropertyInfo), '("pattern-mismatch", DOMValidityStatePatternMismatchPropertyInfo), '("range-overflow", DOMValidityStateRangeOverflowPropertyInfo), '("range-underflow", DOMValidityStateRangeUnderflowPropertyInfo), '("step-mismatch", DOMValidityStateStepMismatchPropertyInfo), '("too-long", DOMValidityStateTooLongPropertyInfo), '("type-mismatch", DOMValidityStateTypeMismatchPropertyInfo), '("valid", DOMValidityStateValidPropertyInfo), '("value-missing", DOMValidityStateValueMissingPropertyInfo)] -- VVV Prop "corrupted-video-frames" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMVideoPlaybackQualityCorruptedVideoFrames :: (MonadIO m, DOMVideoPlaybackQualityK o) => o -> m Word64 getDOMVideoPlaybackQualityCorruptedVideoFrames obj = liftIO $ getObjectPropertyUInt64 obj "corrupted-video-frames" data DOMVideoPlaybackQualityCorruptedVideoFramesPropertyInfo instance AttrInfo DOMVideoPlaybackQualityCorruptedVideoFramesPropertyInfo where type AttrAllowedOps DOMVideoPlaybackQualityCorruptedVideoFramesPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMVideoPlaybackQualityCorruptedVideoFramesPropertyInfo = (~) () type AttrBaseTypeConstraint DOMVideoPlaybackQualityCorruptedVideoFramesPropertyInfo = DOMVideoPlaybackQualityK type AttrGetType DOMVideoPlaybackQualityCorruptedVideoFramesPropertyInfo = Word64 type AttrLabel DOMVideoPlaybackQualityCorruptedVideoFramesPropertyInfo = "DOMVideoPlaybackQuality::corrupted-video-frames" attrGet _ = getDOMVideoPlaybackQualityCorruptedVideoFrames attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "creation-time" -- Type: TBasicType TDouble -- Flags: [PropertyReadable] getDOMVideoPlaybackQualityCreationTime :: (MonadIO m, DOMVideoPlaybackQualityK o) => o -> m Double getDOMVideoPlaybackQualityCreationTime obj = liftIO $ getObjectPropertyDouble obj "creation-time" data DOMVideoPlaybackQualityCreationTimePropertyInfo instance AttrInfo DOMVideoPlaybackQualityCreationTimePropertyInfo where type AttrAllowedOps DOMVideoPlaybackQualityCreationTimePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMVideoPlaybackQualityCreationTimePropertyInfo = (~) () type AttrBaseTypeConstraint DOMVideoPlaybackQualityCreationTimePropertyInfo = DOMVideoPlaybackQualityK type AttrGetType DOMVideoPlaybackQualityCreationTimePropertyInfo = Double type AttrLabel DOMVideoPlaybackQualityCreationTimePropertyInfo = "DOMVideoPlaybackQuality::creation-time" attrGet _ = getDOMVideoPlaybackQualityCreationTime attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "dropped-video-frames" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMVideoPlaybackQualityDroppedVideoFrames :: (MonadIO m, DOMVideoPlaybackQualityK o) => o -> m Word64 getDOMVideoPlaybackQualityDroppedVideoFrames obj = liftIO $ getObjectPropertyUInt64 obj "dropped-video-frames" data DOMVideoPlaybackQualityDroppedVideoFramesPropertyInfo instance AttrInfo DOMVideoPlaybackQualityDroppedVideoFramesPropertyInfo where type AttrAllowedOps DOMVideoPlaybackQualityDroppedVideoFramesPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMVideoPlaybackQualityDroppedVideoFramesPropertyInfo = (~) () type AttrBaseTypeConstraint DOMVideoPlaybackQualityDroppedVideoFramesPropertyInfo = DOMVideoPlaybackQualityK type AttrGetType DOMVideoPlaybackQualityDroppedVideoFramesPropertyInfo = Word64 type AttrLabel DOMVideoPlaybackQualityDroppedVideoFramesPropertyInfo = "DOMVideoPlaybackQuality::dropped-video-frames" attrGet _ = getDOMVideoPlaybackQualityDroppedVideoFrames attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "total-frame-delay" -- Type: TBasicType TDouble -- Flags: [PropertyReadable] getDOMVideoPlaybackQualityTotalFrameDelay :: (MonadIO m, DOMVideoPlaybackQualityK o) => o -> m Double getDOMVideoPlaybackQualityTotalFrameDelay obj = liftIO $ getObjectPropertyDouble obj "total-frame-delay" data DOMVideoPlaybackQualityTotalFrameDelayPropertyInfo instance AttrInfo DOMVideoPlaybackQualityTotalFrameDelayPropertyInfo where type AttrAllowedOps DOMVideoPlaybackQualityTotalFrameDelayPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMVideoPlaybackQualityTotalFrameDelayPropertyInfo = (~) () type AttrBaseTypeConstraint DOMVideoPlaybackQualityTotalFrameDelayPropertyInfo = DOMVideoPlaybackQualityK type AttrGetType DOMVideoPlaybackQualityTotalFrameDelayPropertyInfo = Double type AttrLabel DOMVideoPlaybackQualityTotalFrameDelayPropertyInfo = "DOMVideoPlaybackQuality::total-frame-delay" attrGet _ = getDOMVideoPlaybackQualityTotalFrameDelay attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "total-video-frames" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMVideoPlaybackQualityTotalVideoFrames :: (MonadIO m, DOMVideoPlaybackQualityK o) => o -> m Word64 getDOMVideoPlaybackQualityTotalVideoFrames obj = liftIO $ getObjectPropertyUInt64 obj "total-video-frames" data DOMVideoPlaybackQualityTotalVideoFramesPropertyInfo instance AttrInfo DOMVideoPlaybackQualityTotalVideoFramesPropertyInfo where type AttrAllowedOps DOMVideoPlaybackQualityTotalVideoFramesPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMVideoPlaybackQualityTotalVideoFramesPropertyInfo = (~) () type AttrBaseTypeConstraint DOMVideoPlaybackQualityTotalVideoFramesPropertyInfo = DOMVideoPlaybackQualityK type AttrGetType DOMVideoPlaybackQualityTotalVideoFramesPropertyInfo = Word64 type AttrLabel DOMVideoPlaybackQualityTotalVideoFramesPropertyInfo = "DOMVideoPlaybackQuality::total-video-frames" attrGet _ = getDOMVideoPlaybackQualityTotalVideoFrames attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMVideoPlaybackQuality = '[ '("core-object", DOMObjectCoreObjectPropertyInfo), '("corrupted-video-frames", DOMVideoPlaybackQualityCorruptedVideoFramesPropertyInfo), '("creation-time", DOMVideoPlaybackQualityCreationTimePropertyInfo), '("dropped-video-frames", DOMVideoPlaybackQualityDroppedVideoFramesPropertyInfo), '("total-frame-delay", DOMVideoPlaybackQualityTotalFrameDelayPropertyInfo), '("total-video-frames", DOMVideoPlaybackQualityTotalVideoFramesPropertyInfo)] -- VVV Prop "id" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMVideoTrackId :: (MonadIO m, DOMVideoTrackK o) => o -> m T.Text getDOMVideoTrackId obj = liftIO $ getObjectPropertyString obj "id" data DOMVideoTrackIdPropertyInfo instance AttrInfo DOMVideoTrackIdPropertyInfo where type AttrAllowedOps DOMVideoTrackIdPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMVideoTrackIdPropertyInfo = (~) () type AttrBaseTypeConstraint DOMVideoTrackIdPropertyInfo = DOMVideoTrackK type AttrGetType DOMVideoTrackIdPropertyInfo = T.Text type AttrLabel DOMVideoTrackIdPropertyInfo = "DOMVideoTrack::id" attrGet _ = getDOMVideoTrackId attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "kind" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMVideoTrackKind :: (MonadIO m, DOMVideoTrackK o) => o -> m T.Text getDOMVideoTrackKind obj = liftIO $ getObjectPropertyString obj "kind" data DOMVideoTrackKindPropertyInfo instance AttrInfo DOMVideoTrackKindPropertyInfo where type AttrAllowedOps DOMVideoTrackKindPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMVideoTrackKindPropertyInfo = (~) () type AttrBaseTypeConstraint DOMVideoTrackKindPropertyInfo = DOMVideoTrackK type AttrGetType DOMVideoTrackKindPropertyInfo = T.Text type AttrLabel DOMVideoTrackKindPropertyInfo = "DOMVideoTrack::kind" attrGet _ = getDOMVideoTrackKind attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "label" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMVideoTrackLabel :: (MonadIO m, DOMVideoTrackK o) => o -> m T.Text getDOMVideoTrackLabel obj = liftIO $ getObjectPropertyString obj "label" data DOMVideoTrackLabelPropertyInfo instance AttrInfo DOMVideoTrackLabelPropertyInfo where type AttrAllowedOps DOMVideoTrackLabelPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMVideoTrackLabelPropertyInfo = (~) () type AttrBaseTypeConstraint DOMVideoTrackLabelPropertyInfo = DOMVideoTrackK type AttrGetType DOMVideoTrackLabelPropertyInfo = T.Text type AttrLabel DOMVideoTrackLabelPropertyInfo = "DOMVideoTrack::label" attrGet _ = getDOMVideoTrackLabel attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "language" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMVideoTrackLanguage :: (MonadIO m, DOMVideoTrackK o) => o -> m T.Text getDOMVideoTrackLanguage obj = liftIO $ getObjectPropertyString obj "language" data DOMVideoTrackLanguagePropertyInfo instance AttrInfo DOMVideoTrackLanguagePropertyInfo where type AttrAllowedOps DOMVideoTrackLanguagePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMVideoTrackLanguagePropertyInfo = (~) () type AttrBaseTypeConstraint DOMVideoTrackLanguagePropertyInfo = DOMVideoTrackK type AttrGetType DOMVideoTrackLanguagePropertyInfo = T.Text type AttrLabel DOMVideoTrackLanguagePropertyInfo = "DOMVideoTrack::language" attrGet _ = getDOMVideoTrackLanguage attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "selected" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getDOMVideoTrackSelected :: (MonadIO m, DOMVideoTrackK o) => o -> m Bool getDOMVideoTrackSelected obj = liftIO $ getObjectPropertyBool obj "selected" setDOMVideoTrackSelected :: (MonadIO m, DOMVideoTrackK o) => o -> Bool -> m () setDOMVideoTrackSelected obj val = liftIO $ setObjectPropertyBool obj "selected" val constructDOMVideoTrackSelected :: Bool -> IO ([Char], GValue) constructDOMVideoTrackSelected val = constructObjectPropertyBool "selected" val data DOMVideoTrackSelectedPropertyInfo instance AttrInfo DOMVideoTrackSelectedPropertyInfo where type AttrAllowedOps DOMVideoTrackSelectedPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMVideoTrackSelectedPropertyInfo = (~) Bool type AttrBaseTypeConstraint DOMVideoTrackSelectedPropertyInfo = DOMVideoTrackK type AttrGetType DOMVideoTrackSelectedPropertyInfo = Bool type AttrLabel DOMVideoTrackSelectedPropertyInfo = "DOMVideoTrack::selected" attrGet _ = getDOMVideoTrackSelected attrSet _ = setDOMVideoTrackSelected attrConstruct _ = constructDOMVideoTrackSelected type instance AttributeList DOMVideoTrack = '[ '("core-object", DOMObjectCoreObjectPropertyInfo), '("id", DOMVideoTrackIdPropertyInfo), '("kind", DOMVideoTrackKindPropertyInfo), '("label", DOMVideoTrackLabelPropertyInfo), '("language", DOMVideoTrackLanguagePropertyInfo), '("selected", DOMVideoTrackSelectedPropertyInfo)] -- VVV Prop "length" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMVideoTrackListLength :: (MonadIO m, DOMVideoTrackListK o) => o -> m Word64 getDOMVideoTrackListLength obj = liftIO $ getObjectPropertyUInt64 obj "length" data DOMVideoTrackListLengthPropertyInfo instance AttrInfo DOMVideoTrackListLengthPropertyInfo where type AttrAllowedOps DOMVideoTrackListLengthPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMVideoTrackListLengthPropertyInfo = (~) () type AttrBaseTypeConstraint DOMVideoTrackListLengthPropertyInfo = DOMVideoTrackListK type AttrGetType DOMVideoTrackListLengthPropertyInfo = Word64 type AttrLabel DOMVideoTrackListLengthPropertyInfo = "DOMVideoTrackList::length" attrGet _ = getDOMVideoTrackListLength attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMVideoTrackList = '[ '("core-object", DOMObjectCoreObjectPropertyInfo), '("length", DOMVideoTrackListLengthPropertyInfo)] -- VVV Prop "first-empty-region-index" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMWebKitNamedFlowFirstEmptyRegionIndex :: (MonadIO m, DOMWebKitNamedFlowK o) => o -> m Int64 getDOMWebKitNamedFlowFirstEmptyRegionIndex obj = liftIO $ getObjectPropertyInt64 obj "first-empty-region-index" data DOMWebKitNamedFlowFirstEmptyRegionIndexPropertyInfo instance AttrInfo DOMWebKitNamedFlowFirstEmptyRegionIndexPropertyInfo where type AttrAllowedOps DOMWebKitNamedFlowFirstEmptyRegionIndexPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMWebKitNamedFlowFirstEmptyRegionIndexPropertyInfo = (~) () type AttrBaseTypeConstraint DOMWebKitNamedFlowFirstEmptyRegionIndexPropertyInfo = DOMWebKitNamedFlowK type AttrGetType DOMWebKitNamedFlowFirstEmptyRegionIndexPropertyInfo = Int64 type AttrLabel DOMWebKitNamedFlowFirstEmptyRegionIndexPropertyInfo = "DOMWebKitNamedFlow::first-empty-region-index" attrGet _ = getDOMWebKitNamedFlowFirstEmptyRegionIndex attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "name" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMWebKitNamedFlowName :: (MonadIO m, DOMWebKitNamedFlowK o) => o -> m T.Text getDOMWebKitNamedFlowName obj = liftIO $ getObjectPropertyString obj "name" data DOMWebKitNamedFlowNamePropertyInfo instance AttrInfo DOMWebKitNamedFlowNamePropertyInfo where type AttrAllowedOps DOMWebKitNamedFlowNamePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMWebKitNamedFlowNamePropertyInfo = (~) () type AttrBaseTypeConstraint DOMWebKitNamedFlowNamePropertyInfo = DOMWebKitNamedFlowK type AttrGetType DOMWebKitNamedFlowNamePropertyInfo = T.Text type AttrLabel DOMWebKitNamedFlowNamePropertyInfo = "DOMWebKitNamedFlow::name" attrGet _ = getDOMWebKitNamedFlowName attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "overset" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMWebKitNamedFlowOverset :: (MonadIO m, DOMWebKitNamedFlowK o) => o -> m Bool getDOMWebKitNamedFlowOverset obj = liftIO $ getObjectPropertyBool obj "overset" data DOMWebKitNamedFlowOversetPropertyInfo instance AttrInfo DOMWebKitNamedFlowOversetPropertyInfo where type AttrAllowedOps DOMWebKitNamedFlowOversetPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMWebKitNamedFlowOversetPropertyInfo = (~) () type AttrBaseTypeConstraint DOMWebKitNamedFlowOversetPropertyInfo = DOMWebKitNamedFlowK type AttrGetType DOMWebKitNamedFlowOversetPropertyInfo = Bool type AttrLabel DOMWebKitNamedFlowOversetPropertyInfo = "DOMWebKitNamedFlow::overset" attrGet _ = getDOMWebKitNamedFlowOverset attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMWebKitNamedFlow = '[ '("core-object", DOMObjectCoreObjectPropertyInfo), '("first-empty-region-index", DOMWebKitNamedFlowFirstEmptyRegionIndexPropertyInfo), '("name", DOMWebKitNamedFlowNamePropertyInfo), '("overset", DOMWebKitNamedFlowOversetPropertyInfo)] -- VVV Prop "x" -- Type: TBasicType TFloat -- Flags: [PropertyReadable,PropertyWritable] getDOMWebKitPointX :: (MonadIO m, DOMWebKitPointK o) => o -> m Float getDOMWebKitPointX obj = liftIO $ getObjectPropertyFloat obj "x" setDOMWebKitPointX :: (MonadIO m, DOMWebKitPointK o) => o -> Float -> m () setDOMWebKitPointX obj val = liftIO $ setObjectPropertyFloat obj "x" val constructDOMWebKitPointX :: Float -> IO ([Char], GValue) constructDOMWebKitPointX val = constructObjectPropertyFloat "x" val data DOMWebKitPointXPropertyInfo instance AttrInfo DOMWebKitPointXPropertyInfo where type AttrAllowedOps DOMWebKitPointXPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMWebKitPointXPropertyInfo = (~) Float type AttrBaseTypeConstraint DOMWebKitPointXPropertyInfo = DOMWebKitPointK type AttrGetType DOMWebKitPointXPropertyInfo = Float type AttrLabel DOMWebKitPointXPropertyInfo = "DOMWebKitPoint::x" attrGet _ = getDOMWebKitPointX attrSet _ = setDOMWebKitPointX attrConstruct _ = constructDOMWebKitPointX -- VVV Prop "y" -- Type: TBasicType TFloat -- Flags: [PropertyReadable,PropertyWritable] getDOMWebKitPointY :: (MonadIO m, DOMWebKitPointK o) => o -> m Float getDOMWebKitPointY obj = liftIO $ getObjectPropertyFloat obj "y" setDOMWebKitPointY :: (MonadIO m, DOMWebKitPointK o) => o -> Float -> m () setDOMWebKitPointY obj val = liftIO $ setObjectPropertyFloat obj "y" val constructDOMWebKitPointY :: Float -> IO ([Char], GValue) constructDOMWebKitPointY val = constructObjectPropertyFloat "y" val data DOMWebKitPointYPropertyInfo instance AttrInfo DOMWebKitPointYPropertyInfo where type AttrAllowedOps DOMWebKitPointYPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DOMWebKitPointYPropertyInfo = (~) Float type AttrBaseTypeConstraint DOMWebKitPointYPropertyInfo = DOMWebKitPointK type AttrGetType DOMWebKitPointYPropertyInfo = Float type AttrLabel DOMWebKitPointYPropertyInfo = "DOMWebKitPoint::y" attrGet _ = getDOMWebKitPointY attrSet _ = setDOMWebKitPointY attrConstruct _ = constructDOMWebKitPointY type instance AttributeList DOMWebKitPoint = '[ '("core-object", DOMObjectCoreObjectPropertyInfo), '("x", DOMWebKitPointXPropertyInfo), '("y", DOMWebKitPointYPropertyInfo)] -- VVV Prop "delta-mode" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMWheelEventDeltaMode :: (MonadIO m, DOMWheelEventK o) => o -> m Word64 getDOMWheelEventDeltaMode obj = liftIO $ getObjectPropertyUInt64 obj "delta-mode" data DOMWheelEventDeltaModePropertyInfo instance AttrInfo DOMWheelEventDeltaModePropertyInfo where type AttrAllowedOps DOMWheelEventDeltaModePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMWheelEventDeltaModePropertyInfo = (~) () type AttrBaseTypeConstraint DOMWheelEventDeltaModePropertyInfo = DOMWheelEventK type AttrGetType DOMWheelEventDeltaModePropertyInfo = Word64 type AttrLabel DOMWheelEventDeltaModePropertyInfo = "DOMWheelEvent::delta-mode" attrGet _ = getDOMWheelEventDeltaMode attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "delta-x" -- Type: TBasicType TDouble -- Flags: [PropertyReadable] getDOMWheelEventDeltaX :: (MonadIO m, DOMWheelEventK o) => o -> m Double getDOMWheelEventDeltaX obj = liftIO $ getObjectPropertyDouble obj "delta-x" data DOMWheelEventDeltaXPropertyInfo instance AttrInfo DOMWheelEventDeltaXPropertyInfo where type AttrAllowedOps DOMWheelEventDeltaXPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMWheelEventDeltaXPropertyInfo = (~) () type AttrBaseTypeConstraint DOMWheelEventDeltaXPropertyInfo = DOMWheelEventK type AttrGetType DOMWheelEventDeltaXPropertyInfo = Double type AttrLabel DOMWheelEventDeltaXPropertyInfo = "DOMWheelEvent::delta-x" attrGet _ = getDOMWheelEventDeltaX attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "delta-y" -- Type: TBasicType TDouble -- Flags: [PropertyReadable] getDOMWheelEventDeltaY :: (MonadIO m, DOMWheelEventK o) => o -> m Double getDOMWheelEventDeltaY obj = liftIO $ getObjectPropertyDouble obj "delta-y" data DOMWheelEventDeltaYPropertyInfo instance AttrInfo DOMWheelEventDeltaYPropertyInfo where type AttrAllowedOps DOMWheelEventDeltaYPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMWheelEventDeltaYPropertyInfo = (~) () type AttrBaseTypeConstraint DOMWheelEventDeltaYPropertyInfo = DOMWheelEventK type AttrGetType DOMWheelEventDeltaYPropertyInfo = Double type AttrLabel DOMWheelEventDeltaYPropertyInfo = "DOMWheelEvent::delta-y" attrGet _ = getDOMWheelEventDeltaY attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "delta-z" -- Type: TBasicType TDouble -- Flags: [PropertyReadable] getDOMWheelEventDeltaZ :: (MonadIO m, DOMWheelEventK o) => o -> m Double getDOMWheelEventDeltaZ obj = liftIO $ getObjectPropertyDouble obj "delta-z" data DOMWheelEventDeltaZPropertyInfo instance AttrInfo DOMWheelEventDeltaZPropertyInfo where type AttrAllowedOps DOMWheelEventDeltaZPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMWheelEventDeltaZPropertyInfo = (~) () type AttrBaseTypeConstraint DOMWheelEventDeltaZPropertyInfo = DOMWheelEventK type AttrGetType DOMWheelEventDeltaZPropertyInfo = Double type AttrLabel DOMWheelEventDeltaZPropertyInfo = "DOMWheelEvent::delta-z" attrGet _ = getDOMWheelEventDeltaZ attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "webkit-direction-inverted-from-device" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMWheelEventWebkitDirectionInvertedFromDevice :: (MonadIO m, DOMWheelEventK o) => o -> m Bool getDOMWheelEventWebkitDirectionInvertedFromDevice obj = liftIO $ getObjectPropertyBool obj "webkit-direction-inverted-from-device" data DOMWheelEventWebkitDirectionInvertedFromDevicePropertyInfo instance AttrInfo DOMWheelEventWebkitDirectionInvertedFromDevicePropertyInfo where type AttrAllowedOps DOMWheelEventWebkitDirectionInvertedFromDevicePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMWheelEventWebkitDirectionInvertedFromDevicePropertyInfo = (~) () type AttrBaseTypeConstraint DOMWheelEventWebkitDirectionInvertedFromDevicePropertyInfo = DOMWheelEventK type AttrGetType DOMWheelEventWebkitDirectionInvertedFromDevicePropertyInfo = Bool type AttrLabel DOMWheelEventWebkitDirectionInvertedFromDevicePropertyInfo = "DOMWheelEvent::webkit-direction-inverted-from-device" attrGet _ = getDOMWheelEventWebkitDirectionInvertedFromDevice attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "wheel-delta" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMWheelEventWheelDelta :: (MonadIO m, DOMWheelEventK o) => o -> m Int64 getDOMWheelEventWheelDelta obj = liftIO $ getObjectPropertyInt64 obj "wheel-delta" data DOMWheelEventWheelDeltaPropertyInfo instance AttrInfo DOMWheelEventWheelDeltaPropertyInfo where type AttrAllowedOps DOMWheelEventWheelDeltaPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMWheelEventWheelDeltaPropertyInfo = (~) () type AttrBaseTypeConstraint DOMWheelEventWheelDeltaPropertyInfo = DOMWheelEventK type AttrGetType DOMWheelEventWheelDeltaPropertyInfo = Int64 type AttrLabel DOMWheelEventWheelDeltaPropertyInfo = "DOMWheelEvent::wheel-delta" attrGet _ = getDOMWheelEventWheelDelta attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "wheel-delta-x" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMWheelEventWheelDeltaX :: (MonadIO m, DOMWheelEventK o) => o -> m Int64 getDOMWheelEventWheelDeltaX obj = liftIO $ getObjectPropertyInt64 obj "wheel-delta-x" data DOMWheelEventWheelDeltaXPropertyInfo instance AttrInfo DOMWheelEventWheelDeltaXPropertyInfo where type AttrAllowedOps DOMWheelEventWheelDeltaXPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMWheelEventWheelDeltaXPropertyInfo = (~) () type AttrBaseTypeConstraint DOMWheelEventWheelDeltaXPropertyInfo = DOMWheelEventK type AttrGetType DOMWheelEventWheelDeltaXPropertyInfo = Int64 type AttrLabel DOMWheelEventWheelDeltaXPropertyInfo = "DOMWheelEvent::wheel-delta-x" attrGet _ = getDOMWheelEventWheelDeltaX attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "wheel-delta-y" -- Type: TBasicType TInt64 -- Flags: [PropertyReadable] getDOMWheelEventWheelDeltaY :: (MonadIO m, DOMWheelEventK o) => o -> m Int64 getDOMWheelEventWheelDeltaY obj = liftIO $ getObjectPropertyInt64 obj "wheel-delta-y" data DOMWheelEventWheelDeltaYPropertyInfo instance AttrInfo DOMWheelEventWheelDeltaYPropertyInfo where type AttrAllowedOps DOMWheelEventWheelDeltaYPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMWheelEventWheelDeltaYPropertyInfo = (~) () type AttrBaseTypeConstraint DOMWheelEventWheelDeltaYPropertyInfo = DOMWheelEventK type AttrGetType DOMWheelEventWheelDeltaYPropertyInfo = Int64 type AttrLabel DOMWheelEventWheelDeltaYPropertyInfo = "DOMWheelEvent::wheel-delta-y" attrGet _ = getDOMWheelEventWheelDeltaY attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMWheelEvent = '[ '("alt-key", DOMMouseEventAltKeyPropertyInfo), '("bubbles", DOMEventBubblesPropertyInfo), '("button", DOMMouseEventButtonPropertyInfo), '("cancel-bubble", DOMEventCancelBubblePropertyInfo), '("cancelable", DOMEventCancelablePropertyInfo), '("char-code", DOMUIEventCharCodePropertyInfo), '("client-x", DOMMouseEventClientXPropertyInfo), '("client-y", DOMMouseEventClientYPropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("ctrl-key", DOMMouseEventCtrlKeyPropertyInfo), '("current-target", DOMEventCurrentTargetPropertyInfo), '("default-prevented", DOMEventDefaultPreventedPropertyInfo), '("delta-mode", DOMWheelEventDeltaModePropertyInfo), '("delta-x", DOMWheelEventDeltaXPropertyInfo), '("delta-y", DOMWheelEventDeltaYPropertyInfo), '("delta-z", DOMWheelEventDeltaZPropertyInfo), '("detail", DOMUIEventDetailPropertyInfo), '("event-phase", DOMEventEventPhasePropertyInfo), '("from-element", DOMMouseEventFromElementPropertyInfo), '("key-code", DOMUIEventKeyCodePropertyInfo), '("layer-x", DOMUIEventLayerXPropertyInfo), '("layer-y", DOMUIEventLayerYPropertyInfo), '("meta-key", DOMMouseEventMetaKeyPropertyInfo), '("offset-x", DOMMouseEventOffsetXPropertyInfo), '("offset-y", DOMMouseEventOffsetYPropertyInfo), '("page-x", DOMUIEventPageXPropertyInfo), '("page-y", DOMUIEventPageYPropertyInfo), '("related-target", DOMMouseEventRelatedTargetPropertyInfo), '("return-value", DOMEventReturnValuePropertyInfo), '("screen-x", DOMMouseEventScreenXPropertyInfo), '("screen-y", DOMMouseEventScreenYPropertyInfo), '("shift-key", DOMMouseEventShiftKeyPropertyInfo), '("src-element", DOMEventSrcElementPropertyInfo), '("target", DOMEventTargetPropertyInfo), '("time-stamp", DOMEventTimeStampPropertyInfo), '("to-element", DOMMouseEventToElementPropertyInfo), '("type", DOMEventTypePropertyInfo), '("view", DOMUIEventViewPropertyInfo), '("webkit-direction-inverted-from-device", DOMWheelEventWebkitDirectionInvertedFromDevicePropertyInfo), '("webkit-movement-x", DOMMouseEventWebkitMovementXPropertyInfo), '("webkit-movement-y", DOMMouseEventWebkitMovementYPropertyInfo), '("wheel-delta", DOMWheelEventWheelDeltaPropertyInfo), '("wheel-delta-x", DOMWheelEventWheelDeltaXPropertyInfo), '("wheel-delta-y", DOMWheelEventWheelDeltaYPropertyInfo), '("which", DOMUIEventWhichPropertyInfo), '("x", DOMMouseEventXPropertyInfo), '("y", DOMMouseEventYPropertyInfo)] type instance AttributeList DOMXPathExpression = '[ '("core-object", DOMObjectCoreObjectPropertyInfo)] type instance AttributeList DOMXPathNSResolver = '[ '("core-object", DOMObjectCoreObjectPropertyInfo)] -- VVV Prop "boolean-value" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMXPathResultBooleanValue :: (MonadIO m, DOMXPathResultK o) => o -> m Bool getDOMXPathResultBooleanValue obj = liftIO $ getObjectPropertyBool obj "boolean-value" data DOMXPathResultBooleanValuePropertyInfo instance AttrInfo DOMXPathResultBooleanValuePropertyInfo where type AttrAllowedOps DOMXPathResultBooleanValuePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMXPathResultBooleanValuePropertyInfo = (~) () type AttrBaseTypeConstraint DOMXPathResultBooleanValuePropertyInfo = DOMXPathResultK type AttrGetType DOMXPathResultBooleanValuePropertyInfo = Bool type AttrLabel DOMXPathResultBooleanValuePropertyInfo = "DOMXPathResult::boolean-value" attrGet _ = getDOMXPathResultBooleanValue attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "invalid-iterator-state" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getDOMXPathResultInvalidIteratorState :: (MonadIO m, DOMXPathResultK o) => o -> m Bool getDOMXPathResultInvalidIteratorState obj = liftIO $ getObjectPropertyBool obj "invalid-iterator-state" data DOMXPathResultInvalidIteratorStatePropertyInfo instance AttrInfo DOMXPathResultInvalidIteratorStatePropertyInfo where type AttrAllowedOps DOMXPathResultInvalidIteratorStatePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMXPathResultInvalidIteratorStatePropertyInfo = (~) () type AttrBaseTypeConstraint DOMXPathResultInvalidIteratorStatePropertyInfo = DOMXPathResultK type AttrGetType DOMXPathResultInvalidIteratorStatePropertyInfo = Bool type AttrLabel DOMXPathResultInvalidIteratorStatePropertyInfo = "DOMXPathResult::invalid-iterator-state" attrGet _ = getDOMXPathResultInvalidIteratorState attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "number-value" -- Type: TBasicType TDouble -- Flags: [PropertyReadable] getDOMXPathResultNumberValue :: (MonadIO m, DOMXPathResultK o) => o -> m Double getDOMXPathResultNumberValue obj = liftIO $ getObjectPropertyDouble obj "number-value" data DOMXPathResultNumberValuePropertyInfo instance AttrInfo DOMXPathResultNumberValuePropertyInfo where type AttrAllowedOps DOMXPathResultNumberValuePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMXPathResultNumberValuePropertyInfo = (~) () type AttrBaseTypeConstraint DOMXPathResultNumberValuePropertyInfo = DOMXPathResultK type AttrGetType DOMXPathResultNumberValuePropertyInfo = Double type AttrLabel DOMXPathResultNumberValuePropertyInfo = "DOMXPathResult::number-value" attrGet _ = getDOMXPathResultNumberValue attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "result-type" -- Type: TBasicType TUInt32 -- Flags: [PropertyReadable] getDOMXPathResultResultType :: (MonadIO m, DOMXPathResultK o) => o -> m Word32 getDOMXPathResultResultType obj = liftIO $ getObjectPropertyCUInt obj "result-type" data DOMXPathResultResultTypePropertyInfo instance AttrInfo DOMXPathResultResultTypePropertyInfo where type AttrAllowedOps DOMXPathResultResultTypePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMXPathResultResultTypePropertyInfo = (~) () type AttrBaseTypeConstraint DOMXPathResultResultTypePropertyInfo = DOMXPathResultK type AttrGetType DOMXPathResultResultTypePropertyInfo = Word32 type AttrLabel DOMXPathResultResultTypePropertyInfo = "DOMXPathResult::result-type" attrGet _ = getDOMXPathResultResultType attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "single-node-value" -- Type: TInterface "WebKit" "DOMNode" -- Flags: [PropertyReadable] getDOMXPathResultSingleNodeValue :: (MonadIO m, DOMXPathResultK o) => o -> m DOMNode getDOMXPathResultSingleNodeValue obj = liftIO $ getObjectPropertyObject obj "single-node-value" DOMNode data DOMXPathResultSingleNodeValuePropertyInfo instance AttrInfo DOMXPathResultSingleNodeValuePropertyInfo where type AttrAllowedOps DOMXPathResultSingleNodeValuePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMXPathResultSingleNodeValuePropertyInfo = (~) () type AttrBaseTypeConstraint DOMXPathResultSingleNodeValuePropertyInfo = DOMXPathResultK type AttrGetType DOMXPathResultSingleNodeValuePropertyInfo = DOMNode type AttrLabel DOMXPathResultSingleNodeValuePropertyInfo = "DOMXPathResult::single-node-value" attrGet _ = getDOMXPathResultSingleNodeValue attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "snapshot-length" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDOMXPathResultSnapshotLength :: (MonadIO m, DOMXPathResultK o) => o -> m Word64 getDOMXPathResultSnapshotLength obj = liftIO $ getObjectPropertyUInt64 obj "snapshot-length" data DOMXPathResultSnapshotLengthPropertyInfo instance AttrInfo DOMXPathResultSnapshotLengthPropertyInfo where type AttrAllowedOps DOMXPathResultSnapshotLengthPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMXPathResultSnapshotLengthPropertyInfo = (~) () type AttrBaseTypeConstraint DOMXPathResultSnapshotLengthPropertyInfo = DOMXPathResultK type AttrGetType DOMXPathResultSnapshotLengthPropertyInfo = Word64 type AttrLabel DOMXPathResultSnapshotLengthPropertyInfo = "DOMXPathResult::snapshot-length" attrGet _ = getDOMXPathResultSnapshotLength attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "string-value" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDOMXPathResultStringValue :: (MonadIO m, DOMXPathResultK o) => o -> m T.Text getDOMXPathResultStringValue obj = liftIO $ getObjectPropertyString obj "string-value" data DOMXPathResultStringValuePropertyInfo instance AttrInfo DOMXPathResultStringValuePropertyInfo where type AttrAllowedOps DOMXPathResultStringValuePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DOMXPathResultStringValuePropertyInfo = (~) () type AttrBaseTypeConstraint DOMXPathResultStringValuePropertyInfo = DOMXPathResultK type AttrGetType DOMXPathResultStringValuePropertyInfo = T.Text type AttrLabel DOMXPathResultStringValuePropertyInfo = "DOMXPathResult::string-value" attrGet _ = getDOMXPathResultStringValue attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList DOMXPathResult = '[ '("boolean-value", DOMXPathResultBooleanValuePropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("invalid-iterator-state", DOMXPathResultInvalidIteratorStatePropertyInfo), '("number-value", DOMXPathResultNumberValuePropertyInfo), '("result-type", DOMXPathResultResultTypePropertyInfo), '("single-node-value", DOMXPathResultSingleNodeValuePropertyInfo), '("snapshot-length", DOMXPathResultSnapshotLengthPropertyInfo), '("string-value", DOMXPathResultStringValuePropertyInfo)] -- VVV Prop "current-size" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDownloadCurrentSize :: (MonadIO m, DownloadK o) => o -> m Word64 getDownloadCurrentSize obj = liftIO $ getObjectPropertyUInt64 obj "current-size" data DownloadCurrentSizePropertyInfo instance AttrInfo DownloadCurrentSizePropertyInfo where type AttrAllowedOps DownloadCurrentSizePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DownloadCurrentSizePropertyInfo = (~) () type AttrBaseTypeConstraint DownloadCurrentSizePropertyInfo = DownloadK type AttrGetType DownloadCurrentSizePropertyInfo = Word64 type AttrLabel DownloadCurrentSizePropertyInfo = "Download::current-size" attrGet _ = getDownloadCurrentSize attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "destination-uri" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getDownloadDestinationUri :: (MonadIO m, DownloadK o) => o -> m T.Text getDownloadDestinationUri obj = liftIO $ getObjectPropertyString obj "destination-uri" setDownloadDestinationUri :: (MonadIO m, DownloadK o) => o -> T.Text -> m () setDownloadDestinationUri obj val = liftIO $ setObjectPropertyString obj "destination-uri" val constructDownloadDestinationUri :: T.Text -> IO ([Char], GValue) constructDownloadDestinationUri val = constructObjectPropertyString "destination-uri" val data DownloadDestinationUriPropertyInfo instance AttrInfo DownloadDestinationUriPropertyInfo where type AttrAllowedOps DownloadDestinationUriPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DownloadDestinationUriPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DownloadDestinationUriPropertyInfo = DownloadK type AttrGetType DownloadDestinationUriPropertyInfo = T.Text type AttrLabel DownloadDestinationUriPropertyInfo = "Download::destination-uri" attrGet _ = getDownloadDestinationUri attrSet _ = setDownloadDestinationUri attrConstruct _ = constructDownloadDestinationUri -- VVV Prop "network-request" -- Type: TInterface "WebKit" "NetworkRequest" -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly] getDownloadNetworkRequest :: (MonadIO m, DownloadK o) => o -> m NetworkRequest getDownloadNetworkRequest obj = liftIO $ getObjectPropertyObject obj "network-request" NetworkRequest constructDownloadNetworkRequest :: (NetworkRequestK a) => a -> IO ([Char], GValue) constructDownloadNetworkRequest val = constructObjectPropertyObject "network-request" val data DownloadNetworkRequestPropertyInfo instance AttrInfo DownloadNetworkRequestPropertyInfo where type AttrAllowedOps DownloadNetworkRequestPropertyInfo = '[ 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DownloadNetworkRequestPropertyInfo = NetworkRequestK type AttrBaseTypeConstraint DownloadNetworkRequestPropertyInfo = DownloadK type AttrGetType DownloadNetworkRequestPropertyInfo = NetworkRequest type AttrLabel DownloadNetworkRequestPropertyInfo = "Download::network-request" attrGet _ = getDownloadNetworkRequest attrSet _ = undefined attrConstruct _ = constructDownloadNetworkRequest -- VVV Prop "network-response" -- Type: TInterface "WebKit" "NetworkResponse" -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly] getDownloadNetworkResponse :: (MonadIO m, DownloadK o) => o -> m NetworkResponse getDownloadNetworkResponse obj = liftIO $ getObjectPropertyObject obj "network-response" NetworkResponse constructDownloadNetworkResponse :: (NetworkResponseK a) => a -> IO ([Char], GValue) constructDownloadNetworkResponse val = constructObjectPropertyObject "network-response" val data DownloadNetworkResponsePropertyInfo instance AttrInfo DownloadNetworkResponsePropertyInfo where type AttrAllowedOps DownloadNetworkResponsePropertyInfo = '[ 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DownloadNetworkResponsePropertyInfo = NetworkResponseK type AttrBaseTypeConstraint DownloadNetworkResponsePropertyInfo = DownloadK type AttrGetType DownloadNetworkResponsePropertyInfo = NetworkResponse type AttrLabel DownloadNetworkResponsePropertyInfo = "Download::network-response" attrGet _ = getDownloadNetworkResponse attrSet _ = undefined attrConstruct _ = constructDownloadNetworkResponse -- VVV Prop "progress" -- Type: TBasicType TDouble -- Flags: [PropertyReadable] getDownloadProgress :: (MonadIO m, DownloadK o) => o -> m Double getDownloadProgress obj = liftIO $ getObjectPropertyDouble obj "progress" data DownloadProgressPropertyInfo instance AttrInfo DownloadProgressPropertyInfo where type AttrAllowedOps DownloadProgressPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DownloadProgressPropertyInfo = (~) () type AttrBaseTypeConstraint DownloadProgressPropertyInfo = DownloadK type AttrGetType DownloadProgressPropertyInfo = Double type AttrLabel DownloadProgressPropertyInfo = "Download::progress" attrGet _ = getDownloadProgress attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "status" -- Type: TInterface "WebKit" "DownloadStatus" -- Flags: [PropertyReadable] getDownloadStatus :: (MonadIO m, DownloadK o) => o -> m DownloadStatus getDownloadStatus obj = liftIO $ getObjectPropertyEnum obj "status" data DownloadStatusPropertyInfo instance AttrInfo DownloadStatusPropertyInfo where type AttrAllowedOps DownloadStatusPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DownloadStatusPropertyInfo = (~) () type AttrBaseTypeConstraint DownloadStatusPropertyInfo = DownloadK type AttrGetType DownloadStatusPropertyInfo = DownloadStatus type AttrLabel DownloadStatusPropertyInfo = "Download::status" attrGet _ = getDownloadStatus attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "suggested-filename" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getDownloadSuggestedFilename :: (MonadIO m, DownloadK o) => o -> m T.Text getDownloadSuggestedFilename obj = liftIO $ getObjectPropertyString obj "suggested-filename" data DownloadSuggestedFilenamePropertyInfo instance AttrInfo DownloadSuggestedFilenamePropertyInfo where type AttrAllowedOps DownloadSuggestedFilenamePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DownloadSuggestedFilenamePropertyInfo = (~) () type AttrBaseTypeConstraint DownloadSuggestedFilenamePropertyInfo = DownloadK type AttrGetType DownloadSuggestedFilenamePropertyInfo = T.Text type AttrLabel DownloadSuggestedFilenamePropertyInfo = "Download::suggested-filename" attrGet _ = getDownloadSuggestedFilename attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "total-size" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getDownloadTotalSize :: (MonadIO m, DownloadK o) => o -> m Word64 getDownloadTotalSize obj = liftIO $ getObjectPropertyUInt64 obj "total-size" data DownloadTotalSizePropertyInfo instance AttrInfo DownloadTotalSizePropertyInfo where type AttrAllowedOps DownloadTotalSizePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DownloadTotalSizePropertyInfo = (~) () type AttrBaseTypeConstraint DownloadTotalSizePropertyInfo = DownloadK type AttrGetType DownloadTotalSizePropertyInfo = Word64 type AttrLabel DownloadTotalSizePropertyInfo = "Download::total-size" attrGet _ = getDownloadTotalSize attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList Download = '[ '("current-size", DownloadCurrentSizePropertyInfo), '("destination-uri", DownloadDestinationUriPropertyInfo), '("network-request", DownloadNetworkRequestPropertyInfo), '("network-response", DownloadNetworkResponsePropertyInfo), '("progress", DownloadProgressPropertyInfo), '("status", DownloadStatusPropertyInfo), '("suggested-filename", DownloadSuggestedFilenamePropertyInfo), '("total-size", DownloadTotalSizePropertyInfo)] -- VVV Prop "path" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getFaviconDatabasePath :: (MonadIO m, FaviconDatabaseK o) => o -> m T.Text getFaviconDatabasePath obj = liftIO $ getObjectPropertyString obj "path" setFaviconDatabasePath :: (MonadIO m, FaviconDatabaseK o) => o -> T.Text -> m () setFaviconDatabasePath obj val = liftIO $ setObjectPropertyString obj "path" val constructFaviconDatabasePath :: T.Text -> IO ([Char], GValue) constructFaviconDatabasePath val = constructObjectPropertyString "path" val data FaviconDatabasePathPropertyInfo instance AttrInfo FaviconDatabasePathPropertyInfo where type AttrAllowedOps FaviconDatabasePathPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint FaviconDatabasePathPropertyInfo = (~) T.Text type AttrBaseTypeConstraint FaviconDatabasePathPropertyInfo = FaviconDatabaseK type AttrGetType FaviconDatabasePathPropertyInfo = T.Text type AttrLabel FaviconDatabasePathPropertyInfo = "FaviconDatabase::path" attrGet _ = getFaviconDatabasePath attrSet _ = setFaviconDatabasePath attrConstruct _ = constructFaviconDatabasePath type instance AttributeList FaviconDatabase = '[ '("path", FaviconDatabasePathPropertyInfo)] -- VVV Prop "filter" -- Type: TInterface "Gtk" "FileFilter" -- Flags: [PropertyReadable] getFileChooserRequestFilter :: (MonadIO m, FileChooserRequestK o) => o -> m Gtk.FileFilter getFileChooserRequestFilter obj = liftIO $ getObjectPropertyObject obj "filter" Gtk.FileFilter data FileChooserRequestFilterPropertyInfo instance AttrInfo FileChooserRequestFilterPropertyInfo where type AttrAllowedOps FileChooserRequestFilterPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint FileChooserRequestFilterPropertyInfo = (~) () type AttrBaseTypeConstraint FileChooserRequestFilterPropertyInfo = FileChooserRequestK type AttrGetType FileChooserRequestFilterPropertyInfo = Gtk.FileFilter type AttrLabel FileChooserRequestFilterPropertyInfo = "FileChooserRequest::filter" attrGet _ = getFileChooserRequestFilter attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "mime-types" -- Type: TCArray True (-1) (-1) (TBasicType TUTF8) -- Flags: [PropertyReadable] getFileChooserRequestMimeTypes :: (MonadIO m, FileChooserRequestK o) => o -> m [T.Text] getFileChooserRequestMimeTypes obj = liftIO $ getObjectPropertyStringArray obj "mime-types" data FileChooserRequestMimeTypesPropertyInfo instance AttrInfo FileChooserRequestMimeTypesPropertyInfo where type AttrAllowedOps FileChooserRequestMimeTypesPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint FileChooserRequestMimeTypesPropertyInfo = (~) () type AttrBaseTypeConstraint FileChooserRequestMimeTypesPropertyInfo = FileChooserRequestK type AttrGetType FileChooserRequestMimeTypesPropertyInfo = [T.Text] type AttrLabel FileChooserRequestMimeTypesPropertyInfo = "FileChooserRequest::mime-types" attrGet _ = getFileChooserRequestMimeTypes attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "select-multiple" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getFileChooserRequestSelectMultiple :: (MonadIO m, FileChooserRequestK o) => o -> m Bool getFileChooserRequestSelectMultiple obj = liftIO $ getObjectPropertyBool obj "select-multiple" data FileChooserRequestSelectMultiplePropertyInfo instance AttrInfo FileChooserRequestSelectMultiplePropertyInfo where type AttrAllowedOps FileChooserRequestSelectMultiplePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint FileChooserRequestSelectMultiplePropertyInfo = (~) () type AttrBaseTypeConstraint FileChooserRequestSelectMultiplePropertyInfo = FileChooserRequestK type AttrGetType FileChooserRequestSelectMultiplePropertyInfo = Bool type AttrLabel FileChooserRequestSelectMultiplePropertyInfo = "FileChooserRequest::select-multiple" attrGet _ = getFileChooserRequestSelectMultiple attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "selected-files" -- Type: TCArray True (-1) (-1) (TBasicType TUTF8) -- Flags: [PropertyReadable] getFileChooserRequestSelectedFiles :: (MonadIO m, FileChooserRequestK o) => o -> m [T.Text] getFileChooserRequestSelectedFiles obj = liftIO $ getObjectPropertyStringArray obj "selected-files" data FileChooserRequestSelectedFilesPropertyInfo instance AttrInfo FileChooserRequestSelectedFilesPropertyInfo where type AttrAllowedOps FileChooserRequestSelectedFilesPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint FileChooserRequestSelectedFilesPropertyInfo = (~) () type AttrBaseTypeConstraint FileChooserRequestSelectedFilesPropertyInfo = FileChooserRequestK type AttrGetType FileChooserRequestSelectedFilesPropertyInfo = [T.Text] type AttrLabel FileChooserRequestSelectedFilesPropertyInfo = "FileChooserRequest::selected-files" attrGet _ = getFileChooserRequestSelectedFiles attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList FileChooserRequest = '[ '("filter", FileChooserRequestFilterPropertyInfo), '("mime-types", FileChooserRequestMimeTypesPropertyInfo), '("select-multiple", FileChooserRequestSelectMultiplePropertyInfo), '("selected-files", FileChooserRequestSelectedFilesPropertyInfo)] type instance AttributeList GeolocationPolicyDecision = '[ ] -- VVV Prop "context" -- Type: TInterface "WebKit" "HitTestResultContext" -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly] getHitTestResultContext :: (MonadIO m, HitTestResultK o) => o -> m [HitTestResultContext] getHitTestResultContext obj = liftIO $ getObjectPropertyFlags obj "context" constructHitTestResultContext :: [HitTestResultContext] -> IO ([Char], GValue) constructHitTestResultContext val = constructObjectPropertyFlags "context" val data HitTestResultContextPropertyInfo instance AttrInfo HitTestResultContextPropertyInfo where type AttrAllowedOps HitTestResultContextPropertyInfo = '[ 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint HitTestResultContextPropertyInfo = (~) [HitTestResultContext] type AttrBaseTypeConstraint HitTestResultContextPropertyInfo = HitTestResultK type AttrGetType HitTestResultContextPropertyInfo = [HitTestResultContext] type AttrLabel HitTestResultContextPropertyInfo = "HitTestResult::context" attrGet _ = getHitTestResultContext attrSet _ = undefined attrConstruct _ = constructHitTestResultContext -- VVV Prop "image-uri" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly] getHitTestResultImageUri :: (MonadIO m, HitTestResultK o) => o -> m T.Text getHitTestResultImageUri obj = liftIO $ getObjectPropertyString obj "image-uri" constructHitTestResultImageUri :: T.Text -> IO ([Char], GValue) constructHitTestResultImageUri val = constructObjectPropertyString "image-uri" val data HitTestResultImageUriPropertyInfo instance AttrInfo HitTestResultImageUriPropertyInfo where type AttrAllowedOps HitTestResultImageUriPropertyInfo = '[ 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint HitTestResultImageUriPropertyInfo = (~) T.Text type AttrBaseTypeConstraint HitTestResultImageUriPropertyInfo = HitTestResultK type AttrGetType HitTestResultImageUriPropertyInfo = T.Text type AttrLabel HitTestResultImageUriPropertyInfo = "HitTestResult::image-uri" attrGet _ = getHitTestResultImageUri attrSet _ = undefined attrConstruct _ = constructHitTestResultImageUri -- VVV Prop "inner-node" -- Type: TInterface "WebKit" "DOMNode" -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly] getHitTestResultInnerNode :: (MonadIO m, HitTestResultK o) => o -> m DOMNode getHitTestResultInnerNode obj = liftIO $ getObjectPropertyObject obj "inner-node" DOMNode constructHitTestResultInnerNode :: (DOMNodeK a) => a -> IO ([Char], GValue) constructHitTestResultInnerNode val = constructObjectPropertyObject "inner-node" val data HitTestResultInnerNodePropertyInfo instance AttrInfo HitTestResultInnerNodePropertyInfo where type AttrAllowedOps HitTestResultInnerNodePropertyInfo = '[ 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint HitTestResultInnerNodePropertyInfo = DOMNodeK type AttrBaseTypeConstraint HitTestResultInnerNodePropertyInfo = HitTestResultK type AttrGetType HitTestResultInnerNodePropertyInfo = DOMNode type AttrLabel HitTestResultInnerNodePropertyInfo = "HitTestResult::inner-node" attrGet _ = getHitTestResultInnerNode attrSet _ = undefined attrConstruct _ = constructHitTestResultInnerNode -- VVV Prop "link-uri" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly] getHitTestResultLinkUri :: (MonadIO m, HitTestResultK o) => o -> m T.Text getHitTestResultLinkUri obj = liftIO $ getObjectPropertyString obj "link-uri" constructHitTestResultLinkUri :: T.Text -> IO ([Char], GValue) constructHitTestResultLinkUri val = constructObjectPropertyString "link-uri" val data HitTestResultLinkUriPropertyInfo instance AttrInfo HitTestResultLinkUriPropertyInfo where type AttrAllowedOps HitTestResultLinkUriPropertyInfo = '[ 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint HitTestResultLinkUriPropertyInfo = (~) T.Text type AttrBaseTypeConstraint HitTestResultLinkUriPropertyInfo = HitTestResultK type AttrGetType HitTestResultLinkUriPropertyInfo = T.Text type AttrLabel HitTestResultLinkUriPropertyInfo = "HitTestResult::link-uri" attrGet _ = getHitTestResultLinkUri attrSet _ = undefined attrConstruct _ = constructHitTestResultLinkUri -- VVV Prop "media-uri" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly] getHitTestResultMediaUri :: (MonadIO m, HitTestResultK o) => o -> m T.Text getHitTestResultMediaUri obj = liftIO $ getObjectPropertyString obj "media-uri" constructHitTestResultMediaUri :: T.Text -> IO ([Char], GValue) constructHitTestResultMediaUri val = constructObjectPropertyString "media-uri" val data HitTestResultMediaUriPropertyInfo instance AttrInfo HitTestResultMediaUriPropertyInfo where type AttrAllowedOps HitTestResultMediaUriPropertyInfo = '[ 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint HitTestResultMediaUriPropertyInfo = (~) T.Text type AttrBaseTypeConstraint HitTestResultMediaUriPropertyInfo = HitTestResultK type AttrGetType HitTestResultMediaUriPropertyInfo = T.Text type AttrLabel HitTestResultMediaUriPropertyInfo = "HitTestResult::media-uri" attrGet _ = getHitTestResultMediaUri attrSet _ = undefined attrConstruct _ = constructHitTestResultMediaUri -- VVV Prop "x" -- Type: TBasicType TInt32 -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly] getHitTestResultX :: (MonadIO m, HitTestResultK o) => o -> m Int32 getHitTestResultX obj = liftIO $ getObjectPropertyCInt obj "x" constructHitTestResultX :: Int32 -> IO ([Char], GValue) constructHitTestResultX val = constructObjectPropertyCInt "x" val data HitTestResultXPropertyInfo instance AttrInfo HitTestResultXPropertyInfo where type AttrAllowedOps HitTestResultXPropertyInfo = '[ 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint HitTestResultXPropertyInfo = (~) Int32 type AttrBaseTypeConstraint HitTestResultXPropertyInfo = HitTestResultK type AttrGetType HitTestResultXPropertyInfo = Int32 type AttrLabel HitTestResultXPropertyInfo = "HitTestResult::x" attrGet _ = getHitTestResultX attrSet _ = undefined attrConstruct _ = constructHitTestResultX -- VVV Prop "y" -- Type: TBasicType TInt32 -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly] getHitTestResultY :: (MonadIO m, HitTestResultK o) => o -> m Int32 getHitTestResultY obj = liftIO $ getObjectPropertyCInt obj "y" constructHitTestResultY :: Int32 -> IO ([Char], GValue) constructHitTestResultY val = constructObjectPropertyCInt "y" val data HitTestResultYPropertyInfo instance AttrInfo HitTestResultYPropertyInfo where type AttrAllowedOps HitTestResultYPropertyInfo = '[ 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint HitTestResultYPropertyInfo = (~) Int32 type AttrBaseTypeConstraint HitTestResultYPropertyInfo = HitTestResultK type AttrGetType HitTestResultYPropertyInfo = Int32 type AttrLabel HitTestResultYPropertyInfo = "HitTestResult::y" attrGet _ = getHitTestResultY attrSet _ = undefined attrConstruct _ = constructHitTestResultY type instance AttributeList HitTestResult = '[ '("context", HitTestResultContextPropertyInfo), '("image-uri", HitTestResultImageUriPropertyInfo), '("inner-node", HitTestResultInnerNodePropertyInfo), '("link-uri", HitTestResultLinkUriPropertyInfo), '("media-uri", HitTestResultMediaUriPropertyInfo), '("x", HitTestResultXPropertyInfo), '("y", HitTestResultYPropertyInfo)] -- VVV Prop "path" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getIconDatabasePath :: (MonadIO m, IconDatabaseK o) => o -> m T.Text getIconDatabasePath obj = liftIO $ getObjectPropertyString obj "path" setIconDatabasePath :: (MonadIO m, IconDatabaseK o) => o -> T.Text -> m () setIconDatabasePath obj val = liftIO $ setObjectPropertyString obj "path" val constructIconDatabasePath :: T.Text -> IO ([Char], GValue) constructIconDatabasePath val = constructObjectPropertyString "path" val data IconDatabasePathPropertyInfo instance AttrInfo IconDatabasePathPropertyInfo where type AttrAllowedOps IconDatabasePathPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint IconDatabasePathPropertyInfo = (~) T.Text type AttrBaseTypeConstraint IconDatabasePathPropertyInfo = IconDatabaseK type AttrGetType IconDatabasePathPropertyInfo = T.Text type AttrLabel IconDatabasePathPropertyInfo = "IconDatabase::path" attrGet _ = getIconDatabasePath attrSet _ = setIconDatabasePath attrConstruct _ = constructIconDatabasePath type instance AttributeList IconDatabase = '[ '("path", IconDatabasePathPropertyInfo)] -- VVV Prop "message" -- Type: TInterface "Soup" "Message" -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly] getNetworkRequestMessage :: (MonadIO m, NetworkRequestK o) => o -> m Soup.Message getNetworkRequestMessage obj = liftIO $ getObjectPropertyObject obj "message" Soup.Message constructNetworkRequestMessage :: (Soup.MessageK a) => a -> IO ([Char], GValue) constructNetworkRequestMessage val = constructObjectPropertyObject "message" val data NetworkRequestMessagePropertyInfo instance AttrInfo NetworkRequestMessagePropertyInfo where type AttrAllowedOps NetworkRequestMessagePropertyInfo = '[ 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint NetworkRequestMessagePropertyInfo = Soup.MessageK type AttrBaseTypeConstraint NetworkRequestMessagePropertyInfo = NetworkRequestK type AttrGetType NetworkRequestMessagePropertyInfo = Soup.Message type AttrLabel NetworkRequestMessagePropertyInfo = "NetworkRequest::message" attrGet _ = getNetworkRequestMessage attrSet _ = undefined attrConstruct _ = constructNetworkRequestMessage -- VVV Prop "uri" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getNetworkRequestUri :: (MonadIO m, NetworkRequestK o) => o -> m T.Text getNetworkRequestUri obj = liftIO $ getObjectPropertyString obj "uri" setNetworkRequestUri :: (MonadIO m, NetworkRequestK o) => o -> T.Text -> m () setNetworkRequestUri obj val = liftIO $ setObjectPropertyString obj "uri" val constructNetworkRequestUri :: T.Text -> IO ([Char], GValue) constructNetworkRequestUri val = constructObjectPropertyString "uri" val data NetworkRequestUriPropertyInfo instance AttrInfo NetworkRequestUriPropertyInfo where type AttrAllowedOps NetworkRequestUriPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint NetworkRequestUriPropertyInfo = (~) T.Text type AttrBaseTypeConstraint NetworkRequestUriPropertyInfo = NetworkRequestK type AttrGetType NetworkRequestUriPropertyInfo = T.Text type AttrLabel NetworkRequestUriPropertyInfo = "NetworkRequest::uri" attrGet _ = getNetworkRequestUri attrSet _ = setNetworkRequestUri attrConstruct _ = constructNetworkRequestUri type instance AttributeList NetworkRequest = '[ '("message", NetworkRequestMessagePropertyInfo), '("uri", NetworkRequestUriPropertyInfo)] -- VVV Prop "message" -- Type: TInterface "Soup" "Message" -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly] getNetworkResponseMessage :: (MonadIO m, NetworkResponseK o) => o -> m Soup.Message getNetworkResponseMessage obj = liftIO $ getObjectPropertyObject obj "message" Soup.Message constructNetworkResponseMessage :: (Soup.MessageK a) => a -> IO ([Char], GValue) constructNetworkResponseMessage val = constructObjectPropertyObject "message" val data NetworkResponseMessagePropertyInfo instance AttrInfo NetworkResponseMessagePropertyInfo where type AttrAllowedOps NetworkResponseMessagePropertyInfo = '[ 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint NetworkResponseMessagePropertyInfo = Soup.MessageK type AttrBaseTypeConstraint NetworkResponseMessagePropertyInfo = NetworkResponseK type AttrGetType NetworkResponseMessagePropertyInfo = Soup.Message type AttrLabel NetworkResponseMessagePropertyInfo = "NetworkResponse::message" attrGet _ = getNetworkResponseMessage attrSet _ = undefined attrConstruct _ = constructNetworkResponseMessage -- VVV Prop "suggested-filename" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getNetworkResponseSuggestedFilename :: (MonadIO m, NetworkResponseK o) => o -> m T.Text getNetworkResponseSuggestedFilename obj = liftIO $ getObjectPropertyString obj "suggested-filename" data NetworkResponseSuggestedFilenamePropertyInfo instance AttrInfo NetworkResponseSuggestedFilenamePropertyInfo where type AttrAllowedOps NetworkResponseSuggestedFilenamePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint NetworkResponseSuggestedFilenamePropertyInfo = (~) () type AttrBaseTypeConstraint NetworkResponseSuggestedFilenamePropertyInfo = NetworkResponseK type AttrGetType NetworkResponseSuggestedFilenamePropertyInfo = T.Text type AttrLabel NetworkResponseSuggestedFilenamePropertyInfo = "NetworkResponse::suggested-filename" attrGet _ = getNetworkResponseSuggestedFilename attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "uri" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getNetworkResponseUri :: (MonadIO m, NetworkResponseK o) => o -> m T.Text getNetworkResponseUri obj = liftIO $ getObjectPropertyString obj "uri" setNetworkResponseUri :: (MonadIO m, NetworkResponseK o) => o -> T.Text -> m () setNetworkResponseUri obj val = liftIO $ setObjectPropertyString obj "uri" val constructNetworkResponseUri :: T.Text -> IO ([Char], GValue) constructNetworkResponseUri val = constructObjectPropertyString "uri" val data NetworkResponseUriPropertyInfo instance AttrInfo NetworkResponseUriPropertyInfo where type AttrAllowedOps NetworkResponseUriPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint NetworkResponseUriPropertyInfo = (~) T.Text type AttrBaseTypeConstraint NetworkResponseUriPropertyInfo = NetworkResponseK type AttrGetType NetworkResponseUriPropertyInfo = T.Text type AttrLabel NetworkResponseUriPropertyInfo = "NetworkResponse::uri" attrGet _ = getNetworkResponseUri attrSet _ = setNetworkResponseUri attrConstruct _ = constructNetworkResponseUri type instance AttributeList NetworkResponse = '[ '("message", NetworkResponseMessagePropertyInfo), '("suggested-filename", NetworkResponseSuggestedFilenamePropertyInfo), '("uri", NetworkResponseUriPropertyInfo)] -- VVV Prop "host" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getSecurityOriginHost :: (MonadIO m, SecurityOriginK o) => o -> m T.Text getSecurityOriginHost obj = liftIO $ getObjectPropertyString obj "host" data SecurityOriginHostPropertyInfo instance AttrInfo SecurityOriginHostPropertyInfo where type AttrAllowedOps SecurityOriginHostPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint SecurityOriginHostPropertyInfo = (~) () type AttrBaseTypeConstraint SecurityOriginHostPropertyInfo = SecurityOriginK type AttrGetType SecurityOriginHostPropertyInfo = T.Text type AttrLabel SecurityOriginHostPropertyInfo = "SecurityOrigin::host" attrGet _ = getSecurityOriginHost attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "port" -- Type: TBasicType TUInt32 -- Flags: [PropertyReadable] getSecurityOriginPort :: (MonadIO m, SecurityOriginK o) => o -> m Word32 getSecurityOriginPort obj = liftIO $ getObjectPropertyCUInt obj "port" data SecurityOriginPortPropertyInfo instance AttrInfo SecurityOriginPortPropertyInfo where type AttrAllowedOps SecurityOriginPortPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint SecurityOriginPortPropertyInfo = (~) () type AttrBaseTypeConstraint SecurityOriginPortPropertyInfo = SecurityOriginK type AttrGetType SecurityOriginPortPropertyInfo = Word32 type AttrLabel SecurityOriginPortPropertyInfo = "SecurityOrigin::port" attrGet _ = getSecurityOriginPort attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "protocol" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getSecurityOriginProtocol :: (MonadIO m, SecurityOriginK o) => o -> m T.Text getSecurityOriginProtocol obj = liftIO $ getObjectPropertyString obj "protocol" data SecurityOriginProtocolPropertyInfo instance AttrInfo SecurityOriginProtocolPropertyInfo where type AttrAllowedOps SecurityOriginProtocolPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint SecurityOriginProtocolPropertyInfo = (~) () type AttrBaseTypeConstraint SecurityOriginProtocolPropertyInfo = SecurityOriginK type AttrGetType SecurityOriginProtocolPropertyInfo = T.Text type AttrLabel SecurityOriginProtocolPropertyInfo = "SecurityOrigin::protocol" attrGet _ = getSecurityOriginProtocol attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "web-database-quota" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable,PropertyWritable] getSecurityOriginWebDatabaseQuota :: (MonadIO m, SecurityOriginK o) => o -> m Word64 getSecurityOriginWebDatabaseQuota obj = liftIO $ getObjectPropertyUInt64 obj "web-database-quota" setSecurityOriginWebDatabaseQuota :: (MonadIO m, SecurityOriginK o) => o -> Word64 -> m () setSecurityOriginWebDatabaseQuota obj val = liftIO $ setObjectPropertyUInt64 obj "web-database-quota" val constructSecurityOriginWebDatabaseQuota :: Word64 -> IO ([Char], GValue) constructSecurityOriginWebDatabaseQuota val = constructObjectPropertyUInt64 "web-database-quota" val data SecurityOriginWebDatabaseQuotaPropertyInfo instance AttrInfo SecurityOriginWebDatabaseQuotaPropertyInfo where type AttrAllowedOps SecurityOriginWebDatabaseQuotaPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint SecurityOriginWebDatabaseQuotaPropertyInfo = (~) Word64 type AttrBaseTypeConstraint SecurityOriginWebDatabaseQuotaPropertyInfo = SecurityOriginK type AttrGetType SecurityOriginWebDatabaseQuotaPropertyInfo = Word64 type AttrLabel SecurityOriginWebDatabaseQuotaPropertyInfo = "SecurityOrigin::web-database-quota" attrGet _ = getSecurityOriginWebDatabaseQuota attrSet _ = setSecurityOriginWebDatabaseQuota attrConstruct _ = constructSecurityOriginWebDatabaseQuota -- VVV Prop "web-database-usage" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getSecurityOriginWebDatabaseUsage :: (MonadIO m, SecurityOriginK o) => o -> m Word64 getSecurityOriginWebDatabaseUsage obj = liftIO $ getObjectPropertyUInt64 obj "web-database-usage" data SecurityOriginWebDatabaseUsagePropertyInfo instance AttrInfo SecurityOriginWebDatabaseUsagePropertyInfo where type AttrAllowedOps SecurityOriginWebDatabaseUsagePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint SecurityOriginWebDatabaseUsagePropertyInfo = (~) () type AttrBaseTypeConstraint SecurityOriginWebDatabaseUsagePropertyInfo = SecurityOriginK type AttrGetType SecurityOriginWebDatabaseUsagePropertyInfo = Word64 type AttrLabel SecurityOriginWebDatabaseUsagePropertyInfo = "SecurityOrigin::web-database-usage" attrGet _ = getSecurityOriginWebDatabaseUsage attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList SecurityOrigin = '[ '("host", SecurityOriginHostPropertyInfo), '("port", SecurityOriginPortPropertyInfo), '("protocol", SecurityOriginProtocolPropertyInfo), '("web-database-quota", SecurityOriginWebDatabaseQuotaPropertyInfo), '("web-database-usage", SecurityOriginWebDatabaseUsagePropertyInfo)] type instance AttributeList SoupAuthDialog = '[ ] type instance AttributeList SpellChecker = '[ ] -- VVV Prop "available-height" -- Type: TBasicType TInt32 -- Flags: [PropertyReadable,PropertyWritable] getViewportAttributesAvailableHeight :: (MonadIO m, ViewportAttributesK o) => o -> m Int32 getViewportAttributesAvailableHeight obj = liftIO $ getObjectPropertyCInt obj "available-height" setViewportAttributesAvailableHeight :: (MonadIO m, ViewportAttributesK o) => o -> Int32 -> m () setViewportAttributesAvailableHeight obj val = liftIO $ setObjectPropertyCInt obj "available-height" val constructViewportAttributesAvailableHeight :: Int32 -> IO ([Char], GValue) constructViewportAttributesAvailableHeight val = constructObjectPropertyCInt "available-height" val data ViewportAttributesAvailableHeightPropertyInfo instance AttrInfo ViewportAttributesAvailableHeightPropertyInfo where type AttrAllowedOps ViewportAttributesAvailableHeightPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint ViewportAttributesAvailableHeightPropertyInfo = (~) Int32 type AttrBaseTypeConstraint ViewportAttributesAvailableHeightPropertyInfo = ViewportAttributesK type AttrGetType ViewportAttributesAvailableHeightPropertyInfo = Int32 type AttrLabel ViewportAttributesAvailableHeightPropertyInfo = "ViewportAttributes::available-height" attrGet _ = getViewportAttributesAvailableHeight attrSet _ = setViewportAttributesAvailableHeight attrConstruct _ = constructViewportAttributesAvailableHeight -- VVV Prop "available-width" -- Type: TBasicType TInt32 -- Flags: [PropertyReadable,PropertyWritable] getViewportAttributesAvailableWidth :: (MonadIO m, ViewportAttributesK o) => o -> m Int32 getViewportAttributesAvailableWidth obj = liftIO $ getObjectPropertyCInt obj "available-width" setViewportAttributesAvailableWidth :: (MonadIO m, ViewportAttributesK o) => o -> Int32 -> m () setViewportAttributesAvailableWidth obj val = liftIO $ setObjectPropertyCInt obj "available-width" val constructViewportAttributesAvailableWidth :: Int32 -> IO ([Char], GValue) constructViewportAttributesAvailableWidth val = constructObjectPropertyCInt "available-width" val data ViewportAttributesAvailableWidthPropertyInfo instance AttrInfo ViewportAttributesAvailableWidthPropertyInfo where type AttrAllowedOps ViewportAttributesAvailableWidthPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint ViewportAttributesAvailableWidthPropertyInfo = (~) Int32 type AttrBaseTypeConstraint ViewportAttributesAvailableWidthPropertyInfo = ViewportAttributesK type AttrGetType ViewportAttributesAvailableWidthPropertyInfo = Int32 type AttrLabel ViewportAttributesAvailableWidthPropertyInfo = "ViewportAttributes::available-width" attrGet _ = getViewportAttributesAvailableWidth attrSet _ = setViewportAttributesAvailableWidth attrConstruct _ = constructViewportAttributesAvailableWidth -- VVV Prop "desktop-width" -- Type: TBasicType TInt32 -- Flags: [PropertyReadable,PropertyWritable] getViewportAttributesDesktopWidth :: (MonadIO m, ViewportAttributesK o) => o -> m Int32 getViewportAttributesDesktopWidth obj = liftIO $ getObjectPropertyCInt obj "desktop-width" setViewportAttributesDesktopWidth :: (MonadIO m, ViewportAttributesK o) => o -> Int32 -> m () setViewportAttributesDesktopWidth obj val = liftIO $ setObjectPropertyCInt obj "desktop-width" val constructViewportAttributesDesktopWidth :: Int32 -> IO ([Char], GValue) constructViewportAttributesDesktopWidth val = constructObjectPropertyCInt "desktop-width" val data ViewportAttributesDesktopWidthPropertyInfo instance AttrInfo ViewportAttributesDesktopWidthPropertyInfo where type AttrAllowedOps ViewportAttributesDesktopWidthPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint ViewportAttributesDesktopWidthPropertyInfo = (~) Int32 type AttrBaseTypeConstraint ViewportAttributesDesktopWidthPropertyInfo = ViewportAttributesK type AttrGetType ViewportAttributesDesktopWidthPropertyInfo = Int32 type AttrLabel ViewportAttributesDesktopWidthPropertyInfo = "ViewportAttributes::desktop-width" attrGet _ = getViewportAttributesDesktopWidth attrSet _ = setViewportAttributesDesktopWidth attrConstruct _ = constructViewportAttributesDesktopWidth -- VVV Prop "device-dpi" -- Type: TBasicType TInt32 -- Flags: [PropertyReadable,PropertyWritable] getViewportAttributesDeviceDpi :: (MonadIO m, ViewportAttributesK o) => o -> m Int32 getViewportAttributesDeviceDpi obj = liftIO $ getObjectPropertyCInt obj "device-dpi" setViewportAttributesDeviceDpi :: (MonadIO m, ViewportAttributesK o) => o -> Int32 -> m () setViewportAttributesDeviceDpi obj val = liftIO $ setObjectPropertyCInt obj "device-dpi" val constructViewportAttributesDeviceDpi :: Int32 -> IO ([Char], GValue) constructViewportAttributesDeviceDpi val = constructObjectPropertyCInt "device-dpi" val data ViewportAttributesDeviceDpiPropertyInfo instance AttrInfo ViewportAttributesDeviceDpiPropertyInfo where type AttrAllowedOps ViewportAttributesDeviceDpiPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint ViewportAttributesDeviceDpiPropertyInfo = (~) Int32 type AttrBaseTypeConstraint ViewportAttributesDeviceDpiPropertyInfo = ViewportAttributesK type AttrGetType ViewportAttributesDeviceDpiPropertyInfo = Int32 type AttrLabel ViewportAttributesDeviceDpiPropertyInfo = "ViewportAttributes::device-dpi" attrGet _ = getViewportAttributesDeviceDpi attrSet _ = setViewportAttributesDeviceDpi attrConstruct _ = constructViewportAttributesDeviceDpi -- VVV Prop "device-height" -- Type: TBasicType TInt32 -- Flags: [PropertyReadable,PropertyWritable] getViewportAttributesDeviceHeight :: (MonadIO m, ViewportAttributesK o) => o -> m Int32 getViewportAttributesDeviceHeight obj = liftIO $ getObjectPropertyCInt obj "device-height" setViewportAttributesDeviceHeight :: (MonadIO m, ViewportAttributesK o) => o -> Int32 -> m () setViewportAttributesDeviceHeight obj val = liftIO $ setObjectPropertyCInt obj "device-height" val constructViewportAttributesDeviceHeight :: Int32 -> IO ([Char], GValue) constructViewportAttributesDeviceHeight val = constructObjectPropertyCInt "device-height" val data ViewportAttributesDeviceHeightPropertyInfo instance AttrInfo ViewportAttributesDeviceHeightPropertyInfo where type AttrAllowedOps ViewportAttributesDeviceHeightPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint ViewportAttributesDeviceHeightPropertyInfo = (~) Int32 type AttrBaseTypeConstraint ViewportAttributesDeviceHeightPropertyInfo = ViewportAttributesK type AttrGetType ViewportAttributesDeviceHeightPropertyInfo = Int32 type AttrLabel ViewportAttributesDeviceHeightPropertyInfo = "ViewportAttributes::device-height" attrGet _ = getViewportAttributesDeviceHeight attrSet _ = setViewportAttributesDeviceHeight attrConstruct _ = constructViewportAttributesDeviceHeight -- VVV Prop "device-pixel-ratio" -- Type: TBasicType TFloat -- Flags: [PropertyReadable] getViewportAttributesDevicePixelRatio :: (MonadIO m, ViewportAttributesK o) => o -> m Float getViewportAttributesDevicePixelRatio obj = liftIO $ getObjectPropertyFloat obj "device-pixel-ratio" data ViewportAttributesDevicePixelRatioPropertyInfo instance AttrInfo ViewportAttributesDevicePixelRatioPropertyInfo where type AttrAllowedOps ViewportAttributesDevicePixelRatioPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint ViewportAttributesDevicePixelRatioPropertyInfo = (~) () type AttrBaseTypeConstraint ViewportAttributesDevicePixelRatioPropertyInfo = ViewportAttributesK type AttrGetType ViewportAttributesDevicePixelRatioPropertyInfo = Float type AttrLabel ViewportAttributesDevicePixelRatioPropertyInfo = "ViewportAttributes::device-pixel-ratio" attrGet _ = getViewportAttributesDevicePixelRatio attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "device-width" -- Type: TBasicType TInt32 -- Flags: [PropertyReadable,PropertyWritable] getViewportAttributesDeviceWidth :: (MonadIO m, ViewportAttributesK o) => o -> m Int32 getViewportAttributesDeviceWidth obj = liftIO $ getObjectPropertyCInt obj "device-width" setViewportAttributesDeviceWidth :: (MonadIO m, ViewportAttributesK o) => o -> Int32 -> m () setViewportAttributesDeviceWidth obj val = liftIO $ setObjectPropertyCInt obj "device-width" val constructViewportAttributesDeviceWidth :: Int32 -> IO ([Char], GValue) constructViewportAttributesDeviceWidth val = constructObjectPropertyCInt "device-width" val data ViewportAttributesDeviceWidthPropertyInfo instance AttrInfo ViewportAttributesDeviceWidthPropertyInfo where type AttrAllowedOps ViewportAttributesDeviceWidthPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint ViewportAttributesDeviceWidthPropertyInfo = (~) Int32 type AttrBaseTypeConstraint ViewportAttributesDeviceWidthPropertyInfo = ViewportAttributesK type AttrGetType ViewportAttributesDeviceWidthPropertyInfo = Int32 type AttrLabel ViewportAttributesDeviceWidthPropertyInfo = "ViewportAttributes::device-width" attrGet _ = getViewportAttributesDeviceWidth attrSet _ = setViewportAttributesDeviceWidth attrConstruct _ = constructViewportAttributesDeviceWidth -- VVV Prop "height" -- Type: TBasicType TInt32 -- Flags: [PropertyReadable] getViewportAttributesHeight :: (MonadIO m, ViewportAttributesK o) => o -> m Int32 getViewportAttributesHeight obj = liftIO $ getObjectPropertyCInt obj "height" data ViewportAttributesHeightPropertyInfo instance AttrInfo ViewportAttributesHeightPropertyInfo where type AttrAllowedOps ViewportAttributesHeightPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint ViewportAttributesHeightPropertyInfo = (~) () type AttrBaseTypeConstraint ViewportAttributesHeightPropertyInfo = ViewportAttributesK type AttrGetType ViewportAttributesHeightPropertyInfo = Int32 type AttrLabel ViewportAttributesHeightPropertyInfo = "ViewportAttributes::height" attrGet _ = getViewportAttributesHeight attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "initial-scale-factor" -- Type: TBasicType TFloat -- Flags: [PropertyReadable] getViewportAttributesInitialScaleFactor :: (MonadIO m, ViewportAttributesK o) => o -> m Float getViewportAttributesInitialScaleFactor obj = liftIO $ getObjectPropertyFloat obj "initial-scale-factor" data ViewportAttributesInitialScaleFactorPropertyInfo instance AttrInfo ViewportAttributesInitialScaleFactorPropertyInfo where type AttrAllowedOps ViewportAttributesInitialScaleFactorPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint ViewportAttributesInitialScaleFactorPropertyInfo = (~) () type AttrBaseTypeConstraint ViewportAttributesInitialScaleFactorPropertyInfo = ViewportAttributesK type AttrGetType ViewportAttributesInitialScaleFactorPropertyInfo = Float type AttrLabel ViewportAttributesInitialScaleFactorPropertyInfo = "ViewportAttributes::initial-scale-factor" attrGet _ = getViewportAttributesInitialScaleFactor attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "maximum-scale-factor" -- Type: TBasicType TFloat -- Flags: [PropertyReadable] getViewportAttributesMaximumScaleFactor :: (MonadIO m, ViewportAttributesK o) => o -> m Float getViewportAttributesMaximumScaleFactor obj = liftIO $ getObjectPropertyFloat obj "maximum-scale-factor" data ViewportAttributesMaximumScaleFactorPropertyInfo instance AttrInfo ViewportAttributesMaximumScaleFactorPropertyInfo where type AttrAllowedOps ViewportAttributesMaximumScaleFactorPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint ViewportAttributesMaximumScaleFactorPropertyInfo = (~) () type AttrBaseTypeConstraint ViewportAttributesMaximumScaleFactorPropertyInfo = ViewportAttributesK type AttrGetType ViewportAttributesMaximumScaleFactorPropertyInfo = Float type AttrLabel ViewportAttributesMaximumScaleFactorPropertyInfo = "ViewportAttributes::maximum-scale-factor" attrGet _ = getViewportAttributesMaximumScaleFactor attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "minimum-scale-factor" -- Type: TBasicType TFloat -- Flags: [PropertyReadable] getViewportAttributesMinimumScaleFactor :: (MonadIO m, ViewportAttributesK o) => o -> m Float getViewportAttributesMinimumScaleFactor obj = liftIO $ getObjectPropertyFloat obj "minimum-scale-factor" data ViewportAttributesMinimumScaleFactorPropertyInfo instance AttrInfo ViewportAttributesMinimumScaleFactorPropertyInfo where type AttrAllowedOps ViewportAttributesMinimumScaleFactorPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint ViewportAttributesMinimumScaleFactorPropertyInfo = (~) () type AttrBaseTypeConstraint ViewportAttributesMinimumScaleFactorPropertyInfo = ViewportAttributesK type AttrGetType ViewportAttributesMinimumScaleFactorPropertyInfo = Float type AttrLabel ViewportAttributesMinimumScaleFactorPropertyInfo = "ViewportAttributes::minimum-scale-factor" attrGet _ = getViewportAttributesMinimumScaleFactor attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "user-scalable" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getViewportAttributesUserScalable :: (MonadIO m, ViewportAttributesK o) => o -> m Bool getViewportAttributesUserScalable obj = liftIO $ getObjectPropertyBool obj "user-scalable" data ViewportAttributesUserScalablePropertyInfo instance AttrInfo ViewportAttributesUserScalablePropertyInfo where type AttrAllowedOps ViewportAttributesUserScalablePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint ViewportAttributesUserScalablePropertyInfo = (~) () type AttrBaseTypeConstraint ViewportAttributesUserScalablePropertyInfo = ViewportAttributesK type AttrGetType ViewportAttributesUserScalablePropertyInfo = Bool type AttrLabel ViewportAttributesUserScalablePropertyInfo = "ViewportAttributes::user-scalable" attrGet _ = getViewportAttributesUserScalable attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "valid" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable] getViewportAttributesValid :: (MonadIO m, ViewportAttributesK o) => o -> m Bool getViewportAttributesValid obj = liftIO $ getObjectPropertyBool obj "valid" data ViewportAttributesValidPropertyInfo instance AttrInfo ViewportAttributesValidPropertyInfo where type AttrAllowedOps ViewportAttributesValidPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint ViewportAttributesValidPropertyInfo = (~) () type AttrBaseTypeConstraint ViewportAttributesValidPropertyInfo = ViewportAttributesK type AttrGetType ViewportAttributesValidPropertyInfo = Bool type AttrLabel ViewportAttributesValidPropertyInfo = "ViewportAttributes::valid" attrGet _ = getViewportAttributesValid attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "width" -- Type: TBasicType TInt32 -- Flags: [PropertyReadable] getViewportAttributesWidth :: (MonadIO m, ViewportAttributesK o) => o -> m Int32 getViewportAttributesWidth obj = liftIO $ getObjectPropertyCInt obj "width" data ViewportAttributesWidthPropertyInfo instance AttrInfo ViewportAttributesWidthPropertyInfo where type AttrAllowedOps ViewportAttributesWidthPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint ViewportAttributesWidthPropertyInfo = (~) () type AttrBaseTypeConstraint ViewportAttributesWidthPropertyInfo = ViewportAttributesK type AttrGetType ViewportAttributesWidthPropertyInfo = Int32 type AttrLabel ViewportAttributesWidthPropertyInfo = "ViewportAttributes::width" attrGet _ = getViewportAttributesWidth attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList ViewportAttributes = '[ '("available-height", ViewportAttributesAvailableHeightPropertyInfo), '("available-width", ViewportAttributesAvailableWidthPropertyInfo), '("desktop-width", ViewportAttributesDesktopWidthPropertyInfo), '("device-dpi", ViewportAttributesDeviceDpiPropertyInfo), '("device-height", ViewportAttributesDeviceHeightPropertyInfo), '("device-pixel-ratio", ViewportAttributesDevicePixelRatioPropertyInfo), '("device-width", ViewportAttributesDeviceWidthPropertyInfo), '("height", ViewportAttributesHeightPropertyInfo), '("initial-scale-factor", ViewportAttributesInitialScaleFactorPropertyInfo), '("maximum-scale-factor", ViewportAttributesMaximumScaleFactorPropertyInfo), '("minimum-scale-factor", ViewportAttributesMinimumScaleFactorPropertyInfo), '("user-scalable", ViewportAttributesUserScalablePropertyInfo), '("valid", ViewportAttributesValidPropertyInfo), '("width", ViewportAttributesWidthPropertyInfo)] type instance AttributeList WebBackForwardList = '[ ] type instance AttributeList WebDataSource = '[ ] -- VVV Prop "display-name" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getWebDatabaseDisplayName :: (MonadIO m, WebDatabaseK o) => o -> m T.Text getWebDatabaseDisplayName obj = liftIO $ getObjectPropertyString obj "display-name" data WebDatabaseDisplayNamePropertyInfo instance AttrInfo WebDatabaseDisplayNamePropertyInfo where type AttrAllowedOps WebDatabaseDisplayNamePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint WebDatabaseDisplayNamePropertyInfo = (~) () type AttrBaseTypeConstraint WebDatabaseDisplayNamePropertyInfo = WebDatabaseK type AttrGetType WebDatabaseDisplayNamePropertyInfo = T.Text type AttrLabel WebDatabaseDisplayNamePropertyInfo = "WebDatabase::display-name" attrGet _ = getWebDatabaseDisplayName attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "expected-size" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getWebDatabaseExpectedSize :: (MonadIO m, WebDatabaseK o) => o -> m Word64 getWebDatabaseExpectedSize obj = liftIO $ getObjectPropertyUInt64 obj "expected-size" data WebDatabaseExpectedSizePropertyInfo instance AttrInfo WebDatabaseExpectedSizePropertyInfo where type AttrAllowedOps WebDatabaseExpectedSizePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint WebDatabaseExpectedSizePropertyInfo = (~) () type AttrBaseTypeConstraint WebDatabaseExpectedSizePropertyInfo = WebDatabaseK type AttrGetType WebDatabaseExpectedSizePropertyInfo = Word64 type AttrLabel WebDatabaseExpectedSizePropertyInfo = "WebDatabase::expected-size" attrGet _ = getWebDatabaseExpectedSize attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "filename" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getWebDatabaseFilename :: (MonadIO m, WebDatabaseK o) => o -> m T.Text getWebDatabaseFilename obj = liftIO $ getObjectPropertyString obj "filename" data WebDatabaseFilenamePropertyInfo instance AttrInfo WebDatabaseFilenamePropertyInfo where type AttrAllowedOps WebDatabaseFilenamePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint WebDatabaseFilenamePropertyInfo = (~) () type AttrBaseTypeConstraint WebDatabaseFilenamePropertyInfo = WebDatabaseK type AttrGetType WebDatabaseFilenamePropertyInfo = T.Text type AttrLabel WebDatabaseFilenamePropertyInfo = "WebDatabase::filename" attrGet _ = getWebDatabaseFilename attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "name" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly] getWebDatabaseName :: (MonadIO m, WebDatabaseK o) => o -> m T.Text getWebDatabaseName obj = liftIO $ getObjectPropertyString obj "name" constructWebDatabaseName :: T.Text -> IO ([Char], GValue) constructWebDatabaseName val = constructObjectPropertyString "name" val data WebDatabaseNamePropertyInfo instance AttrInfo WebDatabaseNamePropertyInfo where type AttrAllowedOps WebDatabaseNamePropertyInfo = '[ 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebDatabaseNamePropertyInfo = (~) T.Text type AttrBaseTypeConstraint WebDatabaseNamePropertyInfo = WebDatabaseK type AttrGetType WebDatabaseNamePropertyInfo = T.Text type AttrLabel WebDatabaseNamePropertyInfo = "WebDatabase::name" attrGet _ = getWebDatabaseName attrSet _ = undefined attrConstruct _ = constructWebDatabaseName -- VVV Prop "security-origin" -- Type: TInterface "WebKit" "SecurityOrigin" -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly] getWebDatabaseSecurityOrigin :: (MonadIO m, WebDatabaseK o) => o -> m SecurityOrigin getWebDatabaseSecurityOrigin obj = liftIO $ getObjectPropertyObject obj "security-origin" SecurityOrigin constructWebDatabaseSecurityOrigin :: (SecurityOriginK a) => a -> IO ([Char], GValue) constructWebDatabaseSecurityOrigin val = constructObjectPropertyObject "security-origin" val data WebDatabaseSecurityOriginPropertyInfo instance AttrInfo WebDatabaseSecurityOriginPropertyInfo where type AttrAllowedOps WebDatabaseSecurityOriginPropertyInfo = '[ 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebDatabaseSecurityOriginPropertyInfo = SecurityOriginK type AttrBaseTypeConstraint WebDatabaseSecurityOriginPropertyInfo = WebDatabaseK type AttrGetType WebDatabaseSecurityOriginPropertyInfo = SecurityOrigin type AttrLabel WebDatabaseSecurityOriginPropertyInfo = "WebDatabase::security-origin" attrGet _ = getWebDatabaseSecurityOrigin attrSet _ = undefined attrConstruct _ = constructWebDatabaseSecurityOrigin -- VVV Prop "size" -- Type: TBasicType TUInt64 -- Flags: [PropertyReadable] getWebDatabaseSize :: (MonadIO m, WebDatabaseK o) => o -> m Word64 getWebDatabaseSize obj = liftIO $ getObjectPropertyUInt64 obj "size" data WebDatabaseSizePropertyInfo instance AttrInfo WebDatabaseSizePropertyInfo where type AttrAllowedOps WebDatabaseSizePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint WebDatabaseSizePropertyInfo = (~) () type AttrBaseTypeConstraint WebDatabaseSizePropertyInfo = WebDatabaseK type AttrGetType WebDatabaseSizePropertyInfo = Word64 type AttrLabel WebDatabaseSizePropertyInfo = "WebDatabase::size" attrGet _ = getWebDatabaseSize attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList WebDatabase = '[ '("display-name", WebDatabaseDisplayNamePropertyInfo), '("expected-size", WebDatabaseExpectedSizePropertyInfo), '("filename", WebDatabaseFilenamePropertyInfo), '("name", WebDatabaseNamePropertyInfo), '("security-origin", WebDatabaseSecurityOriginPropertyInfo), '("size", WebDatabaseSizePropertyInfo)] -- VVV Prop "horizontal-scrollbar-policy" -- Type: TInterface "Gtk" "PolicyType" -- Flags: [PropertyReadable] getWebFrameHorizontalScrollbarPolicy :: (MonadIO m, WebFrameK o) => o -> m Gtk.PolicyType getWebFrameHorizontalScrollbarPolicy obj = liftIO $ getObjectPropertyEnum obj "horizontal-scrollbar-policy" data WebFrameHorizontalScrollbarPolicyPropertyInfo instance AttrInfo WebFrameHorizontalScrollbarPolicyPropertyInfo where type AttrAllowedOps WebFrameHorizontalScrollbarPolicyPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint WebFrameHorizontalScrollbarPolicyPropertyInfo = (~) () type AttrBaseTypeConstraint WebFrameHorizontalScrollbarPolicyPropertyInfo = WebFrameK type AttrGetType WebFrameHorizontalScrollbarPolicyPropertyInfo = Gtk.PolicyType type AttrLabel WebFrameHorizontalScrollbarPolicyPropertyInfo = "WebFrame::horizontal-scrollbar-policy" attrGet _ = getWebFrameHorizontalScrollbarPolicy attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "load-status" -- Type: TInterface "WebKit" "LoadStatus" -- Flags: [PropertyReadable] getWebFrameLoadStatus :: (MonadIO m, WebFrameK o) => o -> m LoadStatus getWebFrameLoadStatus obj = liftIO $ getObjectPropertyEnum obj "load-status" data WebFrameLoadStatusPropertyInfo instance AttrInfo WebFrameLoadStatusPropertyInfo where type AttrAllowedOps WebFrameLoadStatusPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint WebFrameLoadStatusPropertyInfo = (~) () type AttrBaseTypeConstraint WebFrameLoadStatusPropertyInfo = WebFrameK type AttrGetType WebFrameLoadStatusPropertyInfo = LoadStatus type AttrLabel WebFrameLoadStatusPropertyInfo = "WebFrame::load-status" attrGet _ = getWebFrameLoadStatus attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "name" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getWebFrameName :: (MonadIO m, WebFrameK o) => o -> m T.Text getWebFrameName obj = liftIO $ getObjectPropertyString obj "name" data WebFrameNamePropertyInfo instance AttrInfo WebFrameNamePropertyInfo where type AttrAllowedOps WebFrameNamePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint WebFrameNamePropertyInfo = (~) () type AttrBaseTypeConstraint WebFrameNamePropertyInfo = WebFrameK type AttrGetType WebFrameNamePropertyInfo = T.Text type AttrLabel WebFrameNamePropertyInfo = "WebFrame::name" attrGet _ = getWebFrameName attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "title" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getWebFrameTitle :: (MonadIO m, WebFrameK o) => o -> m T.Text getWebFrameTitle obj = liftIO $ getObjectPropertyString obj "title" data WebFrameTitlePropertyInfo instance AttrInfo WebFrameTitlePropertyInfo where type AttrAllowedOps WebFrameTitlePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint WebFrameTitlePropertyInfo = (~) () type AttrBaseTypeConstraint WebFrameTitlePropertyInfo = WebFrameK type AttrGetType WebFrameTitlePropertyInfo = T.Text type AttrLabel WebFrameTitlePropertyInfo = "WebFrame::title" attrGet _ = getWebFrameTitle attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "uri" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getWebFrameUri :: (MonadIO m, WebFrameK o) => o -> m T.Text getWebFrameUri obj = liftIO $ getObjectPropertyString obj "uri" data WebFrameUriPropertyInfo instance AttrInfo WebFrameUriPropertyInfo where type AttrAllowedOps WebFrameUriPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint WebFrameUriPropertyInfo = (~) () type AttrBaseTypeConstraint WebFrameUriPropertyInfo = WebFrameK type AttrGetType WebFrameUriPropertyInfo = T.Text type AttrLabel WebFrameUriPropertyInfo = "WebFrame::uri" attrGet _ = getWebFrameUri attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "vertical-scrollbar-policy" -- Type: TInterface "Gtk" "PolicyType" -- Flags: [PropertyReadable] getWebFrameVerticalScrollbarPolicy :: (MonadIO m, WebFrameK o) => o -> m Gtk.PolicyType getWebFrameVerticalScrollbarPolicy obj = liftIO $ getObjectPropertyEnum obj "vertical-scrollbar-policy" data WebFrameVerticalScrollbarPolicyPropertyInfo instance AttrInfo WebFrameVerticalScrollbarPolicyPropertyInfo where type AttrAllowedOps WebFrameVerticalScrollbarPolicyPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint WebFrameVerticalScrollbarPolicyPropertyInfo = (~) () type AttrBaseTypeConstraint WebFrameVerticalScrollbarPolicyPropertyInfo = WebFrameK type AttrGetType WebFrameVerticalScrollbarPolicyPropertyInfo = Gtk.PolicyType type AttrLabel WebFrameVerticalScrollbarPolicyPropertyInfo = "WebFrame::vertical-scrollbar-policy" attrGet _ = getWebFrameVerticalScrollbarPolicy attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList WebFrame = '[ '("horizontal-scrollbar-policy", WebFrameHorizontalScrollbarPolicyPropertyInfo), '("load-status", WebFrameLoadStatusPropertyInfo), '("name", WebFrameNamePropertyInfo), '("title", WebFrameTitlePropertyInfo), '("uri", WebFrameUriPropertyInfo), '("vertical-scrollbar-policy", WebFrameVerticalScrollbarPolicyPropertyInfo)] -- VVV Prop "alternate-title" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getWebHistoryItemAlternateTitle :: (MonadIO m, WebHistoryItemK o) => o -> m T.Text getWebHistoryItemAlternateTitle obj = liftIO $ getObjectPropertyString obj "alternate-title" setWebHistoryItemAlternateTitle :: (MonadIO m, WebHistoryItemK o) => o -> T.Text -> m () setWebHistoryItemAlternateTitle obj val = liftIO $ setObjectPropertyString obj "alternate-title" val constructWebHistoryItemAlternateTitle :: T.Text -> IO ([Char], GValue) constructWebHistoryItemAlternateTitle val = constructObjectPropertyString "alternate-title" val data WebHistoryItemAlternateTitlePropertyInfo instance AttrInfo WebHistoryItemAlternateTitlePropertyInfo where type AttrAllowedOps WebHistoryItemAlternateTitlePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebHistoryItemAlternateTitlePropertyInfo = (~) T.Text type AttrBaseTypeConstraint WebHistoryItemAlternateTitlePropertyInfo = WebHistoryItemK type AttrGetType WebHistoryItemAlternateTitlePropertyInfo = T.Text type AttrLabel WebHistoryItemAlternateTitlePropertyInfo = "WebHistoryItem::alternate-title" attrGet _ = getWebHistoryItemAlternateTitle attrSet _ = setWebHistoryItemAlternateTitle attrConstruct _ = constructWebHistoryItemAlternateTitle -- VVV Prop "last-visited-time" -- Type: TBasicType TDouble -- Flags: [PropertyReadable] getWebHistoryItemLastVisitedTime :: (MonadIO m, WebHistoryItemK o) => o -> m Double getWebHistoryItemLastVisitedTime obj = liftIO $ getObjectPropertyDouble obj "last-visited-time" data WebHistoryItemLastVisitedTimePropertyInfo instance AttrInfo WebHistoryItemLastVisitedTimePropertyInfo where type AttrAllowedOps WebHistoryItemLastVisitedTimePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint WebHistoryItemLastVisitedTimePropertyInfo = (~) () type AttrBaseTypeConstraint WebHistoryItemLastVisitedTimePropertyInfo = WebHistoryItemK type AttrGetType WebHistoryItemLastVisitedTimePropertyInfo = Double type AttrLabel WebHistoryItemLastVisitedTimePropertyInfo = "WebHistoryItem::last-visited-time" attrGet _ = getWebHistoryItemLastVisitedTime attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "original-uri" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getWebHistoryItemOriginalUri :: (MonadIO m, WebHistoryItemK o) => o -> m T.Text getWebHistoryItemOriginalUri obj = liftIO $ getObjectPropertyString obj "original-uri" data WebHistoryItemOriginalUriPropertyInfo instance AttrInfo WebHistoryItemOriginalUriPropertyInfo where type AttrAllowedOps WebHistoryItemOriginalUriPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint WebHistoryItemOriginalUriPropertyInfo = (~) () type AttrBaseTypeConstraint WebHistoryItemOriginalUriPropertyInfo = WebHistoryItemK type AttrGetType WebHistoryItemOriginalUriPropertyInfo = T.Text type AttrLabel WebHistoryItemOriginalUriPropertyInfo = "WebHistoryItem::original-uri" attrGet _ = getWebHistoryItemOriginalUri attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "title" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getWebHistoryItemTitle :: (MonadIO m, WebHistoryItemK o) => o -> m T.Text getWebHistoryItemTitle obj = liftIO $ getObjectPropertyString obj "title" data WebHistoryItemTitlePropertyInfo instance AttrInfo WebHistoryItemTitlePropertyInfo where type AttrAllowedOps WebHistoryItemTitlePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint WebHistoryItemTitlePropertyInfo = (~) () type AttrBaseTypeConstraint WebHistoryItemTitlePropertyInfo = WebHistoryItemK type AttrGetType WebHistoryItemTitlePropertyInfo = T.Text type AttrLabel WebHistoryItemTitlePropertyInfo = "WebHistoryItem::title" attrGet _ = getWebHistoryItemTitle attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "uri" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getWebHistoryItemUri :: (MonadIO m, WebHistoryItemK o) => o -> m T.Text getWebHistoryItemUri obj = liftIO $ getObjectPropertyString obj "uri" data WebHistoryItemUriPropertyInfo instance AttrInfo WebHistoryItemUriPropertyInfo where type AttrAllowedOps WebHistoryItemUriPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint WebHistoryItemUriPropertyInfo = (~) () type AttrBaseTypeConstraint WebHistoryItemUriPropertyInfo = WebHistoryItemK type AttrGetType WebHistoryItemUriPropertyInfo = T.Text type AttrLabel WebHistoryItemUriPropertyInfo = "WebHistoryItem::uri" attrGet _ = getWebHistoryItemUri attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList WebHistoryItem = '[ '("alternate-title", WebHistoryItemAlternateTitlePropertyInfo), '("last-visited-time", WebHistoryItemLastVisitedTimePropertyInfo), '("original-uri", WebHistoryItemOriginalUriPropertyInfo), '("title", WebHistoryItemTitlePropertyInfo), '("uri", WebHistoryItemUriPropertyInfo)] -- VVV Prop "inspected-uri" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getWebInspectorInspectedUri :: (MonadIO m, WebInspectorK o) => o -> m T.Text getWebInspectorInspectedUri obj = liftIO $ getObjectPropertyString obj "inspected-uri" data WebInspectorInspectedUriPropertyInfo instance AttrInfo WebInspectorInspectedUriPropertyInfo where type AttrAllowedOps WebInspectorInspectedUriPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint WebInspectorInspectedUriPropertyInfo = (~) () type AttrBaseTypeConstraint WebInspectorInspectedUriPropertyInfo = WebInspectorK type AttrGetType WebInspectorInspectedUriPropertyInfo = T.Text type AttrLabel WebInspectorInspectedUriPropertyInfo = "WebInspector::inspected-uri" attrGet _ = getWebInspectorInspectedUri attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "javascript-profiling-enabled" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getWebInspectorJavascriptProfilingEnabled :: (MonadIO m, WebInspectorK o) => o -> m Bool getWebInspectorJavascriptProfilingEnabled obj = liftIO $ getObjectPropertyBool obj "javascript-profiling-enabled" setWebInspectorJavascriptProfilingEnabled :: (MonadIO m, WebInspectorK o) => o -> Bool -> m () setWebInspectorJavascriptProfilingEnabled obj val = liftIO $ setObjectPropertyBool obj "javascript-profiling-enabled" val constructWebInspectorJavascriptProfilingEnabled :: Bool -> IO ([Char], GValue) constructWebInspectorJavascriptProfilingEnabled val = constructObjectPropertyBool "javascript-profiling-enabled" val data WebInspectorJavascriptProfilingEnabledPropertyInfo instance AttrInfo WebInspectorJavascriptProfilingEnabledPropertyInfo where type AttrAllowedOps WebInspectorJavascriptProfilingEnabledPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebInspectorJavascriptProfilingEnabledPropertyInfo = (~) Bool type AttrBaseTypeConstraint WebInspectorJavascriptProfilingEnabledPropertyInfo = WebInspectorK type AttrGetType WebInspectorJavascriptProfilingEnabledPropertyInfo = Bool type AttrLabel WebInspectorJavascriptProfilingEnabledPropertyInfo = "WebInspector::javascript-profiling-enabled" attrGet _ = getWebInspectorJavascriptProfilingEnabled attrSet _ = setWebInspectorJavascriptProfilingEnabled attrConstruct _ = constructWebInspectorJavascriptProfilingEnabled -- VVV Prop "timeline-profiling-enabled" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getWebInspectorTimelineProfilingEnabled :: (MonadIO m, WebInspectorK o) => o -> m Bool getWebInspectorTimelineProfilingEnabled obj = liftIO $ getObjectPropertyBool obj "timeline-profiling-enabled" setWebInspectorTimelineProfilingEnabled :: (MonadIO m, WebInspectorK o) => o -> Bool -> m () setWebInspectorTimelineProfilingEnabled obj val = liftIO $ setObjectPropertyBool obj "timeline-profiling-enabled" val constructWebInspectorTimelineProfilingEnabled :: Bool -> IO ([Char], GValue) constructWebInspectorTimelineProfilingEnabled val = constructObjectPropertyBool "timeline-profiling-enabled" val data WebInspectorTimelineProfilingEnabledPropertyInfo instance AttrInfo WebInspectorTimelineProfilingEnabledPropertyInfo where type AttrAllowedOps WebInspectorTimelineProfilingEnabledPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebInspectorTimelineProfilingEnabledPropertyInfo = (~) Bool type AttrBaseTypeConstraint WebInspectorTimelineProfilingEnabledPropertyInfo = WebInspectorK type AttrGetType WebInspectorTimelineProfilingEnabledPropertyInfo = Bool type AttrLabel WebInspectorTimelineProfilingEnabledPropertyInfo = "WebInspector::timeline-profiling-enabled" attrGet _ = getWebInspectorTimelineProfilingEnabled attrSet _ = setWebInspectorTimelineProfilingEnabled attrConstruct _ = constructWebInspectorTimelineProfilingEnabled -- VVV Prop "web-view" -- Type: TInterface "WebKit" "WebView" -- Flags: [PropertyReadable] getWebInspectorWebView :: (MonadIO m, WebInspectorK o) => o -> m WebView getWebInspectorWebView obj = liftIO $ getObjectPropertyObject obj "web-view" WebView data WebInspectorWebViewPropertyInfo instance AttrInfo WebInspectorWebViewPropertyInfo where type AttrAllowedOps WebInspectorWebViewPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint WebInspectorWebViewPropertyInfo = (~) () type AttrBaseTypeConstraint WebInspectorWebViewPropertyInfo = WebInspectorK type AttrGetType WebInspectorWebViewPropertyInfo = WebView type AttrLabel WebInspectorWebViewPropertyInfo = "WebInspector::web-view" attrGet _ = getWebInspectorWebView attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList WebInspector = '[ '("inspected-uri", WebInspectorInspectedUriPropertyInfo), '("javascript-profiling-enabled", WebInspectorJavascriptProfilingEnabledPropertyInfo), '("timeline-profiling-enabled", WebInspectorTimelineProfilingEnabledPropertyInfo), '("web-view", WebInspectorWebViewPropertyInfo)] -- VVV Prop "button" -- Type: TBasicType TInt32 -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly] getWebNavigationActionButton :: (MonadIO m, WebNavigationActionK o) => o -> m Int32 getWebNavigationActionButton obj = liftIO $ getObjectPropertyCInt obj "button" constructWebNavigationActionButton :: Int32 -> IO ([Char], GValue) constructWebNavigationActionButton val = constructObjectPropertyCInt "button" val data WebNavigationActionButtonPropertyInfo instance AttrInfo WebNavigationActionButtonPropertyInfo where type AttrAllowedOps WebNavigationActionButtonPropertyInfo = '[ 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebNavigationActionButtonPropertyInfo = (~) Int32 type AttrBaseTypeConstraint WebNavigationActionButtonPropertyInfo = WebNavigationActionK type AttrGetType WebNavigationActionButtonPropertyInfo = Int32 type AttrLabel WebNavigationActionButtonPropertyInfo = "WebNavigationAction::button" attrGet _ = getWebNavigationActionButton attrSet _ = undefined attrConstruct _ = constructWebNavigationActionButton -- VVV Prop "modifier-state" -- Type: TBasicType TInt32 -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly] getWebNavigationActionModifierState :: (MonadIO m, WebNavigationActionK o) => o -> m Int32 getWebNavigationActionModifierState obj = liftIO $ getObjectPropertyCInt obj "modifier-state" constructWebNavigationActionModifierState :: Int32 -> IO ([Char], GValue) constructWebNavigationActionModifierState val = constructObjectPropertyCInt "modifier-state" val data WebNavigationActionModifierStatePropertyInfo instance AttrInfo WebNavigationActionModifierStatePropertyInfo where type AttrAllowedOps WebNavigationActionModifierStatePropertyInfo = '[ 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebNavigationActionModifierStatePropertyInfo = (~) Int32 type AttrBaseTypeConstraint WebNavigationActionModifierStatePropertyInfo = WebNavigationActionK type AttrGetType WebNavigationActionModifierStatePropertyInfo = Int32 type AttrLabel WebNavigationActionModifierStatePropertyInfo = "WebNavigationAction::modifier-state" attrGet _ = getWebNavigationActionModifierState attrSet _ = undefined attrConstruct _ = constructWebNavigationActionModifierState -- VVV Prop "original-uri" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebNavigationActionOriginalUri :: (MonadIO m, WebNavigationActionK o) => o -> m T.Text getWebNavigationActionOriginalUri obj = liftIO $ getObjectPropertyString obj "original-uri" setWebNavigationActionOriginalUri :: (MonadIO m, WebNavigationActionK o) => o -> T.Text -> m () setWebNavigationActionOriginalUri obj val = liftIO $ setObjectPropertyString obj "original-uri" val constructWebNavigationActionOriginalUri :: T.Text -> IO ([Char], GValue) constructWebNavigationActionOriginalUri val = constructObjectPropertyString "original-uri" val data WebNavigationActionOriginalUriPropertyInfo instance AttrInfo WebNavigationActionOriginalUriPropertyInfo where type AttrAllowedOps WebNavigationActionOriginalUriPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebNavigationActionOriginalUriPropertyInfo = (~) T.Text type AttrBaseTypeConstraint WebNavigationActionOriginalUriPropertyInfo = WebNavigationActionK type AttrGetType WebNavigationActionOriginalUriPropertyInfo = T.Text type AttrLabel WebNavigationActionOriginalUriPropertyInfo = "WebNavigationAction::original-uri" attrGet _ = getWebNavigationActionOriginalUri attrSet _ = setWebNavigationActionOriginalUri attrConstruct _ = constructWebNavigationActionOriginalUri -- VVV Prop "reason" -- Type: TInterface "WebKit" "WebNavigationReason" -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebNavigationActionReason :: (MonadIO m, WebNavigationActionK o) => o -> m WebNavigationReason getWebNavigationActionReason obj = liftIO $ getObjectPropertyEnum obj "reason" setWebNavigationActionReason :: (MonadIO m, WebNavigationActionK o) => o -> WebNavigationReason -> m () setWebNavigationActionReason obj val = liftIO $ setObjectPropertyEnum obj "reason" val constructWebNavigationActionReason :: WebNavigationReason -> IO ([Char], GValue) constructWebNavigationActionReason val = constructObjectPropertyEnum "reason" val data WebNavigationActionReasonPropertyInfo instance AttrInfo WebNavigationActionReasonPropertyInfo where type AttrAllowedOps WebNavigationActionReasonPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebNavigationActionReasonPropertyInfo = (~) WebNavigationReason type AttrBaseTypeConstraint WebNavigationActionReasonPropertyInfo = WebNavigationActionK type AttrGetType WebNavigationActionReasonPropertyInfo = WebNavigationReason type AttrLabel WebNavigationActionReasonPropertyInfo = "WebNavigationAction::reason" attrGet _ = getWebNavigationActionReason attrSet _ = setWebNavigationActionReason attrConstruct _ = constructWebNavigationActionReason -- VVV Prop "target-frame" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly] getWebNavigationActionTargetFrame :: (MonadIO m, WebNavigationActionK o) => o -> m T.Text getWebNavigationActionTargetFrame obj = liftIO $ getObjectPropertyString obj "target-frame" constructWebNavigationActionTargetFrame :: T.Text -> IO ([Char], GValue) constructWebNavigationActionTargetFrame val = constructObjectPropertyString "target-frame" val data WebNavigationActionTargetFramePropertyInfo instance AttrInfo WebNavigationActionTargetFramePropertyInfo where type AttrAllowedOps WebNavigationActionTargetFramePropertyInfo = '[ 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebNavigationActionTargetFramePropertyInfo = (~) T.Text type AttrBaseTypeConstraint WebNavigationActionTargetFramePropertyInfo = WebNavigationActionK type AttrGetType WebNavigationActionTargetFramePropertyInfo = T.Text type AttrLabel WebNavigationActionTargetFramePropertyInfo = "WebNavigationAction::target-frame" attrGet _ = getWebNavigationActionTargetFrame attrSet _ = undefined attrConstruct _ = constructWebNavigationActionTargetFrame type instance AttributeList WebNavigationAction = '[ '("button", WebNavigationActionButtonPropertyInfo), '("modifier-state", WebNavigationActionModifierStatePropertyInfo), '("original-uri", WebNavigationActionOriginalUriPropertyInfo), '("reason", WebNavigationActionReasonPropertyInfo), '("target-frame", WebNavigationActionTargetFramePropertyInfo)] -- VVV Prop "enabled" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getWebPluginEnabled :: (MonadIO m, WebPluginK o) => o -> m Bool getWebPluginEnabled obj = liftIO $ getObjectPropertyBool obj "enabled" setWebPluginEnabled :: (MonadIO m, WebPluginK o) => o -> Bool -> m () setWebPluginEnabled obj val = liftIO $ setObjectPropertyBool obj "enabled" val constructWebPluginEnabled :: Bool -> IO ([Char], GValue) constructWebPluginEnabled val = constructObjectPropertyBool "enabled" val data WebPluginEnabledPropertyInfo instance AttrInfo WebPluginEnabledPropertyInfo where type AttrAllowedOps WebPluginEnabledPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebPluginEnabledPropertyInfo = (~) Bool type AttrBaseTypeConstraint WebPluginEnabledPropertyInfo = WebPluginK type AttrGetType WebPluginEnabledPropertyInfo = Bool type AttrLabel WebPluginEnabledPropertyInfo = "WebPlugin::enabled" attrGet _ = getWebPluginEnabled attrSet _ = setWebPluginEnabled attrConstruct _ = constructWebPluginEnabled type instance AttributeList WebPlugin = '[ '("enabled", WebPluginEnabledPropertyInfo)] type instance AttributeList WebPluginDatabase = '[ ] type instance AttributeList WebPolicyDecision = '[ ] -- VVV Prop "encoding" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getWebResourceEncoding :: (MonadIO m, WebResourceK o) => o -> m T.Text getWebResourceEncoding obj = liftIO $ getObjectPropertyString obj "encoding" data WebResourceEncodingPropertyInfo instance AttrInfo WebResourceEncodingPropertyInfo where type AttrAllowedOps WebResourceEncodingPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint WebResourceEncodingPropertyInfo = (~) () type AttrBaseTypeConstraint WebResourceEncodingPropertyInfo = WebResourceK type AttrGetType WebResourceEncodingPropertyInfo = T.Text type AttrLabel WebResourceEncodingPropertyInfo = "WebResource::encoding" attrGet _ = getWebResourceEncoding attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "frame-name" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getWebResourceFrameName :: (MonadIO m, WebResourceK o) => o -> m T.Text getWebResourceFrameName obj = liftIO $ getObjectPropertyString obj "frame-name" data WebResourceFrameNamePropertyInfo instance AttrInfo WebResourceFrameNamePropertyInfo where type AttrAllowedOps WebResourceFrameNamePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint WebResourceFrameNamePropertyInfo = (~) () type AttrBaseTypeConstraint WebResourceFrameNamePropertyInfo = WebResourceK type AttrGetType WebResourceFrameNamePropertyInfo = T.Text type AttrLabel WebResourceFrameNamePropertyInfo = "WebResource::frame-name" attrGet _ = getWebResourceFrameName attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "mime-type" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getWebResourceMimeType :: (MonadIO m, WebResourceK o) => o -> m T.Text getWebResourceMimeType obj = liftIO $ getObjectPropertyString obj "mime-type" data WebResourceMimeTypePropertyInfo instance AttrInfo WebResourceMimeTypePropertyInfo where type AttrAllowedOps WebResourceMimeTypePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint WebResourceMimeTypePropertyInfo = (~) () type AttrBaseTypeConstraint WebResourceMimeTypePropertyInfo = WebResourceK type AttrGetType WebResourceMimeTypePropertyInfo = T.Text type AttrLabel WebResourceMimeTypePropertyInfo = "WebResource::mime-type" attrGet _ = getWebResourceMimeType attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "uri" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly] getWebResourceUri :: (MonadIO m, WebResourceK o) => o -> m T.Text getWebResourceUri obj = liftIO $ getObjectPropertyString obj "uri" constructWebResourceUri :: T.Text -> IO ([Char], GValue) constructWebResourceUri val = constructObjectPropertyString "uri" val data WebResourceUriPropertyInfo instance AttrInfo WebResourceUriPropertyInfo where type AttrAllowedOps WebResourceUriPropertyInfo = '[ 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebResourceUriPropertyInfo = (~) T.Text type AttrBaseTypeConstraint WebResourceUriPropertyInfo = WebResourceK type AttrGetType WebResourceUriPropertyInfo = T.Text type AttrLabel WebResourceUriPropertyInfo = "WebResource::uri" attrGet _ = getWebResourceUri attrSet _ = undefined attrConstruct _ = constructWebResourceUri type instance AttributeList WebResource = '[ '("encoding", WebResourceEncodingPropertyInfo), '("frame-name", WebResourceFrameNamePropertyInfo), '("mime-type", WebResourceMimeTypePropertyInfo), '("uri", WebResourceUriPropertyInfo)] -- VVV Prop "auto-load-images" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebSettingsAutoLoadImages :: (MonadIO m, WebSettingsK o) => o -> m Bool getWebSettingsAutoLoadImages obj = liftIO $ getObjectPropertyBool obj "auto-load-images" setWebSettingsAutoLoadImages :: (MonadIO m, WebSettingsK o) => o -> Bool -> m () setWebSettingsAutoLoadImages obj val = liftIO $ setObjectPropertyBool obj "auto-load-images" val constructWebSettingsAutoLoadImages :: Bool -> IO ([Char], GValue) constructWebSettingsAutoLoadImages val = constructObjectPropertyBool "auto-load-images" val data WebSettingsAutoLoadImagesPropertyInfo instance AttrInfo WebSettingsAutoLoadImagesPropertyInfo where type AttrAllowedOps WebSettingsAutoLoadImagesPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebSettingsAutoLoadImagesPropertyInfo = (~) Bool type AttrBaseTypeConstraint WebSettingsAutoLoadImagesPropertyInfo = WebSettingsK type AttrGetType WebSettingsAutoLoadImagesPropertyInfo = Bool type AttrLabel WebSettingsAutoLoadImagesPropertyInfo = "WebSettings::auto-load-images" attrGet _ = getWebSettingsAutoLoadImages attrSet _ = setWebSettingsAutoLoadImages attrConstruct _ = constructWebSettingsAutoLoadImages -- VVV Prop "auto-resize-window" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebSettingsAutoResizeWindow :: (MonadIO m, WebSettingsK o) => o -> m Bool getWebSettingsAutoResizeWindow obj = liftIO $ getObjectPropertyBool obj "auto-resize-window" setWebSettingsAutoResizeWindow :: (MonadIO m, WebSettingsK o) => o -> Bool -> m () setWebSettingsAutoResizeWindow obj val = liftIO $ setObjectPropertyBool obj "auto-resize-window" val constructWebSettingsAutoResizeWindow :: Bool -> IO ([Char], GValue) constructWebSettingsAutoResizeWindow val = constructObjectPropertyBool "auto-resize-window" val data WebSettingsAutoResizeWindowPropertyInfo instance AttrInfo WebSettingsAutoResizeWindowPropertyInfo where type AttrAllowedOps WebSettingsAutoResizeWindowPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebSettingsAutoResizeWindowPropertyInfo = (~) Bool type AttrBaseTypeConstraint WebSettingsAutoResizeWindowPropertyInfo = WebSettingsK type AttrGetType WebSettingsAutoResizeWindowPropertyInfo = Bool type AttrLabel WebSettingsAutoResizeWindowPropertyInfo = "WebSettings::auto-resize-window" attrGet _ = getWebSettingsAutoResizeWindow attrSet _ = setWebSettingsAutoResizeWindow attrConstruct _ = constructWebSettingsAutoResizeWindow -- VVV Prop "auto-shrink-images" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebSettingsAutoShrinkImages :: (MonadIO m, WebSettingsK o) => o -> m Bool getWebSettingsAutoShrinkImages obj = liftIO $ getObjectPropertyBool obj "auto-shrink-images" setWebSettingsAutoShrinkImages :: (MonadIO m, WebSettingsK o) => o -> Bool -> m () setWebSettingsAutoShrinkImages obj val = liftIO $ setObjectPropertyBool obj "auto-shrink-images" val constructWebSettingsAutoShrinkImages :: Bool -> IO ([Char], GValue) constructWebSettingsAutoShrinkImages val = constructObjectPropertyBool "auto-shrink-images" val data WebSettingsAutoShrinkImagesPropertyInfo instance AttrInfo WebSettingsAutoShrinkImagesPropertyInfo where type AttrAllowedOps WebSettingsAutoShrinkImagesPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebSettingsAutoShrinkImagesPropertyInfo = (~) Bool type AttrBaseTypeConstraint WebSettingsAutoShrinkImagesPropertyInfo = WebSettingsK type AttrGetType WebSettingsAutoShrinkImagesPropertyInfo = Bool type AttrLabel WebSettingsAutoShrinkImagesPropertyInfo = "WebSettings::auto-shrink-images" attrGet _ = getWebSettingsAutoShrinkImages attrSet _ = setWebSettingsAutoShrinkImages attrConstruct _ = constructWebSettingsAutoShrinkImages -- VVV Prop "cursive-font-family" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebSettingsCursiveFontFamily :: (MonadIO m, WebSettingsK o) => o -> m T.Text getWebSettingsCursiveFontFamily obj = liftIO $ getObjectPropertyString obj "cursive-font-family" setWebSettingsCursiveFontFamily :: (MonadIO m, WebSettingsK o) => o -> T.Text -> m () setWebSettingsCursiveFontFamily obj val = liftIO $ setObjectPropertyString obj "cursive-font-family" val constructWebSettingsCursiveFontFamily :: T.Text -> IO ([Char], GValue) constructWebSettingsCursiveFontFamily val = constructObjectPropertyString "cursive-font-family" val data WebSettingsCursiveFontFamilyPropertyInfo instance AttrInfo WebSettingsCursiveFontFamilyPropertyInfo where type AttrAllowedOps WebSettingsCursiveFontFamilyPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebSettingsCursiveFontFamilyPropertyInfo = (~) T.Text type AttrBaseTypeConstraint WebSettingsCursiveFontFamilyPropertyInfo = WebSettingsK type AttrGetType WebSettingsCursiveFontFamilyPropertyInfo = T.Text type AttrLabel WebSettingsCursiveFontFamilyPropertyInfo = "WebSettings::cursive-font-family" attrGet _ = getWebSettingsCursiveFontFamily attrSet _ = setWebSettingsCursiveFontFamily attrConstruct _ = constructWebSettingsCursiveFontFamily -- VVV Prop "default-encoding" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebSettingsDefaultEncoding :: (MonadIO m, WebSettingsK o) => o -> m T.Text getWebSettingsDefaultEncoding obj = liftIO $ getObjectPropertyString obj "default-encoding" setWebSettingsDefaultEncoding :: (MonadIO m, WebSettingsK o) => o -> T.Text -> m () setWebSettingsDefaultEncoding obj val = liftIO $ setObjectPropertyString obj "default-encoding" val constructWebSettingsDefaultEncoding :: T.Text -> IO ([Char], GValue) constructWebSettingsDefaultEncoding val = constructObjectPropertyString "default-encoding" val data WebSettingsDefaultEncodingPropertyInfo instance AttrInfo WebSettingsDefaultEncodingPropertyInfo where type AttrAllowedOps WebSettingsDefaultEncodingPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebSettingsDefaultEncodingPropertyInfo = (~) T.Text type AttrBaseTypeConstraint WebSettingsDefaultEncodingPropertyInfo = WebSettingsK type AttrGetType WebSettingsDefaultEncodingPropertyInfo = T.Text type AttrLabel WebSettingsDefaultEncodingPropertyInfo = "WebSettings::default-encoding" attrGet _ = getWebSettingsDefaultEncoding attrSet _ = setWebSettingsDefaultEncoding attrConstruct _ = constructWebSettingsDefaultEncoding -- VVV Prop "default-font-family" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebSettingsDefaultFontFamily :: (MonadIO m, WebSettingsK o) => o -> m T.Text getWebSettingsDefaultFontFamily obj = liftIO $ getObjectPropertyString obj "default-font-family" setWebSettingsDefaultFontFamily :: (MonadIO m, WebSettingsK o) => o -> T.Text -> m () setWebSettingsDefaultFontFamily obj val = liftIO $ setObjectPropertyString obj "default-font-family" val constructWebSettingsDefaultFontFamily :: T.Text -> IO ([Char], GValue) constructWebSettingsDefaultFontFamily val = constructObjectPropertyString "default-font-family" val data WebSettingsDefaultFontFamilyPropertyInfo instance AttrInfo WebSettingsDefaultFontFamilyPropertyInfo where type AttrAllowedOps WebSettingsDefaultFontFamilyPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebSettingsDefaultFontFamilyPropertyInfo = (~) T.Text type AttrBaseTypeConstraint WebSettingsDefaultFontFamilyPropertyInfo = WebSettingsK type AttrGetType WebSettingsDefaultFontFamilyPropertyInfo = T.Text type AttrLabel WebSettingsDefaultFontFamilyPropertyInfo = "WebSettings::default-font-family" attrGet _ = getWebSettingsDefaultFontFamily attrSet _ = setWebSettingsDefaultFontFamily attrConstruct _ = constructWebSettingsDefaultFontFamily -- VVV Prop "default-font-size" -- Type: TBasicType TInt32 -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebSettingsDefaultFontSize :: (MonadIO m, WebSettingsK o) => o -> m Int32 getWebSettingsDefaultFontSize obj = liftIO $ getObjectPropertyCInt obj "default-font-size" setWebSettingsDefaultFontSize :: (MonadIO m, WebSettingsK o) => o -> Int32 -> m () setWebSettingsDefaultFontSize obj val = liftIO $ setObjectPropertyCInt obj "default-font-size" val constructWebSettingsDefaultFontSize :: Int32 -> IO ([Char], GValue) constructWebSettingsDefaultFontSize val = constructObjectPropertyCInt "default-font-size" val data WebSettingsDefaultFontSizePropertyInfo instance AttrInfo WebSettingsDefaultFontSizePropertyInfo where type AttrAllowedOps WebSettingsDefaultFontSizePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebSettingsDefaultFontSizePropertyInfo = (~) Int32 type AttrBaseTypeConstraint WebSettingsDefaultFontSizePropertyInfo = WebSettingsK type AttrGetType WebSettingsDefaultFontSizePropertyInfo = Int32 type AttrLabel WebSettingsDefaultFontSizePropertyInfo = "WebSettings::default-font-size" attrGet _ = getWebSettingsDefaultFontSize attrSet _ = setWebSettingsDefaultFontSize attrConstruct _ = constructWebSettingsDefaultFontSize -- VVV Prop "default-monospace-font-size" -- Type: TBasicType TInt32 -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebSettingsDefaultMonospaceFontSize :: (MonadIO m, WebSettingsK o) => o -> m Int32 getWebSettingsDefaultMonospaceFontSize obj = liftIO $ getObjectPropertyCInt obj "default-monospace-font-size" setWebSettingsDefaultMonospaceFontSize :: (MonadIO m, WebSettingsK o) => o -> Int32 -> m () setWebSettingsDefaultMonospaceFontSize obj val = liftIO $ setObjectPropertyCInt obj "default-monospace-font-size" val constructWebSettingsDefaultMonospaceFontSize :: Int32 -> IO ([Char], GValue) constructWebSettingsDefaultMonospaceFontSize val = constructObjectPropertyCInt "default-monospace-font-size" val data WebSettingsDefaultMonospaceFontSizePropertyInfo instance AttrInfo WebSettingsDefaultMonospaceFontSizePropertyInfo where type AttrAllowedOps WebSettingsDefaultMonospaceFontSizePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebSettingsDefaultMonospaceFontSizePropertyInfo = (~) Int32 type AttrBaseTypeConstraint WebSettingsDefaultMonospaceFontSizePropertyInfo = WebSettingsK type AttrGetType WebSettingsDefaultMonospaceFontSizePropertyInfo = Int32 type AttrLabel WebSettingsDefaultMonospaceFontSizePropertyInfo = "WebSettings::default-monospace-font-size" attrGet _ = getWebSettingsDefaultMonospaceFontSize attrSet _ = setWebSettingsDefaultMonospaceFontSize attrConstruct _ = constructWebSettingsDefaultMonospaceFontSize -- VVV Prop "editing-behavior" -- Type: TInterface "WebKit" "EditingBehavior" -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebSettingsEditingBehavior :: (MonadIO m, WebSettingsK o) => o -> m EditingBehavior getWebSettingsEditingBehavior obj = liftIO $ getObjectPropertyEnum obj "editing-behavior" setWebSettingsEditingBehavior :: (MonadIO m, WebSettingsK o) => o -> EditingBehavior -> m () setWebSettingsEditingBehavior obj val = liftIO $ setObjectPropertyEnum obj "editing-behavior" val constructWebSettingsEditingBehavior :: EditingBehavior -> IO ([Char], GValue) constructWebSettingsEditingBehavior val = constructObjectPropertyEnum "editing-behavior" val data WebSettingsEditingBehaviorPropertyInfo instance AttrInfo WebSettingsEditingBehaviorPropertyInfo where type AttrAllowedOps WebSettingsEditingBehaviorPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebSettingsEditingBehaviorPropertyInfo = (~) EditingBehavior type AttrBaseTypeConstraint WebSettingsEditingBehaviorPropertyInfo = WebSettingsK type AttrGetType WebSettingsEditingBehaviorPropertyInfo = EditingBehavior type AttrLabel WebSettingsEditingBehaviorPropertyInfo = "WebSettings::editing-behavior" attrGet _ = getWebSettingsEditingBehavior attrSet _ = setWebSettingsEditingBehavior attrConstruct _ = constructWebSettingsEditingBehavior -- VVV Prop "enable-accelerated-compositing" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebSettingsEnableAcceleratedCompositing :: (MonadIO m, WebSettingsK o) => o -> m Bool getWebSettingsEnableAcceleratedCompositing obj = liftIO $ getObjectPropertyBool obj "enable-accelerated-compositing" setWebSettingsEnableAcceleratedCompositing :: (MonadIO m, WebSettingsK o) => o -> Bool -> m () setWebSettingsEnableAcceleratedCompositing obj val = liftIO $ setObjectPropertyBool obj "enable-accelerated-compositing" val constructWebSettingsEnableAcceleratedCompositing :: Bool -> IO ([Char], GValue) constructWebSettingsEnableAcceleratedCompositing val = constructObjectPropertyBool "enable-accelerated-compositing" val data WebSettingsEnableAcceleratedCompositingPropertyInfo instance AttrInfo WebSettingsEnableAcceleratedCompositingPropertyInfo where type AttrAllowedOps WebSettingsEnableAcceleratedCompositingPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebSettingsEnableAcceleratedCompositingPropertyInfo = (~) Bool type AttrBaseTypeConstraint WebSettingsEnableAcceleratedCompositingPropertyInfo = WebSettingsK type AttrGetType WebSettingsEnableAcceleratedCompositingPropertyInfo = Bool type AttrLabel WebSettingsEnableAcceleratedCompositingPropertyInfo = "WebSettings::enable-accelerated-compositing" attrGet _ = getWebSettingsEnableAcceleratedCompositing attrSet _ = setWebSettingsEnableAcceleratedCompositing attrConstruct _ = constructWebSettingsEnableAcceleratedCompositing -- VVV Prop "enable-caret-browsing" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebSettingsEnableCaretBrowsing :: (MonadIO m, WebSettingsK o) => o -> m Bool getWebSettingsEnableCaretBrowsing obj = liftIO $ getObjectPropertyBool obj "enable-caret-browsing" setWebSettingsEnableCaretBrowsing :: (MonadIO m, WebSettingsK o) => o -> Bool -> m () setWebSettingsEnableCaretBrowsing obj val = liftIO $ setObjectPropertyBool obj "enable-caret-browsing" val constructWebSettingsEnableCaretBrowsing :: Bool -> IO ([Char], GValue) constructWebSettingsEnableCaretBrowsing val = constructObjectPropertyBool "enable-caret-browsing" val data WebSettingsEnableCaretBrowsingPropertyInfo instance AttrInfo WebSettingsEnableCaretBrowsingPropertyInfo where type AttrAllowedOps WebSettingsEnableCaretBrowsingPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebSettingsEnableCaretBrowsingPropertyInfo = (~) Bool type AttrBaseTypeConstraint WebSettingsEnableCaretBrowsingPropertyInfo = WebSettingsK type AttrGetType WebSettingsEnableCaretBrowsingPropertyInfo = Bool type AttrLabel WebSettingsEnableCaretBrowsingPropertyInfo = "WebSettings::enable-caret-browsing" attrGet _ = getWebSettingsEnableCaretBrowsing attrSet _ = setWebSettingsEnableCaretBrowsing attrConstruct _ = constructWebSettingsEnableCaretBrowsing -- VVV Prop "enable-default-context-menu" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebSettingsEnableDefaultContextMenu :: (MonadIO m, WebSettingsK o) => o -> m Bool getWebSettingsEnableDefaultContextMenu obj = liftIO $ getObjectPropertyBool obj "enable-default-context-menu" setWebSettingsEnableDefaultContextMenu :: (MonadIO m, WebSettingsK o) => o -> Bool -> m () setWebSettingsEnableDefaultContextMenu obj val = liftIO $ setObjectPropertyBool obj "enable-default-context-menu" val constructWebSettingsEnableDefaultContextMenu :: Bool -> IO ([Char], GValue) constructWebSettingsEnableDefaultContextMenu val = constructObjectPropertyBool "enable-default-context-menu" val data WebSettingsEnableDefaultContextMenuPropertyInfo instance AttrInfo WebSettingsEnableDefaultContextMenuPropertyInfo where type AttrAllowedOps WebSettingsEnableDefaultContextMenuPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebSettingsEnableDefaultContextMenuPropertyInfo = (~) Bool type AttrBaseTypeConstraint WebSettingsEnableDefaultContextMenuPropertyInfo = WebSettingsK type AttrGetType WebSettingsEnableDefaultContextMenuPropertyInfo = Bool type AttrLabel WebSettingsEnableDefaultContextMenuPropertyInfo = "WebSettings::enable-default-context-menu" attrGet _ = getWebSettingsEnableDefaultContextMenu attrSet _ = setWebSettingsEnableDefaultContextMenu attrConstruct _ = constructWebSettingsEnableDefaultContextMenu -- VVV Prop "enable-developer-extras" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebSettingsEnableDeveloperExtras :: (MonadIO m, WebSettingsK o) => o -> m Bool getWebSettingsEnableDeveloperExtras obj = liftIO $ getObjectPropertyBool obj "enable-developer-extras" setWebSettingsEnableDeveloperExtras :: (MonadIO m, WebSettingsK o) => o -> Bool -> m () setWebSettingsEnableDeveloperExtras obj val = liftIO $ setObjectPropertyBool obj "enable-developer-extras" val constructWebSettingsEnableDeveloperExtras :: Bool -> IO ([Char], GValue) constructWebSettingsEnableDeveloperExtras val = constructObjectPropertyBool "enable-developer-extras" val data WebSettingsEnableDeveloperExtrasPropertyInfo instance AttrInfo WebSettingsEnableDeveloperExtrasPropertyInfo where type AttrAllowedOps WebSettingsEnableDeveloperExtrasPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebSettingsEnableDeveloperExtrasPropertyInfo = (~) Bool type AttrBaseTypeConstraint WebSettingsEnableDeveloperExtrasPropertyInfo = WebSettingsK type AttrGetType WebSettingsEnableDeveloperExtrasPropertyInfo = Bool type AttrLabel WebSettingsEnableDeveloperExtrasPropertyInfo = "WebSettings::enable-developer-extras" attrGet _ = getWebSettingsEnableDeveloperExtras attrSet _ = setWebSettingsEnableDeveloperExtras attrConstruct _ = constructWebSettingsEnableDeveloperExtras -- VVV Prop "enable-display-of-insecure-content" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebSettingsEnableDisplayOfInsecureContent :: (MonadIO m, WebSettingsK o) => o -> m Bool getWebSettingsEnableDisplayOfInsecureContent obj = liftIO $ getObjectPropertyBool obj "enable-display-of-insecure-content" setWebSettingsEnableDisplayOfInsecureContent :: (MonadIO m, WebSettingsK o) => o -> Bool -> m () setWebSettingsEnableDisplayOfInsecureContent obj val = liftIO $ setObjectPropertyBool obj "enable-display-of-insecure-content" val constructWebSettingsEnableDisplayOfInsecureContent :: Bool -> IO ([Char], GValue) constructWebSettingsEnableDisplayOfInsecureContent val = constructObjectPropertyBool "enable-display-of-insecure-content" val data WebSettingsEnableDisplayOfInsecureContentPropertyInfo instance AttrInfo WebSettingsEnableDisplayOfInsecureContentPropertyInfo where type AttrAllowedOps WebSettingsEnableDisplayOfInsecureContentPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebSettingsEnableDisplayOfInsecureContentPropertyInfo = (~) Bool type AttrBaseTypeConstraint WebSettingsEnableDisplayOfInsecureContentPropertyInfo = WebSettingsK type AttrGetType WebSettingsEnableDisplayOfInsecureContentPropertyInfo = Bool type AttrLabel WebSettingsEnableDisplayOfInsecureContentPropertyInfo = "WebSettings::enable-display-of-insecure-content" attrGet _ = getWebSettingsEnableDisplayOfInsecureContent attrSet _ = setWebSettingsEnableDisplayOfInsecureContent attrConstruct _ = constructWebSettingsEnableDisplayOfInsecureContent -- VVV Prop "enable-dns-prefetching" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebSettingsEnableDnsPrefetching :: (MonadIO m, WebSettingsK o) => o -> m Bool getWebSettingsEnableDnsPrefetching obj = liftIO $ getObjectPropertyBool obj "enable-dns-prefetching" setWebSettingsEnableDnsPrefetching :: (MonadIO m, WebSettingsK o) => o -> Bool -> m () setWebSettingsEnableDnsPrefetching obj val = liftIO $ setObjectPropertyBool obj "enable-dns-prefetching" val constructWebSettingsEnableDnsPrefetching :: Bool -> IO ([Char], GValue) constructWebSettingsEnableDnsPrefetching val = constructObjectPropertyBool "enable-dns-prefetching" val data WebSettingsEnableDnsPrefetchingPropertyInfo instance AttrInfo WebSettingsEnableDnsPrefetchingPropertyInfo where type AttrAllowedOps WebSettingsEnableDnsPrefetchingPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebSettingsEnableDnsPrefetchingPropertyInfo = (~) Bool type AttrBaseTypeConstraint WebSettingsEnableDnsPrefetchingPropertyInfo = WebSettingsK type AttrGetType WebSettingsEnableDnsPrefetchingPropertyInfo = Bool type AttrLabel WebSettingsEnableDnsPrefetchingPropertyInfo = "WebSettings::enable-dns-prefetching" attrGet _ = getWebSettingsEnableDnsPrefetching attrSet _ = setWebSettingsEnableDnsPrefetching attrConstruct _ = constructWebSettingsEnableDnsPrefetching -- VVV Prop "enable-dom-paste" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebSettingsEnableDomPaste :: (MonadIO m, WebSettingsK o) => o -> m Bool getWebSettingsEnableDomPaste obj = liftIO $ getObjectPropertyBool obj "enable-dom-paste" setWebSettingsEnableDomPaste :: (MonadIO m, WebSettingsK o) => o -> Bool -> m () setWebSettingsEnableDomPaste obj val = liftIO $ setObjectPropertyBool obj "enable-dom-paste" val constructWebSettingsEnableDomPaste :: Bool -> IO ([Char], GValue) constructWebSettingsEnableDomPaste val = constructObjectPropertyBool "enable-dom-paste" val data WebSettingsEnableDomPastePropertyInfo instance AttrInfo WebSettingsEnableDomPastePropertyInfo where type AttrAllowedOps WebSettingsEnableDomPastePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebSettingsEnableDomPastePropertyInfo = (~) Bool type AttrBaseTypeConstraint WebSettingsEnableDomPastePropertyInfo = WebSettingsK type AttrGetType WebSettingsEnableDomPastePropertyInfo = Bool type AttrLabel WebSettingsEnableDomPastePropertyInfo = "WebSettings::enable-dom-paste" attrGet _ = getWebSettingsEnableDomPaste attrSet _ = setWebSettingsEnableDomPaste attrConstruct _ = constructWebSettingsEnableDomPaste -- VVV Prop "enable-file-access-from-file-uris" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebSettingsEnableFileAccessFromFileUris :: (MonadIO m, WebSettingsK o) => o -> m Bool getWebSettingsEnableFileAccessFromFileUris obj = liftIO $ getObjectPropertyBool obj "enable-file-access-from-file-uris" setWebSettingsEnableFileAccessFromFileUris :: (MonadIO m, WebSettingsK o) => o -> Bool -> m () setWebSettingsEnableFileAccessFromFileUris obj val = liftIO $ setObjectPropertyBool obj "enable-file-access-from-file-uris" val constructWebSettingsEnableFileAccessFromFileUris :: Bool -> IO ([Char], GValue) constructWebSettingsEnableFileAccessFromFileUris val = constructObjectPropertyBool "enable-file-access-from-file-uris" val data WebSettingsEnableFileAccessFromFileUrisPropertyInfo instance AttrInfo WebSettingsEnableFileAccessFromFileUrisPropertyInfo where type AttrAllowedOps WebSettingsEnableFileAccessFromFileUrisPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebSettingsEnableFileAccessFromFileUrisPropertyInfo = (~) Bool type AttrBaseTypeConstraint WebSettingsEnableFileAccessFromFileUrisPropertyInfo = WebSettingsK type AttrGetType WebSettingsEnableFileAccessFromFileUrisPropertyInfo = Bool type AttrLabel WebSettingsEnableFileAccessFromFileUrisPropertyInfo = "WebSettings::enable-file-access-from-file-uris" attrGet _ = getWebSettingsEnableFileAccessFromFileUris attrSet _ = setWebSettingsEnableFileAccessFromFileUris attrConstruct _ = constructWebSettingsEnableFileAccessFromFileUris -- VVV Prop "enable-frame-flattening" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebSettingsEnableFrameFlattening :: (MonadIO m, WebSettingsK o) => o -> m Bool getWebSettingsEnableFrameFlattening obj = liftIO $ getObjectPropertyBool obj "enable-frame-flattening" setWebSettingsEnableFrameFlattening :: (MonadIO m, WebSettingsK o) => o -> Bool -> m () setWebSettingsEnableFrameFlattening obj val = liftIO $ setObjectPropertyBool obj "enable-frame-flattening" val constructWebSettingsEnableFrameFlattening :: Bool -> IO ([Char], GValue) constructWebSettingsEnableFrameFlattening val = constructObjectPropertyBool "enable-frame-flattening" val data WebSettingsEnableFrameFlatteningPropertyInfo instance AttrInfo WebSettingsEnableFrameFlatteningPropertyInfo where type AttrAllowedOps WebSettingsEnableFrameFlatteningPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebSettingsEnableFrameFlatteningPropertyInfo = (~) Bool type AttrBaseTypeConstraint WebSettingsEnableFrameFlatteningPropertyInfo = WebSettingsK type AttrGetType WebSettingsEnableFrameFlatteningPropertyInfo = Bool type AttrLabel WebSettingsEnableFrameFlatteningPropertyInfo = "WebSettings::enable-frame-flattening" attrGet _ = getWebSettingsEnableFrameFlattening attrSet _ = setWebSettingsEnableFrameFlattening attrConstruct _ = constructWebSettingsEnableFrameFlattening -- VVV Prop "enable-fullscreen" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebSettingsEnableFullscreen :: (MonadIO m, WebSettingsK o) => o -> m Bool getWebSettingsEnableFullscreen obj = liftIO $ getObjectPropertyBool obj "enable-fullscreen" setWebSettingsEnableFullscreen :: (MonadIO m, WebSettingsK o) => o -> Bool -> m () setWebSettingsEnableFullscreen obj val = liftIO $ setObjectPropertyBool obj "enable-fullscreen" val constructWebSettingsEnableFullscreen :: Bool -> IO ([Char], GValue) constructWebSettingsEnableFullscreen val = constructObjectPropertyBool "enable-fullscreen" val data WebSettingsEnableFullscreenPropertyInfo instance AttrInfo WebSettingsEnableFullscreenPropertyInfo where type AttrAllowedOps WebSettingsEnableFullscreenPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebSettingsEnableFullscreenPropertyInfo = (~) Bool type AttrBaseTypeConstraint WebSettingsEnableFullscreenPropertyInfo = WebSettingsK type AttrGetType WebSettingsEnableFullscreenPropertyInfo = Bool type AttrLabel WebSettingsEnableFullscreenPropertyInfo = "WebSettings::enable-fullscreen" attrGet _ = getWebSettingsEnableFullscreen attrSet _ = setWebSettingsEnableFullscreen attrConstruct _ = constructWebSettingsEnableFullscreen -- VVV Prop "enable-html5-database" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebSettingsEnableHtml5Database :: (MonadIO m, WebSettingsK o) => o -> m Bool getWebSettingsEnableHtml5Database obj = liftIO $ getObjectPropertyBool obj "enable-html5-database" setWebSettingsEnableHtml5Database :: (MonadIO m, WebSettingsK o) => o -> Bool -> m () setWebSettingsEnableHtml5Database obj val = liftIO $ setObjectPropertyBool obj "enable-html5-database" val constructWebSettingsEnableHtml5Database :: Bool -> IO ([Char], GValue) constructWebSettingsEnableHtml5Database val = constructObjectPropertyBool "enable-html5-database" val data WebSettingsEnableHtml5DatabasePropertyInfo instance AttrInfo WebSettingsEnableHtml5DatabasePropertyInfo where type AttrAllowedOps WebSettingsEnableHtml5DatabasePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebSettingsEnableHtml5DatabasePropertyInfo = (~) Bool type AttrBaseTypeConstraint WebSettingsEnableHtml5DatabasePropertyInfo = WebSettingsK type AttrGetType WebSettingsEnableHtml5DatabasePropertyInfo = Bool type AttrLabel WebSettingsEnableHtml5DatabasePropertyInfo = "WebSettings::enable-html5-database" attrGet _ = getWebSettingsEnableHtml5Database attrSet _ = setWebSettingsEnableHtml5Database attrConstruct _ = constructWebSettingsEnableHtml5Database -- VVV Prop "enable-html5-local-storage" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebSettingsEnableHtml5LocalStorage :: (MonadIO m, WebSettingsK o) => o -> m Bool getWebSettingsEnableHtml5LocalStorage obj = liftIO $ getObjectPropertyBool obj "enable-html5-local-storage" setWebSettingsEnableHtml5LocalStorage :: (MonadIO m, WebSettingsK o) => o -> Bool -> m () setWebSettingsEnableHtml5LocalStorage obj val = liftIO $ setObjectPropertyBool obj "enable-html5-local-storage" val constructWebSettingsEnableHtml5LocalStorage :: Bool -> IO ([Char], GValue) constructWebSettingsEnableHtml5LocalStorage val = constructObjectPropertyBool "enable-html5-local-storage" val data WebSettingsEnableHtml5LocalStoragePropertyInfo instance AttrInfo WebSettingsEnableHtml5LocalStoragePropertyInfo where type AttrAllowedOps WebSettingsEnableHtml5LocalStoragePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebSettingsEnableHtml5LocalStoragePropertyInfo = (~) Bool type AttrBaseTypeConstraint WebSettingsEnableHtml5LocalStoragePropertyInfo = WebSettingsK type AttrGetType WebSettingsEnableHtml5LocalStoragePropertyInfo = Bool type AttrLabel WebSettingsEnableHtml5LocalStoragePropertyInfo = "WebSettings::enable-html5-local-storage" attrGet _ = getWebSettingsEnableHtml5LocalStorage attrSet _ = setWebSettingsEnableHtml5LocalStorage attrConstruct _ = constructWebSettingsEnableHtml5LocalStorage -- VVV Prop "enable-hyperlink-auditing" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebSettingsEnableHyperlinkAuditing :: (MonadIO m, WebSettingsK o) => o -> m Bool getWebSettingsEnableHyperlinkAuditing obj = liftIO $ getObjectPropertyBool obj "enable-hyperlink-auditing" setWebSettingsEnableHyperlinkAuditing :: (MonadIO m, WebSettingsK o) => o -> Bool -> m () setWebSettingsEnableHyperlinkAuditing obj val = liftIO $ setObjectPropertyBool obj "enable-hyperlink-auditing" val constructWebSettingsEnableHyperlinkAuditing :: Bool -> IO ([Char], GValue) constructWebSettingsEnableHyperlinkAuditing val = constructObjectPropertyBool "enable-hyperlink-auditing" val data WebSettingsEnableHyperlinkAuditingPropertyInfo instance AttrInfo WebSettingsEnableHyperlinkAuditingPropertyInfo where type AttrAllowedOps WebSettingsEnableHyperlinkAuditingPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebSettingsEnableHyperlinkAuditingPropertyInfo = (~) Bool type AttrBaseTypeConstraint WebSettingsEnableHyperlinkAuditingPropertyInfo = WebSettingsK type AttrGetType WebSettingsEnableHyperlinkAuditingPropertyInfo = Bool type AttrLabel WebSettingsEnableHyperlinkAuditingPropertyInfo = "WebSettings::enable-hyperlink-auditing" attrGet _ = getWebSettingsEnableHyperlinkAuditing attrSet _ = setWebSettingsEnableHyperlinkAuditing attrConstruct _ = constructWebSettingsEnableHyperlinkAuditing -- VVV Prop "enable-java-applet" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebSettingsEnableJavaApplet :: (MonadIO m, WebSettingsK o) => o -> m Bool getWebSettingsEnableJavaApplet obj = liftIO $ getObjectPropertyBool obj "enable-java-applet" setWebSettingsEnableJavaApplet :: (MonadIO m, WebSettingsK o) => o -> Bool -> m () setWebSettingsEnableJavaApplet obj val = liftIO $ setObjectPropertyBool obj "enable-java-applet" val constructWebSettingsEnableJavaApplet :: Bool -> IO ([Char], GValue) constructWebSettingsEnableJavaApplet val = constructObjectPropertyBool "enable-java-applet" val data WebSettingsEnableJavaAppletPropertyInfo instance AttrInfo WebSettingsEnableJavaAppletPropertyInfo where type AttrAllowedOps WebSettingsEnableJavaAppletPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebSettingsEnableJavaAppletPropertyInfo = (~) Bool type AttrBaseTypeConstraint WebSettingsEnableJavaAppletPropertyInfo = WebSettingsK type AttrGetType WebSettingsEnableJavaAppletPropertyInfo = Bool type AttrLabel WebSettingsEnableJavaAppletPropertyInfo = "WebSettings::enable-java-applet" attrGet _ = getWebSettingsEnableJavaApplet attrSet _ = setWebSettingsEnableJavaApplet attrConstruct _ = constructWebSettingsEnableJavaApplet -- VVV Prop "enable-media-stream" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebSettingsEnableMediaStream :: (MonadIO m, WebSettingsK o) => o -> m Bool getWebSettingsEnableMediaStream obj = liftIO $ getObjectPropertyBool obj "enable-media-stream" setWebSettingsEnableMediaStream :: (MonadIO m, WebSettingsK o) => o -> Bool -> m () setWebSettingsEnableMediaStream obj val = liftIO $ setObjectPropertyBool obj "enable-media-stream" val constructWebSettingsEnableMediaStream :: Bool -> IO ([Char], GValue) constructWebSettingsEnableMediaStream val = constructObjectPropertyBool "enable-media-stream" val data WebSettingsEnableMediaStreamPropertyInfo instance AttrInfo WebSettingsEnableMediaStreamPropertyInfo where type AttrAllowedOps WebSettingsEnableMediaStreamPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebSettingsEnableMediaStreamPropertyInfo = (~) Bool type AttrBaseTypeConstraint WebSettingsEnableMediaStreamPropertyInfo = WebSettingsK type AttrGetType WebSettingsEnableMediaStreamPropertyInfo = Bool type AttrLabel WebSettingsEnableMediaStreamPropertyInfo = "WebSettings::enable-media-stream" attrGet _ = getWebSettingsEnableMediaStream attrSet _ = setWebSettingsEnableMediaStream attrConstruct _ = constructWebSettingsEnableMediaStream -- VVV Prop "enable-mediasource" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebSettingsEnableMediasource :: (MonadIO m, WebSettingsK o) => o -> m Bool getWebSettingsEnableMediasource obj = liftIO $ getObjectPropertyBool obj "enable-mediasource" setWebSettingsEnableMediasource :: (MonadIO m, WebSettingsK o) => o -> Bool -> m () setWebSettingsEnableMediasource obj val = liftIO $ setObjectPropertyBool obj "enable-mediasource" val constructWebSettingsEnableMediasource :: Bool -> IO ([Char], GValue) constructWebSettingsEnableMediasource val = constructObjectPropertyBool "enable-mediasource" val data WebSettingsEnableMediasourcePropertyInfo instance AttrInfo WebSettingsEnableMediasourcePropertyInfo where type AttrAllowedOps WebSettingsEnableMediasourcePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebSettingsEnableMediasourcePropertyInfo = (~) Bool type AttrBaseTypeConstraint WebSettingsEnableMediasourcePropertyInfo = WebSettingsK type AttrGetType WebSettingsEnableMediasourcePropertyInfo = Bool type AttrLabel WebSettingsEnableMediasourcePropertyInfo = "WebSettings::enable-mediasource" attrGet _ = getWebSettingsEnableMediasource attrSet _ = setWebSettingsEnableMediasource attrConstruct _ = constructWebSettingsEnableMediasource -- VVV Prop "enable-offline-web-application-cache" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebSettingsEnableOfflineWebApplicationCache :: (MonadIO m, WebSettingsK o) => o -> m Bool getWebSettingsEnableOfflineWebApplicationCache obj = liftIO $ getObjectPropertyBool obj "enable-offline-web-application-cache" setWebSettingsEnableOfflineWebApplicationCache :: (MonadIO m, WebSettingsK o) => o -> Bool -> m () setWebSettingsEnableOfflineWebApplicationCache obj val = liftIO $ setObjectPropertyBool obj "enable-offline-web-application-cache" val constructWebSettingsEnableOfflineWebApplicationCache :: Bool -> IO ([Char], GValue) constructWebSettingsEnableOfflineWebApplicationCache val = constructObjectPropertyBool "enable-offline-web-application-cache" val data WebSettingsEnableOfflineWebApplicationCachePropertyInfo instance AttrInfo WebSettingsEnableOfflineWebApplicationCachePropertyInfo where type AttrAllowedOps WebSettingsEnableOfflineWebApplicationCachePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebSettingsEnableOfflineWebApplicationCachePropertyInfo = (~) Bool type AttrBaseTypeConstraint WebSettingsEnableOfflineWebApplicationCachePropertyInfo = WebSettingsK type AttrGetType WebSettingsEnableOfflineWebApplicationCachePropertyInfo = Bool type AttrLabel WebSettingsEnableOfflineWebApplicationCachePropertyInfo = "WebSettings::enable-offline-web-application-cache" attrGet _ = getWebSettingsEnableOfflineWebApplicationCache attrSet _ = setWebSettingsEnableOfflineWebApplicationCache attrConstruct _ = constructWebSettingsEnableOfflineWebApplicationCache -- VVV Prop "enable-page-cache" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebSettingsEnablePageCache :: (MonadIO m, WebSettingsK o) => o -> m Bool getWebSettingsEnablePageCache obj = liftIO $ getObjectPropertyBool obj "enable-page-cache" setWebSettingsEnablePageCache :: (MonadIO m, WebSettingsK o) => o -> Bool -> m () setWebSettingsEnablePageCache obj val = liftIO $ setObjectPropertyBool obj "enable-page-cache" val constructWebSettingsEnablePageCache :: Bool -> IO ([Char], GValue) constructWebSettingsEnablePageCache val = constructObjectPropertyBool "enable-page-cache" val data WebSettingsEnablePageCachePropertyInfo instance AttrInfo WebSettingsEnablePageCachePropertyInfo where type AttrAllowedOps WebSettingsEnablePageCachePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebSettingsEnablePageCachePropertyInfo = (~) Bool type AttrBaseTypeConstraint WebSettingsEnablePageCachePropertyInfo = WebSettingsK type AttrGetType WebSettingsEnablePageCachePropertyInfo = Bool type AttrLabel WebSettingsEnablePageCachePropertyInfo = "WebSettings::enable-page-cache" attrGet _ = getWebSettingsEnablePageCache attrSet _ = setWebSettingsEnablePageCache attrConstruct _ = constructWebSettingsEnablePageCache -- VVV Prop "enable-plugins" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebSettingsEnablePlugins :: (MonadIO m, WebSettingsK o) => o -> m Bool getWebSettingsEnablePlugins obj = liftIO $ getObjectPropertyBool obj "enable-plugins" setWebSettingsEnablePlugins :: (MonadIO m, WebSettingsK o) => o -> Bool -> m () setWebSettingsEnablePlugins obj val = liftIO $ setObjectPropertyBool obj "enable-plugins" val constructWebSettingsEnablePlugins :: Bool -> IO ([Char], GValue) constructWebSettingsEnablePlugins val = constructObjectPropertyBool "enable-plugins" val data WebSettingsEnablePluginsPropertyInfo instance AttrInfo WebSettingsEnablePluginsPropertyInfo where type AttrAllowedOps WebSettingsEnablePluginsPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebSettingsEnablePluginsPropertyInfo = (~) Bool type AttrBaseTypeConstraint WebSettingsEnablePluginsPropertyInfo = WebSettingsK type AttrGetType WebSettingsEnablePluginsPropertyInfo = Bool type AttrLabel WebSettingsEnablePluginsPropertyInfo = "WebSettings::enable-plugins" attrGet _ = getWebSettingsEnablePlugins attrSet _ = setWebSettingsEnablePlugins attrConstruct _ = constructWebSettingsEnablePlugins -- VVV Prop "enable-private-browsing" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebSettingsEnablePrivateBrowsing :: (MonadIO m, WebSettingsK o) => o -> m Bool getWebSettingsEnablePrivateBrowsing obj = liftIO $ getObjectPropertyBool obj "enable-private-browsing" setWebSettingsEnablePrivateBrowsing :: (MonadIO m, WebSettingsK o) => o -> Bool -> m () setWebSettingsEnablePrivateBrowsing obj val = liftIO $ setObjectPropertyBool obj "enable-private-browsing" val constructWebSettingsEnablePrivateBrowsing :: Bool -> IO ([Char], GValue) constructWebSettingsEnablePrivateBrowsing val = constructObjectPropertyBool "enable-private-browsing" val data WebSettingsEnablePrivateBrowsingPropertyInfo instance AttrInfo WebSettingsEnablePrivateBrowsingPropertyInfo where type AttrAllowedOps WebSettingsEnablePrivateBrowsingPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebSettingsEnablePrivateBrowsingPropertyInfo = (~) Bool type AttrBaseTypeConstraint WebSettingsEnablePrivateBrowsingPropertyInfo = WebSettingsK type AttrGetType WebSettingsEnablePrivateBrowsingPropertyInfo = Bool type AttrLabel WebSettingsEnablePrivateBrowsingPropertyInfo = "WebSettings::enable-private-browsing" attrGet _ = getWebSettingsEnablePrivateBrowsing attrSet _ = setWebSettingsEnablePrivateBrowsing attrConstruct _ = constructWebSettingsEnablePrivateBrowsing -- VVV Prop "enable-running-of-insecure-content" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebSettingsEnableRunningOfInsecureContent :: (MonadIO m, WebSettingsK o) => o -> m Bool getWebSettingsEnableRunningOfInsecureContent obj = liftIO $ getObjectPropertyBool obj "enable-running-of-insecure-content" setWebSettingsEnableRunningOfInsecureContent :: (MonadIO m, WebSettingsK o) => o -> Bool -> m () setWebSettingsEnableRunningOfInsecureContent obj val = liftIO $ setObjectPropertyBool obj "enable-running-of-insecure-content" val constructWebSettingsEnableRunningOfInsecureContent :: Bool -> IO ([Char], GValue) constructWebSettingsEnableRunningOfInsecureContent val = constructObjectPropertyBool "enable-running-of-insecure-content" val data WebSettingsEnableRunningOfInsecureContentPropertyInfo instance AttrInfo WebSettingsEnableRunningOfInsecureContentPropertyInfo where type AttrAllowedOps WebSettingsEnableRunningOfInsecureContentPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebSettingsEnableRunningOfInsecureContentPropertyInfo = (~) Bool type AttrBaseTypeConstraint WebSettingsEnableRunningOfInsecureContentPropertyInfo = WebSettingsK type AttrGetType WebSettingsEnableRunningOfInsecureContentPropertyInfo = Bool type AttrLabel WebSettingsEnableRunningOfInsecureContentPropertyInfo = "WebSettings::enable-running-of-insecure-content" attrGet _ = getWebSettingsEnableRunningOfInsecureContent attrSet _ = setWebSettingsEnableRunningOfInsecureContent attrConstruct _ = constructWebSettingsEnableRunningOfInsecureContent -- VVV Prop "enable-scripts" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebSettingsEnableScripts :: (MonadIO m, WebSettingsK o) => o -> m Bool getWebSettingsEnableScripts obj = liftIO $ getObjectPropertyBool obj "enable-scripts" setWebSettingsEnableScripts :: (MonadIO m, WebSettingsK o) => o -> Bool -> m () setWebSettingsEnableScripts obj val = liftIO $ setObjectPropertyBool obj "enable-scripts" val constructWebSettingsEnableScripts :: Bool -> IO ([Char], GValue) constructWebSettingsEnableScripts val = constructObjectPropertyBool "enable-scripts" val data WebSettingsEnableScriptsPropertyInfo instance AttrInfo WebSettingsEnableScriptsPropertyInfo where type AttrAllowedOps WebSettingsEnableScriptsPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebSettingsEnableScriptsPropertyInfo = (~) Bool type AttrBaseTypeConstraint WebSettingsEnableScriptsPropertyInfo = WebSettingsK type AttrGetType WebSettingsEnableScriptsPropertyInfo = Bool type AttrLabel WebSettingsEnableScriptsPropertyInfo = "WebSettings::enable-scripts" attrGet _ = getWebSettingsEnableScripts attrSet _ = setWebSettingsEnableScripts attrConstruct _ = constructWebSettingsEnableScripts -- VVV Prop "enable-site-specific-quirks" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebSettingsEnableSiteSpecificQuirks :: (MonadIO m, WebSettingsK o) => o -> m Bool getWebSettingsEnableSiteSpecificQuirks obj = liftIO $ getObjectPropertyBool obj "enable-site-specific-quirks" setWebSettingsEnableSiteSpecificQuirks :: (MonadIO m, WebSettingsK o) => o -> Bool -> m () setWebSettingsEnableSiteSpecificQuirks obj val = liftIO $ setObjectPropertyBool obj "enable-site-specific-quirks" val constructWebSettingsEnableSiteSpecificQuirks :: Bool -> IO ([Char], GValue) constructWebSettingsEnableSiteSpecificQuirks val = constructObjectPropertyBool "enable-site-specific-quirks" val data WebSettingsEnableSiteSpecificQuirksPropertyInfo instance AttrInfo WebSettingsEnableSiteSpecificQuirksPropertyInfo where type AttrAllowedOps WebSettingsEnableSiteSpecificQuirksPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebSettingsEnableSiteSpecificQuirksPropertyInfo = (~) Bool type AttrBaseTypeConstraint WebSettingsEnableSiteSpecificQuirksPropertyInfo = WebSettingsK type AttrGetType WebSettingsEnableSiteSpecificQuirksPropertyInfo = Bool type AttrLabel WebSettingsEnableSiteSpecificQuirksPropertyInfo = "WebSettings::enable-site-specific-quirks" attrGet _ = getWebSettingsEnableSiteSpecificQuirks attrSet _ = setWebSettingsEnableSiteSpecificQuirks attrConstruct _ = constructWebSettingsEnableSiteSpecificQuirks -- VVV Prop "enable-smooth-scrolling" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebSettingsEnableSmoothScrolling :: (MonadIO m, WebSettingsK o) => o -> m Bool getWebSettingsEnableSmoothScrolling obj = liftIO $ getObjectPropertyBool obj "enable-smooth-scrolling" setWebSettingsEnableSmoothScrolling :: (MonadIO m, WebSettingsK o) => o -> Bool -> m () setWebSettingsEnableSmoothScrolling obj val = liftIO $ setObjectPropertyBool obj "enable-smooth-scrolling" val constructWebSettingsEnableSmoothScrolling :: Bool -> IO ([Char], GValue) constructWebSettingsEnableSmoothScrolling val = constructObjectPropertyBool "enable-smooth-scrolling" val data WebSettingsEnableSmoothScrollingPropertyInfo instance AttrInfo WebSettingsEnableSmoothScrollingPropertyInfo where type AttrAllowedOps WebSettingsEnableSmoothScrollingPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebSettingsEnableSmoothScrollingPropertyInfo = (~) Bool type AttrBaseTypeConstraint WebSettingsEnableSmoothScrollingPropertyInfo = WebSettingsK type AttrGetType WebSettingsEnableSmoothScrollingPropertyInfo = Bool type AttrLabel WebSettingsEnableSmoothScrollingPropertyInfo = "WebSettings::enable-smooth-scrolling" attrGet _ = getWebSettingsEnableSmoothScrolling attrSet _ = setWebSettingsEnableSmoothScrolling attrConstruct _ = constructWebSettingsEnableSmoothScrolling -- VVV Prop "enable-spatial-navigation" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebSettingsEnableSpatialNavigation :: (MonadIO m, WebSettingsK o) => o -> m Bool getWebSettingsEnableSpatialNavigation obj = liftIO $ getObjectPropertyBool obj "enable-spatial-navigation" setWebSettingsEnableSpatialNavigation :: (MonadIO m, WebSettingsK o) => o -> Bool -> m () setWebSettingsEnableSpatialNavigation obj val = liftIO $ setObjectPropertyBool obj "enable-spatial-navigation" val constructWebSettingsEnableSpatialNavigation :: Bool -> IO ([Char], GValue) constructWebSettingsEnableSpatialNavigation val = constructObjectPropertyBool "enable-spatial-navigation" val data WebSettingsEnableSpatialNavigationPropertyInfo instance AttrInfo WebSettingsEnableSpatialNavigationPropertyInfo where type AttrAllowedOps WebSettingsEnableSpatialNavigationPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebSettingsEnableSpatialNavigationPropertyInfo = (~) Bool type AttrBaseTypeConstraint WebSettingsEnableSpatialNavigationPropertyInfo = WebSettingsK type AttrGetType WebSettingsEnableSpatialNavigationPropertyInfo = Bool type AttrLabel WebSettingsEnableSpatialNavigationPropertyInfo = "WebSettings::enable-spatial-navigation" attrGet _ = getWebSettingsEnableSpatialNavigation attrSet _ = setWebSettingsEnableSpatialNavigation attrConstruct _ = constructWebSettingsEnableSpatialNavigation -- VVV Prop "enable-spell-checking" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebSettingsEnableSpellChecking :: (MonadIO m, WebSettingsK o) => o -> m Bool getWebSettingsEnableSpellChecking obj = liftIO $ getObjectPropertyBool obj "enable-spell-checking" setWebSettingsEnableSpellChecking :: (MonadIO m, WebSettingsK o) => o -> Bool -> m () setWebSettingsEnableSpellChecking obj val = liftIO $ setObjectPropertyBool obj "enable-spell-checking" val constructWebSettingsEnableSpellChecking :: Bool -> IO ([Char], GValue) constructWebSettingsEnableSpellChecking val = constructObjectPropertyBool "enable-spell-checking" val data WebSettingsEnableSpellCheckingPropertyInfo instance AttrInfo WebSettingsEnableSpellCheckingPropertyInfo where type AttrAllowedOps WebSettingsEnableSpellCheckingPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebSettingsEnableSpellCheckingPropertyInfo = (~) Bool type AttrBaseTypeConstraint WebSettingsEnableSpellCheckingPropertyInfo = WebSettingsK type AttrGetType WebSettingsEnableSpellCheckingPropertyInfo = Bool type AttrLabel WebSettingsEnableSpellCheckingPropertyInfo = "WebSettings::enable-spell-checking" attrGet _ = getWebSettingsEnableSpellChecking attrSet _ = setWebSettingsEnableSpellChecking attrConstruct _ = constructWebSettingsEnableSpellChecking -- VVV Prop "enable-universal-access-from-file-uris" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebSettingsEnableUniversalAccessFromFileUris :: (MonadIO m, WebSettingsK o) => o -> m Bool getWebSettingsEnableUniversalAccessFromFileUris obj = liftIO $ getObjectPropertyBool obj "enable-universal-access-from-file-uris" setWebSettingsEnableUniversalAccessFromFileUris :: (MonadIO m, WebSettingsK o) => o -> Bool -> m () setWebSettingsEnableUniversalAccessFromFileUris obj val = liftIO $ setObjectPropertyBool obj "enable-universal-access-from-file-uris" val constructWebSettingsEnableUniversalAccessFromFileUris :: Bool -> IO ([Char], GValue) constructWebSettingsEnableUniversalAccessFromFileUris val = constructObjectPropertyBool "enable-universal-access-from-file-uris" val data WebSettingsEnableUniversalAccessFromFileUrisPropertyInfo instance AttrInfo WebSettingsEnableUniversalAccessFromFileUrisPropertyInfo where type AttrAllowedOps WebSettingsEnableUniversalAccessFromFileUrisPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebSettingsEnableUniversalAccessFromFileUrisPropertyInfo = (~) Bool type AttrBaseTypeConstraint WebSettingsEnableUniversalAccessFromFileUrisPropertyInfo = WebSettingsK type AttrGetType WebSettingsEnableUniversalAccessFromFileUrisPropertyInfo = Bool type AttrLabel WebSettingsEnableUniversalAccessFromFileUrisPropertyInfo = "WebSettings::enable-universal-access-from-file-uris" attrGet _ = getWebSettingsEnableUniversalAccessFromFileUris attrSet _ = setWebSettingsEnableUniversalAccessFromFileUris attrConstruct _ = constructWebSettingsEnableUniversalAccessFromFileUris -- VVV Prop "enable-webaudio" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebSettingsEnableWebaudio :: (MonadIO m, WebSettingsK o) => o -> m Bool getWebSettingsEnableWebaudio obj = liftIO $ getObjectPropertyBool obj "enable-webaudio" setWebSettingsEnableWebaudio :: (MonadIO m, WebSettingsK o) => o -> Bool -> m () setWebSettingsEnableWebaudio obj val = liftIO $ setObjectPropertyBool obj "enable-webaudio" val constructWebSettingsEnableWebaudio :: Bool -> IO ([Char], GValue) constructWebSettingsEnableWebaudio val = constructObjectPropertyBool "enable-webaudio" val data WebSettingsEnableWebaudioPropertyInfo instance AttrInfo WebSettingsEnableWebaudioPropertyInfo where type AttrAllowedOps WebSettingsEnableWebaudioPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebSettingsEnableWebaudioPropertyInfo = (~) Bool type AttrBaseTypeConstraint WebSettingsEnableWebaudioPropertyInfo = WebSettingsK type AttrGetType WebSettingsEnableWebaudioPropertyInfo = Bool type AttrLabel WebSettingsEnableWebaudioPropertyInfo = "WebSettings::enable-webaudio" attrGet _ = getWebSettingsEnableWebaudio attrSet _ = setWebSettingsEnableWebaudio attrConstruct _ = constructWebSettingsEnableWebaudio -- VVV Prop "enable-webgl" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebSettingsEnableWebgl :: (MonadIO m, WebSettingsK o) => o -> m Bool getWebSettingsEnableWebgl obj = liftIO $ getObjectPropertyBool obj "enable-webgl" setWebSettingsEnableWebgl :: (MonadIO m, WebSettingsK o) => o -> Bool -> m () setWebSettingsEnableWebgl obj val = liftIO $ setObjectPropertyBool obj "enable-webgl" val constructWebSettingsEnableWebgl :: Bool -> IO ([Char], GValue) constructWebSettingsEnableWebgl val = constructObjectPropertyBool "enable-webgl" val data WebSettingsEnableWebglPropertyInfo instance AttrInfo WebSettingsEnableWebglPropertyInfo where type AttrAllowedOps WebSettingsEnableWebglPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebSettingsEnableWebglPropertyInfo = (~) Bool type AttrBaseTypeConstraint WebSettingsEnableWebglPropertyInfo = WebSettingsK type AttrGetType WebSettingsEnableWebglPropertyInfo = Bool type AttrLabel WebSettingsEnableWebglPropertyInfo = "WebSettings::enable-webgl" attrGet _ = getWebSettingsEnableWebgl attrSet _ = setWebSettingsEnableWebgl attrConstruct _ = constructWebSettingsEnableWebgl -- VVV Prop "enable-xss-auditor" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebSettingsEnableXssAuditor :: (MonadIO m, WebSettingsK o) => o -> m Bool getWebSettingsEnableXssAuditor obj = liftIO $ getObjectPropertyBool obj "enable-xss-auditor" setWebSettingsEnableXssAuditor :: (MonadIO m, WebSettingsK o) => o -> Bool -> m () setWebSettingsEnableXssAuditor obj val = liftIO $ setObjectPropertyBool obj "enable-xss-auditor" val constructWebSettingsEnableXssAuditor :: Bool -> IO ([Char], GValue) constructWebSettingsEnableXssAuditor val = constructObjectPropertyBool "enable-xss-auditor" val data WebSettingsEnableXssAuditorPropertyInfo instance AttrInfo WebSettingsEnableXssAuditorPropertyInfo where type AttrAllowedOps WebSettingsEnableXssAuditorPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebSettingsEnableXssAuditorPropertyInfo = (~) Bool type AttrBaseTypeConstraint WebSettingsEnableXssAuditorPropertyInfo = WebSettingsK type AttrGetType WebSettingsEnableXssAuditorPropertyInfo = Bool type AttrLabel WebSettingsEnableXssAuditorPropertyInfo = "WebSettings::enable-xss-auditor" attrGet _ = getWebSettingsEnableXssAuditor attrSet _ = setWebSettingsEnableXssAuditor attrConstruct _ = constructWebSettingsEnableXssAuditor -- VVV Prop "enforce-96-dpi" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebSettingsEnforce96Dpi :: (MonadIO m, WebSettingsK o) => o -> m Bool getWebSettingsEnforce96Dpi obj = liftIO $ getObjectPropertyBool obj "enforce-96-dpi" setWebSettingsEnforce96Dpi :: (MonadIO m, WebSettingsK o) => o -> Bool -> m () setWebSettingsEnforce96Dpi obj val = liftIO $ setObjectPropertyBool obj "enforce-96-dpi" val constructWebSettingsEnforce96Dpi :: Bool -> IO ([Char], GValue) constructWebSettingsEnforce96Dpi val = constructObjectPropertyBool "enforce-96-dpi" val data WebSettingsEnforce96DpiPropertyInfo instance AttrInfo WebSettingsEnforce96DpiPropertyInfo where type AttrAllowedOps WebSettingsEnforce96DpiPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebSettingsEnforce96DpiPropertyInfo = (~) Bool type AttrBaseTypeConstraint WebSettingsEnforce96DpiPropertyInfo = WebSettingsK type AttrGetType WebSettingsEnforce96DpiPropertyInfo = Bool type AttrLabel WebSettingsEnforce96DpiPropertyInfo = "WebSettings::enforce-96-dpi" attrGet _ = getWebSettingsEnforce96Dpi attrSet _ = setWebSettingsEnforce96Dpi attrConstruct _ = constructWebSettingsEnforce96Dpi -- VVV Prop "fantasy-font-family" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebSettingsFantasyFontFamily :: (MonadIO m, WebSettingsK o) => o -> m T.Text getWebSettingsFantasyFontFamily obj = liftIO $ getObjectPropertyString obj "fantasy-font-family" setWebSettingsFantasyFontFamily :: (MonadIO m, WebSettingsK o) => o -> T.Text -> m () setWebSettingsFantasyFontFamily obj val = liftIO $ setObjectPropertyString obj "fantasy-font-family" val constructWebSettingsFantasyFontFamily :: T.Text -> IO ([Char], GValue) constructWebSettingsFantasyFontFamily val = constructObjectPropertyString "fantasy-font-family" val data WebSettingsFantasyFontFamilyPropertyInfo instance AttrInfo WebSettingsFantasyFontFamilyPropertyInfo where type AttrAllowedOps WebSettingsFantasyFontFamilyPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebSettingsFantasyFontFamilyPropertyInfo = (~) T.Text type AttrBaseTypeConstraint WebSettingsFantasyFontFamilyPropertyInfo = WebSettingsK type AttrGetType WebSettingsFantasyFontFamilyPropertyInfo = T.Text type AttrLabel WebSettingsFantasyFontFamilyPropertyInfo = "WebSettings::fantasy-font-family" attrGet _ = getWebSettingsFantasyFontFamily attrSet _ = setWebSettingsFantasyFontFamily attrConstruct _ = constructWebSettingsFantasyFontFamily -- VVV Prop "html5-local-storage-database-path" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebSettingsHtml5LocalStorageDatabasePath :: (MonadIO m, WebSettingsK o) => o -> m T.Text getWebSettingsHtml5LocalStorageDatabasePath obj = liftIO $ getObjectPropertyString obj "html5-local-storage-database-path" setWebSettingsHtml5LocalStorageDatabasePath :: (MonadIO m, WebSettingsK o) => o -> T.Text -> m () setWebSettingsHtml5LocalStorageDatabasePath obj val = liftIO $ setObjectPropertyString obj "html5-local-storage-database-path" val constructWebSettingsHtml5LocalStorageDatabasePath :: T.Text -> IO ([Char], GValue) constructWebSettingsHtml5LocalStorageDatabasePath val = constructObjectPropertyString "html5-local-storage-database-path" val data WebSettingsHtml5LocalStorageDatabasePathPropertyInfo instance AttrInfo WebSettingsHtml5LocalStorageDatabasePathPropertyInfo where type AttrAllowedOps WebSettingsHtml5LocalStorageDatabasePathPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebSettingsHtml5LocalStorageDatabasePathPropertyInfo = (~) T.Text type AttrBaseTypeConstraint WebSettingsHtml5LocalStorageDatabasePathPropertyInfo = WebSettingsK type AttrGetType WebSettingsHtml5LocalStorageDatabasePathPropertyInfo = T.Text type AttrLabel WebSettingsHtml5LocalStorageDatabasePathPropertyInfo = "WebSettings::html5-local-storage-database-path" attrGet _ = getWebSettingsHtml5LocalStorageDatabasePath attrSet _ = setWebSettingsHtml5LocalStorageDatabasePath attrConstruct _ = constructWebSettingsHtml5LocalStorageDatabasePath -- VVV Prop "javascript-can-access-clipboard" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebSettingsJavascriptCanAccessClipboard :: (MonadIO m, WebSettingsK o) => o -> m Bool getWebSettingsJavascriptCanAccessClipboard obj = liftIO $ getObjectPropertyBool obj "javascript-can-access-clipboard" setWebSettingsJavascriptCanAccessClipboard :: (MonadIO m, WebSettingsK o) => o -> Bool -> m () setWebSettingsJavascriptCanAccessClipboard obj val = liftIO $ setObjectPropertyBool obj "javascript-can-access-clipboard" val constructWebSettingsJavascriptCanAccessClipboard :: Bool -> IO ([Char], GValue) constructWebSettingsJavascriptCanAccessClipboard val = constructObjectPropertyBool "javascript-can-access-clipboard" val data WebSettingsJavascriptCanAccessClipboardPropertyInfo instance AttrInfo WebSettingsJavascriptCanAccessClipboardPropertyInfo where type AttrAllowedOps WebSettingsJavascriptCanAccessClipboardPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebSettingsJavascriptCanAccessClipboardPropertyInfo = (~) Bool type AttrBaseTypeConstraint WebSettingsJavascriptCanAccessClipboardPropertyInfo = WebSettingsK type AttrGetType WebSettingsJavascriptCanAccessClipboardPropertyInfo = Bool type AttrLabel WebSettingsJavascriptCanAccessClipboardPropertyInfo = "WebSettings::javascript-can-access-clipboard" attrGet _ = getWebSettingsJavascriptCanAccessClipboard attrSet _ = setWebSettingsJavascriptCanAccessClipboard attrConstruct _ = constructWebSettingsJavascriptCanAccessClipboard -- VVV Prop "javascript-can-open-windows-automatically" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebSettingsJavascriptCanOpenWindowsAutomatically :: (MonadIO m, WebSettingsK o) => o -> m Bool getWebSettingsJavascriptCanOpenWindowsAutomatically obj = liftIO $ getObjectPropertyBool obj "javascript-can-open-windows-automatically" setWebSettingsJavascriptCanOpenWindowsAutomatically :: (MonadIO m, WebSettingsK o) => o -> Bool -> m () setWebSettingsJavascriptCanOpenWindowsAutomatically obj val = liftIO $ setObjectPropertyBool obj "javascript-can-open-windows-automatically" val constructWebSettingsJavascriptCanOpenWindowsAutomatically :: Bool -> IO ([Char], GValue) constructWebSettingsJavascriptCanOpenWindowsAutomatically val = constructObjectPropertyBool "javascript-can-open-windows-automatically" val data WebSettingsJavascriptCanOpenWindowsAutomaticallyPropertyInfo instance AttrInfo WebSettingsJavascriptCanOpenWindowsAutomaticallyPropertyInfo where type AttrAllowedOps WebSettingsJavascriptCanOpenWindowsAutomaticallyPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebSettingsJavascriptCanOpenWindowsAutomaticallyPropertyInfo = (~) Bool type AttrBaseTypeConstraint WebSettingsJavascriptCanOpenWindowsAutomaticallyPropertyInfo = WebSettingsK type AttrGetType WebSettingsJavascriptCanOpenWindowsAutomaticallyPropertyInfo = Bool type AttrLabel WebSettingsJavascriptCanOpenWindowsAutomaticallyPropertyInfo = "WebSettings::javascript-can-open-windows-automatically" attrGet _ = getWebSettingsJavascriptCanOpenWindowsAutomatically attrSet _ = setWebSettingsJavascriptCanOpenWindowsAutomatically attrConstruct _ = constructWebSettingsJavascriptCanOpenWindowsAutomatically -- VVV Prop "media-playback-allows-inline" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebSettingsMediaPlaybackAllowsInline :: (MonadIO m, WebSettingsK o) => o -> m Bool getWebSettingsMediaPlaybackAllowsInline obj = liftIO $ getObjectPropertyBool obj "media-playback-allows-inline" setWebSettingsMediaPlaybackAllowsInline :: (MonadIO m, WebSettingsK o) => o -> Bool -> m () setWebSettingsMediaPlaybackAllowsInline obj val = liftIO $ setObjectPropertyBool obj "media-playback-allows-inline" val constructWebSettingsMediaPlaybackAllowsInline :: Bool -> IO ([Char], GValue) constructWebSettingsMediaPlaybackAllowsInline val = constructObjectPropertyBool "media-playback-allows-inline" val data WebSettingsMediaPlaybackAllowsInlinePropertyInfo instance AttrInfo WebSettingsMediaPlaybackAllowsInlinePropertyInfo where type AttrAllowedOps WebSettingsMediaPlaybackAllowsInlinePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebSettingsMediaPlaybackAllowsInlinePropertyInfo = (~) Bool type AttrBaseTypeConstraint WebSettingsMediaPlaybackAllowsInlinePropertyInfo = WebSettingsK type AttrGetType WebSettingsMediaPlaybackAllowsInlinePropertyInfo = Bool type AttrLabel WebSettingsMediaPlaybackAllowsInlinePropertyInfo = "WebSettings::media-playback-allows-inline" attrGet _ = getWebSettingsMediaPlaybackAllowsInline attrSet _ = setWebSettingsMediaPlaybackAllowsInline attrConstruct _ = constructWebSettingsMediaPlaybackAllowsInline -- VVV Prop "media-playback-requires-user-gesture" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebSettingsMediaPlaybackRequiresUserGesture :: (MonadIO m, WebSettingsK o) => o -> m Bool getWebSettingsMediaPlaybackRequiresUserGesture obj = liftIO $ getObjectPropertyBool obj "media-playback-requires-user-gesture" setWebSettingsMediaPlaybackRequiresUserGesture :: (MonadIO m, WebSettingsK o) => o -> Bool -> m () setWebSettingsMediaPlaybackRequiresUserGesture obj val = liftIO $ setObjectPropertyBool obj "media-playback-requires-user-gesture" val constructWebSettingsMediaPlaybackRequiresUserGesture :: Bool -> IO ([Char], GValue) constructWebSettingsMediaPlaybackRequiresUserGesture val = constructObjectPropertyBool "media-playback-requires-user-gesture" val data WebSettingsMediaPlaybackRequiresUserGesturePropertyInfo instance AttrInfo WebSettingsMediaPlaybackRequiresUserGesturePropertyInfo where type AttrAllowedOps WebSettingsMediaPlaybackRequiresUserGesturePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebSettingsMediaPlaybackRequiresUserGesturePropertyInfo = (~) Bool type AttrBaseTypeConstraint WebSettingsMediaPlaybackRequiresUserGesturePropertyInfo = WebSettingsK type AttrGetType WebSettingsMediaPlaybackRequiresUserGesturePropertyInfo = Bool type AttrLabel WebSettingsMediaPlaybackRequiresUserGesturePropertyInfo = "WebSettings::media-playback-requires-user-gesture" attrGet _ = getWebSettingsMediaPlaybackRequiresUserGesture attrSet _ = setWebSettingsMediaPlaybackRequiresUserGesture attrConstruct _ = constructWebSettingsMediaPlaybackRequiresUserGesture -- VVV Prop "minimum-font-size" -- Type: TBasicType TInt32 -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebSettingsMinimumFontSize :: (MonadIO m, WebSettingsK o) => o -> m Int32 getWebSettingsMinimumFontSize obj = liftIO $ getObjectPropertyCInt obj "minimum-font-size" setWebSettingsMinimumFontSize :: (MonadIO m, WebSettingsK o) => o -> Int32 -> m () setWebSettingsMinimumFontSize obj val = liftIO $ setObjectPropertyCInt obj "minimum-font-size" val constructWebSettingsMinimumFontSize :: Int32 -> IO ([Char], GValue) constructWebSettingsMinimumFontSize val = constructObjectPropertyCInt "minimum-font-size" val data WebSettingsMinimumFontSizePropertyInfo instance AttrInfo WebSettingsMinimumFontSizePropertyInfo where type AttrAllowedOps WebSettingsMinimumFontSizePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebSettingsMinimumFontSizePropertyInfo = (~) Int32 type AttrBaseTypeConstraint WebSettingsMinimumFontSizePropertyInfo = WebSettingsK type AttrGetType WebSettingsMinimumFontSizePropertyInfo = Int32 type AttrLabel WebSettingsMinimumFontSizePropertyInfo = "WebSettings::minimum-font-size" attrGet _ = getWebSettingsMinimumFontSize attrSet _ = setWebSettingsMinimumFontSize attrConstruct _ = constructWebSettingsMinimumFontSize -- VVV Prop "minimum-logical-font-size" -- Type: TBasicType TInt32 -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebSettingsMinimumLogicalFontSize :: (MonadIO m, WebSettingsK o) => o -> m Int32 getWebSettingsMinimumLogicalFontSize obj = liftIO $ getObjectPropertyCInt obj "minimum-logical-font-size" setWebSettingsMinimumLogicalFontSize :: (MonadIO m, WebSettingsK o) => o -> Int32 -> m () setWebSettingsMinimumLogicalFontSize obj val = liftIO $ setObjectPropertyCInt obj "minimum-logical-font-size" val constructWebSettingsMinimumLogicalFontSize :: Int32 -> IO ([Char], GValue) constructWebSettingsMinimumLogicalFontSize val = constructObjectPropertyCInt "minimum-logical-font-size" val data WebSettingsMinimumLogicalFontSizePropertyInfo instance AttrInfo WebSettingsMinimumLogicalFontSizePropertyInfo where type AttrAllowedOps WebSettingsMinimumLogicalFontSizePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebSettingsMinimumLogicalFontSizePropertyInfo = (~) Int32 type AttrBaseTypeConstraint WebSettingsMinimumLogicalFontSizePropertyInfo = WebSettingsK type AttrGetType WebSettingsMinimumLogicalFontSizePropertyInfo = Int32 type AttrLabel WebSettingsMinimumLogicalFontSizePropertyInfo = "WebSettings::minimum-logical-font-size" attrGet _ = getWebSettingsMinimumLogicalFontSize attrSet _ = setWebSettingsMinimumLogicalFontSize attrConstruct _ = constructWebSettingsMinimumLogicalFontSize -- VVV Prop "monospace-font-family" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebSettingsMonospaceFontFamily :: (MonadIO m, WebSettingsK o) => o -> m T.Text getWebSettingsMonospaceFontFamily obj = liftIO $ getObjectPropertyString obj "monospace-font-family" setWebSettingsMonospaceFontFamily :: (MonadIO m, WebSettingsK o) => o -> T.Text -> m () setWebSettingsMonospaceFontFamily obj val = liftIO $ setObjectPropertyString obj "monospace-font-family" val constructWebSettingsMonospaceFontFamily :: T.Text -> IO ([Char], GValue) constructWebSettingsMonospaceFontFamily val = constructObjectPropertyString "monospace-font-family" val data WebSettingsMonospaceFontFamilyPropertyInfo instance AttrInfo WebSettingsMonospaceFontFamilyPropertyInfo where type AttrAllowedOps WebSettingsMonospaceFontFamilyPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebSettingsMonospaceFontFamilyPropertyInfo = (~) T.Text type AttrBaseTypeConstraint WebSettingsMonospaceFontFamilyPropertyInfo = WebSettingsK type AttrGetType WebSettingsMonospaceFontFamilyPropertyInfo = T.Text type AttrLabel WebSettingsMonospaceFontFamilyPropertyInfo = "WebSettings::monospace-font-family" attrGet _ = getWebSettingsMonospaceFontFamily attrSet _ = setWebSettingsMonospaceFontFamily attrConstruct _ = constructWebSettingsMonospaceFontFamily -- VVV Prop "print-backgrounds" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebSettingsPrintBackgrounds :: (MonadIO m, WebSettingsK o) => o -> m Bool getWebSettingsPrintBackgrounds obj = liftIO $ getObjectPropertyBool obj "print-backgrounds" setWebSettingsPrintBackgrounds :: (MonadIO m, WebSettingsK o) => o -> Bool -> m () setWebSettingsPrintBackgrounds obj val = liftIO $ setObjectPropertyBool obj "print-backgrounds" val constructWebSettingsPrintBackgrounds :: Bool -> IO ([Char], GValue) constructWebSettingsPrintBackgrounds val = constructObjectPropertyBool "print-backgrounds" val data WebSettingsPrintBackgroundsPropertyInfo instance AttrInfo WebSettingsPrintBackgroundsPropertyInfo where type AttrAllowedOps WebSettingsPrintBackgroundsPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebSettingsPrintBackgroundsPropertyInfo = (~) Bool type AttrBaseTypeConstraint WebSettingsPrintBackgroundsPropertyInfo = WebSettingsK type AttrGetType WebSettingsPrintBackgroundsPropertyInfo = Bool type AttrLabel WebSettingsPrintBackgroundsPropertyInfo = "WebSettings::print-backgrounds" attrGet _ = getWebSettingsPrintBackgrounds attrSet _ = setWebSettingsPrintBackgrounds attrConstruct _ = constructWebSettingsPrintBackgrounds -- VVV Prop "resizable-text-areas" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebSettingsResizableTextAreas :: (MonadIO m, WebSettingsK o) => o -> m Bool getWebSettingsResizableTextAreas obj = liftIO $ getObjectPropertyBool obj "resizable-text-areas" setWebSettingsResizableTextAreas :: (MonadIO m, WebSettingsK o) => o -> Bool -> m () setWebSettingsResizableTextAreas obj val = liftIO $ setObjectPropertyBool obj "resizable-text-areas" val constructWebSettingsResizableTextAreas :: Bool -> IO ([Char], GValue) constructWebSettingsResizableTextAreas val = constructObjectPropertyBool "resizable-text-areas" val data WebSettingsResizableTextAreasPropertyInfo instance AttrInfo WebSettingsResizableTextAreasPropertyInfo where type AttrAllowedOps WebSettingsResizableTextAreasPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebSettingsResizableTextAreasPropertyInfo = (~) Bool type AttrBaseTypeConstraint WebSettingsResizableTextAreasPropertyInfo = WebSettingsK type AttrGetType WebSettingsResizableTextAreasPropertyInfo = Bool type AttrLabel WebSettingsResizableTextAreasPropertyInfo = "WebSettings::resizable-text-areas" attrGet _ = getWebSettingsResizableTextAreas attrSet _ = setWebSettingsResizableTextAreas attrConstruct _ = constructWebSettingsResizableTextAreas -- VVV Prop "respect-image-orientation" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebSettingsRespectImageOrientation :: (MonadIO m, WebSettingsK o) => o -> m Bool getWebSettingsRespectImageOrientation obj = liftIO $ getObjectPropertyBool obj "respect-image-orientation" setWebSettingsRespectImageOrientation :: (MonadIO m, WebSettingsK o) => o -> Bool -> m () setWebSettingsRespectImageOrientation obj val = liftIO $ setObjectPropertyBool obj "respect-image-orientation" val constructWebSettingsRespectImageOrientation :: Bool -> IO ([Char], GValue) constructWebSettingsRespectImageOrientation val = constructObjectPropertyBool "respect-image-orientation" val data WebSettingsRespectImageOrientationPropertyInfo instance AttrInfo WebSettingsRespectImageOrientationPropertyInfo where type AttrAllowedOps WebSettingsRespectImageOrientationPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebSettingsRespectImageOrientationPropertyInfo = (~) Bool type AttrBaseTypeConstraint WebSettingsRespectImageOrientationPropertyInfo = WebSettingsK type AttrGetType WebSettingsRespectImageOrientationPropertyInfo = Bool type AttrLabel WebSettingsRespectImageOrientationPropertyInfo = "WebSettings::respect-image-orientation" attrGet _ = getWebSettingsRespectImageOrientation attrSet _ = setWebSettingsRespectImageOrientation attrConstruct _ = constructWebSettingsRespectImageOrientation -- VVV Prop "sans-serif-font-family" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebSettingsSansSerifFontFamily :: (MonadIO m, WebSettingsK o) => o -> m T.Text getWebSettingsSansSerifFontFamily obj = liftIO $ getObjectPropertyString obj "sans-serif-font-family" setWebSettingsSansSerifFontFamily :: (MonadIO m, WebSettingsK o) => o -> T.Text -> m () setWebSettingsSansSerifFontFamily obj val = liftIO $ setObjectPropertyString obj "sans-serif-font-family" val constructWebSettingsSansSerifFontFamily :: T.Text -> IO ([Char], GValue) constructWebSettingsSansSerifFontFamily val = constructObjectPropertyString "sans-serif-font-family" val data WebSettingsSansSerifFontFamilyPropertyInfo instance AttrInfo WebSettingsSansSerifFontFamilyPropertyInfo where type AttrAllowedOps WebSettingsSansSerifFontFamilyPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebSettingsSansSerifFontFamilyPropertyInfo = (~) T.Text type AttrBaseTypeConstraint WebSettingsSansSerifFontFamilyPropertyInfo = WebSettingsK type AttrGetType WebSettingsSansSerifFontFamilyPropertyInfo = T.Text type AttrLabel WebSettingsSansSerifFontFamilyPropertyInfo = "WebSettings::sans-serif-font-family" attrGet _ = getWebSettingsSansSerifFontFamily attrSet _ = setWebSettingsSansSerifFontFamily attrConstruct _ = constructWebSettingsSansSerifFontFamily -- VVV Prop "serif-font-family" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebSettingsSerifFontFamily :: (MonadIO m, WebSettingsK o) => o -> m T.Text getWebSettingsSerifFontFamily obj = liftIO $ getObjectPropertyString obj "serif-font-family" setWebSettingsSerifFontFamily :: (MonadIO m, WebSettingsK o) => o -> T.Text -> m () setWebSettingsSerifFontFamily obj val = liftIO $ setObjectPropertyString obj "serif-font-family" val constructWebSettingsSerifFontFamily :: T.Text -> IO ([Char], GValue) constructWebSettingsSerifFontFamily val = constructObjectPropertyString "serif-font-family" val data WebSettingsSerifFontFamilyPropertyInfo instance AttrInfo WebSettingsSerifFontFamilyPropertyInfo where type AttrAllowedOps WebSettingsSerifFontFamilyPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebSettingsSerifFontFamilyPropertyInfo = (~) T.Text type AttrBaseTypeConstraint WebSettingsSerifFontFamilyPropertyInfo = WebSettingsK type AttrGetType WebSettingsSerifFontFamilyPropertyInfo = T.Text type AttrLabel WebSettingsSerifFontFamilyPropertyInfo = "WebSettings::serif-font-family" attrGet _ = getWebSettingsSerifFontFamily attrSet _ = setWebSettingsSerifFontFamily attrConstruct _ = constructWebSettingsSerifFontFamily -- VVV Prop "spell-checking-languages" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebSettingsSpellCheckingLanguages :: (MonadIO m, WebSettingsK o) => o -> m T.Text getWebSettingsSpellCheckingLanguages obj = liftIO $ getObjectPropertyString obj "spell-checking-languages" setWebSettingsSpellCheckingLanguages :: (MonadIO m, WebSettingsK o) => o -> T.Text -> m () setWebSettingsSpellCheckingLanguages obj val = liftIO $ setObjectPropertyString obj "spell-checking-languages" val constructWebSettingsSpellCheckingLanguages :: T.Text -> IO ([Char], GValue) constructWebSettingsSpellCheckingLanguages val = constructObjectPropertyString "spell-checking-languages" val data WebSettingsSpellCheckingLanguagesPropertyInfo instance AttrInfo WebSettingsSpellCheckingLanguagesPropertyInfo where type AttrAllowedOps WebSettingsSpellCheckingLanguagesPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebSettingsSpellCheckingLanguagesPropertyInfo = (~) T.Text type AttrBaseTypeConstraint WebSettingsSpellCheckingLanguagesPropertyInfo = WebSettingsK type AttrGetType WebSettingsSpellCheckingLanguagesPropertyInfo = T.Text type AttrLabel WebSettingsSpellCheckingLanguagesPropertyInfo = "WebSettings::spell-checking-languages" attrGet _ = getWebSettingsSpellCheckingLanguages attrSet _ = setWebSettingsSpellCheckingLanguages attrConstruct _ = constructWebSettingsSpellCheckingLanguages -- VVV Prop "tab-key-cycles-through-elements" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebSettingsTabKeyCyclesThroughElements :: (MonadIO m, WebSettingsK o) => o -> m Bool getWebSettingsTabKeyCyclesThroughElements obj = liftIO $ getObjectPropertyBool obj "tab-key-cycles-through-elements" setWebSettingsTabKeyCyclesThroughElements :: (MonadIO m, WebSettingsK o) => o -> Bool -> m () setWebSettingsTabKeyCyclesThroughElements obj val = liftIO $ setObjectPropertyBool obj "tab-key-cycles-through-elements" val constructWebSettingsTabKeyCyclesThroughElements :: Bool -> IO ([Char], GValue) constructWebSettingsTabKeyCyclesThroughElements val = constructObjectPropertyBool "tab-key-cycles-through-elements" val data WebSettingsTabKeyCyclesThroughElementsPropertyInfo instance AttrInfo WebSettingsTabKeyCyclesThroughElementsPropertyInfo where type AttrAllowedOps WebSettingsTabKeyCyclesThroughElementsPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebSettingsTabKeyCyclesThroughElementsPropertyInfo = (~) Bool type AttrBaseTypeConstraint WebSettingsTabKeyCyclesThroughElementsPropertyInfo = WebSettingsK type AttrGetType WebSettingsTabKeyCyclesThroughElementsPropertyInfo = Bool type AttrLabel WebSettingsTabKeyCyclesThroughElementsPropertyInfo = "WebSettings::tab-key-cycles-through-elements" attrGet _ = getWebSettingsTabKeyCyclesThroughElements attrSet _ = setWebSettingsTabKeyCyclesThroughElements attrConstruct _ = constructWebSettingsTabKeyCyclesThroughElements -- VVV Prop "user-agent" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebSettingsUserAgent :: (MonadIO m, WebSettingsK o) => o -> m T.Text getWebSettingsUserAgent obj = liftIO $ getObjectPropertyString obj "user-agent" setWebSettingsUserAgent :: (MonadIO m, WebSettingsK o) => o -> T.Text -> m () setWebSettingsUserAgent obj val = liftIO $ setObjectPropertyString obj "user-agent" val constructWebSettingsUserAgent :: T.Text -> IO ([Char], GValue) constructWebSettingsUserAgent val = constructObjectPropertyString "user-agent" val data WebSettingsUserAgentPropertyInfo instance AttrInfo WebSettingsUserAgentPropertyInfo where type AttrAllowedOps WebSettingsUserAgentPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebSettingsUserAgentPropertyInfo = (~) T.Text type AttrBaseTypeConstraint WebSettingsUserAgentPropertyInfo = WebSettingsK type AttrGetType WebSettingsUserAgentPropertyInfo = T.Text type AttrLabel WebSettingsUserAgentPropertyInfo = "WebSettings::user-agent" attrGet _ = getWebSettingsUserAgent attrSet _ = setWebSettingsUserAgent attrConstruct _ = constructWebSettingsUserAgent -- VVV Prop "user-stylesheet-uri" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebSettingsUserStylesheetUri :: (MonadIO m, WebSettingsK o) => o -> m T.Text getWebSettingsUserStylesheetUri obj = liftIO $ getObjectPropertyString obj "user-stylesheet-uri" setWebSettingsUserStylesheetUri :: (MonadIO m, WebSettingsK o) => o -> T.Text -> m () setWebSettingsUserStylesheetUri obj val = liftIO $ setObjectPropertyString obj "user-stylesheet-uri" val constructWebSettingsUserStylesheetUri :: T.Text -> IO ([Char], GValue) constructWebSettingsUserStylesheetUri val = constructObjectPropertyString "user-stylesheet-uri" val data WebSettingsUserStylesheetUriPropertyInfo instance AttrInfo WebSettingsUserStylesheetUriPropertyInfo where type AttrAllowedOps WebSettingsUserStylesheetUriPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebSettingsUserStylesheetUriPropertyInfo = (~) T.Text type AttrBaseTypeConstraint WebSettingsUserStylesheetUriPropertyInfo = WebSettingsK type AttrGetType WebSettingsUserStylesheetUriPropertyInfo = T.Text type AttrLabel WebSettingsUserStylesheetUriPropertyInfo = "WebSettings::user-stylesheet-uri" attrGet _ = getWebSettingsUserStylesheetUri attrSet _ = setWebSettingsUserStylesheetUri attrConstruct _ = constructWebSettingsUserStylesheetUri -- VVV Prop "zoom-step" -- Type: TBasicType TFloat -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebSettingsZoomStep :: (MonadIO m, WebSettingsK o) => o -> m Float getWebSettingsZoomStep obj = liftIO $ getObjectPropertyFloat obj "zoom-step" setWebSettingsZoomStep :: (MonadIO m, WebSettingsK o) => o -> Float -> m () setWebSettingsZoomStep obj val = liftIO $ setObjectPropertyFloat obj "zoom-step" val constructWebSettingsZoomStep :: Float -> IO ([Char], GValue) constructWebSettingsZoomStep val = constructObjectPropertyFloat "zoom-step" val data WebSettingsZoomStepPropertyInfo instance AttrInfo WebSettingsZoomStepPropertyInfo where type AttrAllowedOps WebSettingsZoomStepPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebSettingsZoomStepPropertyInfo = (~) Float type AttrBaseTypeConstraint WebSettingsZoomStepPropertyInfo = WebSettingsK type AttrGetType WebSettingsZoomStepPropertyInfo = Float type AttrLabel WebSettingsZoomStepPropertyInfo = "WebSettings::zoom-step" attrGet _ = getWebSettingsZoomStep attrSet _ = setWebSettingsZoomStep attrConstruct _ = constructWebSettingsZoomStep type instance AttributeList WebSettings = '[ '("auto-load-images", WebSettingsAutoLoadImagesPropertyInfo), '("auto-resize-window", WebSettingsAutoResizeWindowPropertyInfo), '("auto-shrink-images", WebSettingsAutoShrinkImagesPropertyInfo), '("cursive-font-family", WebSettingsCursiveFontFamilyPropertyInfo), '("default-encoding", WebSettingsDefaultEncodingPropertyInfo), '("default-font-family", WebSettingsDefaultFontFamilyPropertyInfo), '("default-font-size", WebSettingsDefaultFontSizePropertyInfo), '("default-monospace-font-size", WebSettingsDefaultMonospaceFontSizePropertyInfo), '("editing-behavior", WebSettingsEditingBehaviorPropertyInfo), '("enable-accelerated-compositing", WebSettingsEnableAcceleratedCompositingPropertyInfo), '("enable-caret-browsing", WebSettingsEnableCaretBrowsingPropertyInfo), '("enable-default-context-menu", WebSettingsEnableDefaultContextMenuPropertyInfo), '("enable-developer-extras", WebSettingsEnableDeveloperExtrasPropertyInfo), '("enable-display-of-insecure-content", WebSettingsEnableDisplayOfInsecureContentPropertyInfo), '("enable-dns-prefetching", WebSettingsEnableDnsPrefetchingPropertyInfo), '("enable-dom-paste", WebSettingsEnableDomPastePropertyInfo), '("enable-file-access-from-file-uris", WebSettingsEnableFileAccessFromFileUrisPropertyInfo), '("enable-frame-flattening", WebSettingsEnableFrameFlatteningPropertyInfo), '("enable-fullscreen", WebSettingsEnableFullscreenPropertyInfo), '("enable-html5-database", WebSettingsEnableHtml5DatabasePropertyInfo), '("enable-html5-local-storage", WebSettingsEnableHtml5LocalStoragePropertyInfo), '("enable-hyperlink-auditing", WebSettingsEnableHyperlinkAuditingPropertyInfo), '("enable-java-applet", WebSettingsEnableJavaAppletPropertyInfo), '("enable-media-stream", WebSettingsEnableMediaStreamPropertyInfo), '("enable-mediasource", WebSettingsEnableMediasourcePropertyInfo), '("enable-offline-web-application-cache", WebSettingsEnableOfflineWebApplicationCachePropertyInfo), '("enable-page-cache", WebSettingsEnablePageCachePropertyInfo), '("enable-plugins", WebSettingsEnablePluginsPropertyInfo), '("enable-private-browsing", WebSettingsEnablePrivateBrowsingPropertyInfo), '("enable-running-of-insecure-content", WebSettingsEnableRunningOfInsecureContentPropertyInfo), '("enable-scripts", WebSettingsEnableScriptsPropertyInfo), '("enable-site-specific-quirks", WebSettingsEnableSiteSpecificQuirksPropertyInfo), '("enable-smooth-scrolling", WebSettingsEnableSmoothScrollingPropertyInfo), '("enable-spatial-navigation", WebSettingsEnableSpatialNavigationPropertyInfo), '("enable-spell-checking", WebSettingsEnableSpellCheckingPropertyInfo), '("enable-universal-access-from-file-uris", WebSettingsEnableUniversalAccessFromFileUrisPropertyInfo), '("enable-webaudio", WebSettingsEnableWebaudioPropertyInfo), '("enable-webgl", WebSettingsEnableWebglPropertyInfo), '("enable-xss-auditor", WebSettingsEnableXssAuditorPropertyInfo), '("enforce-96-dpi", WebSettingsEnforce96DpiPropertyInfo), '("fantasy-font-family", WebSettingsFantasyFontFamilyPropertyInfo), '("html5-local-storage-database-path", WebSettingsHtml5LocalStorageDatabasePathPropertyInfo), '("javascript-can-access-clipboard", WebSettingsJavascriptCanAccessClipboardPropertyInfo), '("javascript-can-open-windows-automatically", WebSettingsJavascriptCanOpenWindowsAutomaticallyPropertyInfo), '("media-playback-allows-inline", WebSettingsMediaPlaybackAllowsInlinePropertyInfo), '("media-playback-requires-user-gesture", WebSettingsMediaPlaybackRequiresUserGesturePropertyInfo), '("minimum-font-size", WebSettingsMinimumFontSizePropertyInfo), '("minimum-logical-font-size", WebSettingsMinimumLogicalFontSizePropertyInfo), '("monospace-font-family", WebSettingsMonospaceFontFamilyPropertyInfo), '("print-backgrounds", WebSettingsPrintBackgroundsPropertyInfo), '("resizable-text-areas", WebSettingsResizableTextAreasPropertyInfo), '("respect-image-orientation", WebSettingsRespectImageOrientationPropertyInfo), '("sans-serif-font-family", WebSettingsSansSerifFontFamilyPropertyInfo), '("serif-font-family", WebSettingsSerifFontFamilyPropertyInfo), '("spell-checking-languages", WebSettingsSpellCheckingLanguagesPropertyInfo), '("tab-key-cycles-through-elements", WebSettingsTabKeyCyclesThroughElementsPropertyInfo), '("user-agent", WebSettingsUserAgentPropertyInfo), '("user-stylesheet-uri", WebSettingsUserStylesheetUriPropertyInfo), '("zoom-step", WebSettingsZoomStepPropertyInfo)] -- VVV Prop "copy-target-list" -- Type: TInterface "Gtk" "TargetList" -- Flags: [PropertyReadable] getWebViewCopyTargetList :: (MonadIO m, WebViewK o) => o -> m Gtk.TargetList getWebViewCopyTargetList obj = liftIO $ getObjectPropertyBoxed obj "copy-target-list" Gtk.TargetList data WebViewCopyTargetListPropertyInfo instance AttrInfo WebViewCopyTargetListPropertyInfo where type AttrAllowedOps WebViewCopyTargetListPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint WebViewCopyTargetListPropertyInfo = (~) () type AttrBaseTypeConstraint WebViewCopyTargetListPropertyInfo = WebViewK type AttrGetType WebViewCopyTargetListPropertyInfo = Gtk.TargetList type AttrLabel WebViewCopyTargetListPropertyInfo = "WebView::copy-target-list" attrGet _ = getWebViewCopyTargetList attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "custom-encoding" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getWebViewCustomEncoding :: (MonadIO m, WebViewK o) => o -> m T.Text getWebViewCustomEncoding obj = liftIO $ getObjectPropertyString obj "custom-encoding" setWebViewCustomEncoding :: (MonadIO m, WebViewK o) => o -> T.Text -> m () setWebViewCustomEncoding obj val = liftIO $ setObjectPropertyString obj "custom-encoding" val constructWebViewCustomEncoding :: T.Text -> IO ([Char], GValue) constructWebViewCustomEncoding val = constructObjectPropertyString "custom-encoding" val data WebViewCustomEncodingPropertyInfo instance AttrInfo WebViewCustomEncodingPropertyInfo where type AttrAllowedOps WebViewCustomEncodingPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebViewCustomEncodingPropertyInfo = (~) T.Text type AttrBaseTypeConstraint WebViewCustomEncodingPropertyInfo = WebViewK type AttrGetType WebViewCustomEncodingPropertyInfo = T.Text type AttrLabel WebViewCustomEncodingPropertyInfo = "WebView::custom-encoding" attrGet _ = getWebViewCustomEncoding attrSet _ = setWebViewCustomEncoding attrConstruct _ = constructWebViewCustomEncoding -- VVV Prop "editable" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getWebViewEditable :: (MonadIO m, WebViewK o) => o -> m Bool getWebViewEditable obj = liftIO $ getObjectPropertyBool obj "editable" setWebViewEditable :: (MonadIO m, WebViewK o) => o -> Bool -> m () setWebViewEditable obj val = liftIO $ setObjectPropertyBool obj "editable" val constructWebViewEditable :: Bool -> IO ([Char], GValue) constructWebViewEditable val = constructObjectPropertyBool "editable" val data WebViewEditablePropertyInfo instance AttrInfo WebViewEditablePropertyInfo where type AttrAllowedOps WebViewEditablePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebViewEditablePropertyInfo = (~) Bool type AttrBaseTypeConstraint WebViewEditablePropertyInfo = WebViewK type AttrGetType WebViewEditablePropertyInfo = Bool type AttrLabel WebViewEditablePropertyInfo = "WebView::editable" attrGet _ = getWebViewEditable attrSet _ = setWebViewEditable attrConstruct _ = constructWebViewEditable -- VVV Prop "encoding" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getWebViewEncoding :: (MonadIO m, WebViewK o) => o -> m T.Text getWebViewEncoding obj = liftIO $ getObjectPropertyString obj "encoding" data WebViewEncodingPropertyInfo instance AttrInfo WebViewEncodingPropertyInfo where type AttrAllowedOps WebViewEncodingPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint WebViewEncodingPropertyInfo = (~) () type AttrBaseTypeConstraint WebViewEncodingPropertyInfo = WebViewK type AttrGetType WebViewEncodingPropertyInfo = T.Text type AttrLabel WebViewEncodingPropertyInfo = "WebView::encoding" attrGet _ = getWebViewEncoding attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "full-content-zoom" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getWebViewFullContentZoom :: (MonadIO m, WebViewK o) => o -> m Bool getWebViewFullContentZoom obj = liftIO $ getObjectPropertyBool obj "full-content-zoom" setWebViewFullContentZoom :: (MonadIO m, WebViewK o) => o -> Bool -> m () setWebViewFullContentZoom obj val = liftIO $ setObjectPropertyBool obj "full-content-zoom" val constructWebViewFullContentZoom :: Bool -> IO ([Char], GValue) constructWebViewFullContentZoom val = constructObjectPropertyBool "full-content-zoom" val data WebViewFullContentZoomPropertyInfo instance AttrInfo WebViewFullContentZoomPropertyInfo where type AttrAllowedOps WebViewFullContentZoomPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebViewFullContentZoomPropertyInfo = (~) Bool type AttrBaseTypeConstraint WebViewFullContentZoomPropertyInfo = WebViewK type AttrGetType WebViewFullContentZoomPropertyInfo = Bool type AttrLabel WebViewFullContentZoomPropertyInfo = "WebView::full-content-zoom" attrGet _ = getWebViewFullContentZoom attrSet _ = setWebViewFullContentZoom attrConstruct _ = constructWebViewFullContentZoom -- VVV Prop "icon-uri" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getWebViewIconUri :: (MonadIO m, WebViewK o) => o -> m T.Text getWebViewIconUri obj = liftIO $ getObjectPropertyString obj "icon-uri" data WebViewIconUriPropertyInfo instance AttrInfo WebViewIconUriPropertyInfo where type AttrAllowedOps WebViewIconUriPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint WebViewIconUriPropertyInfo = (~) () type AttrBaseTypeConstraint WebViewIconUriPropertyInfo = WebViewK type AttrGetType WebViewIconUriPropertyInfo = T.Text type AttrLabel WebViewIconUriPropertyInfo = "WebView::icon-uri" attrGet _ = getWebViewIconUri attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "im-context" -- Type: TInterface "Gtk" "IMContext" -- Flags: [PropertyReadable] getWebViewImContext :: (MonadIO m, WebViewK o) => o -> m Gtk.IMContext getWebViewImContext obj = liftIO $ getObjectPropertyObject obj "im-context" Gtk.IMContext data WebViewImContextPropertyInfo instance AttrInfo WebViewImContextPropertyInfo where type AttrAllowedOps WebViewImContextPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint WebViewImContextPropertyInfo = (~) () type AttrBaseTypeConstraint WebViewImContextPropertyInfo = WebViewK type AttrGetType WebViewImContextPropertyInfo = Gtk.IMContext type AttrLabel WebViewImContextPropertyInfo = "WebView::im-context" attrGet _ = getWebViewImContext attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "load-status" -- Type: TInterface "WebKit" "LoadStatus" -- Flags: [PropertyReadable] getWebViewLoadStatus :: (MonadIO m, WebViewK o) => o -> m LoadStatus getWebViewLoadStatus obj = liftIO $ getObjectPropertyEnum obj "load-status" data WebViewLoadStatusPropertyInfo instance AttrInfo WebViewLoadStatusPropertyInfo where type AttrAllowedOps WebViewLoadStatusPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint WebViewLoadStatusPropertyInfo = (~) () type AttrBaseTypeConstraint WebViewLoadStatusPropertyInfo = WebViewK type AttrGetType WebViewLoadStatusPropertyInfo = LoadStatus type AttrLabel WebViewLoadStatusPropertyInfo = "WebView::load-status" attrGet _ = getWebViewLoadStatus attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "paste-target-list" -- Type: TInterface "Gtk" "TargetList" -- Flags: [PropertyReadable] getWebViewPasteTargetList :: (MonadIO m, WebViewK o) => o -> m Gtk.TargetList getWebViewPasteTargetList obj = liftIO $ getObjectPropertyBoxed obj "paste-target-list" Gtk.TargetList data WebViewPasteTargetListPropertyInfo instance AttrInfo WebViewPasteTargetListPropertyInfo where type AttrAllowedOps WebViewPasteTargetListPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint WebViewPasteTargetListPropertyInfo = (~) () type AttrBaseTypeConstraint WebViewPasteTargetListPropertyInfo = WebViewK type AttrGetType WebViewPasteTargetListPropertyInfo = Gtk.TargetList type AttrLabel WebViewPasteTargetListPropertyInfo = "WebView::paste-target-list" attrGet _ = getWebViewPasteTargetList attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "progress" -- Type: TBasicType TDouble -- Flags: [PropertyReadable] getWebViewProgress :: (MonadIO m, WebViewK o) => o -> m Double getWebViewProgress obj = liftIO $ getObjectPropertyDouble obj "progress" data WebViewProgressPropertyInfo instance AttrInfo WebViewProgressPropertyInfo where type AttrAllowedOps WebViewProgressPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint WebViewProgressPropertyInfo = (~) () type AttrBaseTypeConstraint WebViewProgressPropertyInfo = WebViewK type AttrGetType WebViewProgressPropertyInfo = Double type AttrLabel WebViewProgressPropertyInfo = "WebView::progress" attrGet _ = getWebViewProgress attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "self-scrolling" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly] getWebViewSelfScrolling :: (MonadIO m, WebViewK o) => o -> m Bool getWebViewSelfScrolling obj = liftIO $ getObjectPropertyBool obj "self-scrolling" constructWebViewSelfScrolling :: Bool -> IO ([Char], GValue) constructWebViewSelfScrolling val = constructObjectPropertyBool "self-scrolling" val data WebViewSelfScrollingPropertyInfo instance AttrInfo WebViewSelfScrollingPropertyInfo where type AttrAllowedOps WebViewSelfScrollingPropertyInfo = '[ 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebViewSelfScrollingPropertyInfo = (~) Bool type AttrBaseTypeConstraint WebViewSelfScrollingPropertyInfo = WebViewK type AttrGetType WebViewSelfScrollingPropertyInfo = Bool type AttrLabel WebViewSelfScrollingPropertyInfo = "WebView::self-scrolling" attrGet _ = getWebViewSelfScrolling attrSet _ = undefined attrConstruct _ = constructWebViewSelfScrolling -- VVV Prop "settings" -- Type: TInterface "WebKit" "WebSettings" -- Flags: [PropertyReadable,PropertyWritable] getWebViewSettings :: (MonadIO m, WebViewK o) => o -> m WebSettings getWebViewSettings obj = liftIO $ getObjectPropertyObject obj "settings" WebSettings setWebViewSettings :: (MonadIO m, WebViewK o, WebSettingsK a) => o -> a -> m () setWebViewSettings obj val = liftIO $ setObjectPropertyObject obj "settings" val constructWebViewSettings :: (WebSettingsK a) => a -> IO ([Char], GValue) constructWebViewSettings val = constructObjectPropertyObject "settings" val data WebViewSettingsPropertyInfo instance AttrInfo WebViewSettingsPropertyInfo where type AttrAllowedOps WebViewSettingsPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebViewSettingsPropertyInfo = WebSettingsK type AttrBaseTypeConstraint WebViewSettingsPropertyInfo = WebViewK type AttrGetType WebViewSettingsPropertyInfo = WebSettings type AttrLabel WebViewSettingsPropertyInfo = "WebView::settings" attrGet _ = getWebViewSettings attrSet _ = setWebViewSettings attrConstruct _ = constructWebViewSettings -- VVV Prop "title" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getWebViewTitle :: (MonadIO m, WebViewK o) => o -> m T.Text getWebViewTitle obj = liftIO $ getObjectPropertyString obj "title" data WebViewTitlePropertyInfo instance AttrInfo WebViewTitlePropertyInfo where type AttrAllowedOps WebViewTitlePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint WebViewTitlePropertyInfo = (~) () type AttrBaseTypeConstraint WebViewTitlePropertyInfo = WebViewK type AttrGetType WebViewTitlePropertyInfo = T.Text type AttrLabel WebViewTitlePropertyInfo = "WebView::title" attrGet _ = getWebViewTitle attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "transparent" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getWebViewTransparent :: (MonadIO m, WebViewK o) => o -> m Bool getWebViewTransparent obj = liftIO $ getObjectPropertyBool obj "transparent" setWebViewTransparent :: (MonadIO m, WebViewK o) => o -> Bool -> m () setWebViewTransparent obj val = liftIO $ setObjectPropertyBool obj "transparent" val constructWebViewTransparent :: Bool -> IO ([Char], GValue) constructWebViewTransparent val = constructObjectPropertyBool "transparent" val data WebViewTransparentPropertyInfo instance AttrInfo WebViewTransparentPropertyInfo where type AttrAllowedOps WebViewTransparentPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebViewTransparentPropertyInfo = (~) Bool type AttrBaseTypeConstraint WebViewTransparentPropertyInfo = WebViewK type AttrGetType WebViewTransparentPropertyInfo = Bool type AttrLabel WebViewTransparentPropertyInfo = "WebView::transparent" attrGet _ = getWebViewTransparent attrSet _ = setWebViewTransparent attrConstruct _ = constructWebViewTransparent -- VVV Prop "uri" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getWebViewUri :: (MonadIO m, WebViewK o) => o -> m T.Text getWebViewUri obj = liftIO $ getObjectPropertyString obj "uri" data WebViewUriPropertyInfo instance AttrInfo WebViewUriPropertyInfo where type AttrAllowedOps WebViewUriPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint WebViewUriPropertyInfo = (~) () type AttrBaseTypeConstraint WebViewUriPropertyInfo = WebViewK type AttrGetType WebViewUriPropertyInfo = T.Text type AttrLabel WebViewUriPropertyInfo = "WebView::uri" attrGet _ = getWebViewUri attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "view-mode" -- Type: TInterface "WebKit" "WebViewViewMode" -- Flags: [PropertyReadable,PropertyWritable] getWebViewViewMode :: (MonadIO m, WebViewK o) => o -> m WebViewViewMode getWebViewViewMode obj = liftIO $ getObjectPropertyEnum obj "view-mode" setWebViewViewMode :: (MonadIO m, WebViewK o) => o -> WebViewViewMode -> m () setWebViewViewMode obj val = liftIO $ setObjectPropertyEnum obj "view-mode" val constructWebViewViewMode :: WebViewViewMode -> IO ([Char], GValue) constructWebViewViewMode val = constructObjectPropertyEnum "view-mode" val data WebViewViewModePropertyInfo instance AttrInfo WebViewViewModePropertyInfo where type AttrAllowedOps WebViewViewModePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebViewViewModePropertyInfo = (~) WebViewViewMode type AttrBaseTypeConstraint WebViewViewModePropertyInfo = WebViewK type AttrGetType WebViewViewModePropertyInfo = WebViewViewMode type AttrLabel WebViewViewModePropertyInfo = "WebView::view-mode" attrGet _ = getWebViewViewMode attrSet _ = setWebViewViewMode attrConstruct _ = constructWebViewViewMode -- VVV Prop "viewport-attributes" -- Type: TInterface "WebKit" "ViewportAttributes" -- Flags: [PropertyReadable] getWebViewViewportAttributes :: (MonadIO m, WebViewK o) => o -> m ViewportAttributes getWebViewViewportAttributes obj = liftIO $ getObjectPropertyObject obj "viewport-attributes" ViewportAttributes data WebViewViewportAttributesPropertyInfo instance AttrInfo WebViewViewportAttributesPropertyInfo where type AttrAllowedOps WebViewViewportAttributesPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint WebViewViewportAttributesPropertyInfo = (~) () type AttrBaseTypeConstraint WebViewViewportAttributesPropertyInfo = WebViewK type AttrGetType WebViewViewportAttributesPropertyInfo = ViewportAttributes type AttrLabel WebViewViewportAttributesPropertyInfo = "WebView::viewport-attributes" attrGet _ = getWebViewViewportAttributes attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "web-inspector" -- Type: TInterface "WebKit" "WebInspector" -- Flags: [PropertyReadable] getWebViewWebInspector :: (MonadIO m, WebViewK o) => o -> m WebInspector getWebViewWebInspector obj = liftIO $ getObjectPropertyObject obj "web-inspector" WebInspector data WebViewWebInspectorPropertyInfo instance AttrInfo WebViewWebInspectorPropertyInfo where type AttrAllowedOps WebViewWebInspectorPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint WebViewWebInspectorPropertyInfo = (~) () type AttrBaseTypeConstraint WebViewWebInspectorPropertyInfo = WebViewK type AttrGetType WebViewWebInspectorPropertyInfo = WebInspector type AttrLabel WebViewWebInspectorPropertyInfo = "WebView::web-inspector" attrGet _ = getWebViewWebInspector attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "window-features" -- Type: TInterface "WebKit" "WebWindowFeatures" -- Flags: [PropertyReadable,PropertyWritable] getWebViewWindowFeatures :: (MonadIO m, WebViewK o) => o -> m WebWindowFeatures getWebViewWindowFeatures obj = liftIO $ getObjectPropertyObject obj "window-features" WebWindowFeatures setWebViewWindowFeatures :: (MonadIO m, WebViewK o, WebWindowFeaturesK a) => o -> a -> m () setWebViewWindowFeatures obj val = liftIO $ setObjectPropertyObject obj "window-features" val constructWebViewWindowFeatures :: (WebWindowFeaturesK a) => a -> IO ([Char], GValue) constructWebViewWindowFeatures val = constructObjectPropertyObject "window-features" val data WebViewWindowFeaturesPropertyInfo instance AttrInfo WebViewWindowFeaturesPropertyInfo where type AttrAllowedOps WebViewWindowFeaturesPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebViewWindowFeaturesPropertyInfo = WebWindowFeaturesK type AttrBaseTypeConstraint WebViewWindowFeaturesPropertyInfo = WebViewK type AttrGetType WebViewWindowFeaturesPropertyInfo = WebWindowFeatures type AttrLabel WebViewWindowFeaturesPropertyInfo = "WebView::window-features" attrGet _ = getWebViewWindowFeatures attrSet _ = setWebViewWindowFeatures attrConstruct _ = constructWebViewWindowFeatures -- VVV Prop "zoom-level" -- Type: TBasicType TFloat -- Flags: [PropertyReadable,PropertyWritable] getWebViewZoomLevel :: (MonadIO m, WebViewK o) => o -> m Float getWebViewZoomLevel obj = liftIO $ getObjectPropertyFloat obj "zoom-level" setWebViewZoomLevel :: (MonadIO m, WebViewK o) => o -> Float -> m () setWebViewZoomLevel obj val = liftIO $ setObjectPropertyFloat obj "zoom-level" val constructWebViewZoomLevel :: Float -> IO ([Char], GValue) constructWebViewZoomLevel val = constructObjectPropertyFloat "zoom-level" val data WebViewZoomLevelPropertyInfo instance AttrInfo WebViewZoomLevelPropertyInfo where type AttrAllowedOps WebViewZoomLevelPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebViewZoomLevelPropertyInfo = (~) Float type AttrBaseTypeConstraint WebViewZoomLevelPropertyInfo = WebViewK type AttrGetType WebViewZoomLevelPropertyInfo = Float type AttrLabel WebViewZoomLevelPropertyInfo = "WebView::zoom-level" attrGet _ = getWebViewZoomLevel attrSet _ = setWebViewZoomLevel attrConstruct _ = constructWebViewZoomLevel type instance AttributeList WebView = '[ '("app-paintable", GtkA.WidgetAppPaintablePropertyInfo), '("border-width", GtkA.ContainerBorderWidthPropertyInfo), '("can-default", GtkA.WidgetCanDefaultPropertyInfo), '("can-focus", GtkA.WidgetCanFocusPropertyInfo), '("child", GtkA.ContainerChildPropertyInfo), '("composite-child", GtkA.WidgetCompositeChildPropertyInfo), '("copy-target-list", WebViewCopyTargetListPropertyInfo), '("custom-encoding", WebViewCustomEncodingPropertyInfo), '("double-buffered", GtkA.WidgetDoubleBufferedPropertyInfo), '("editable", WebViewEditablePropertyInfo), '("encoding", WebViewEncodingPropertyInfo), '("events", GtkA.WidgetEventsPropertyInfo), '("expand", GtkA.WidgetExpandPropertyInfo), '("full-content-zoom", WebViewFullContentZoomPropertyInfo), '("hadjustment", GtkA.ScrollableHadjustmentPropertyInfo), '("halign", GtkA.WidgetHalignPropertyInfo), '("has-default", GtkA.WidgetHasDefaultPropertyInfo), '("has-focus", GtkA.WidgetHasFocusPropertyInfo), '("has-tooltip", GtkA.WidgetHasTooltipPropertyInfo), '("height-request", GtkA.WidgetHeightRequestPropertyInfo), '("hexpand", GtkA.WidgetHexpandPropertyInfo), '("hexpand-set", GtkA.WidgetHexpandSetPropertyInfo), '("hscroll-policy", GtkA.ScrollableHscrollPolicyPropertyInfo), '("icon-uri", WebViewIconUriPropertyInfo), '("im-context", WebViewImContextPropertyInfo), '("is-focus", GtkA.WidgetIsFocusPropertyInfo), '("load-status", WebViewLoadStatusPropertyInfo), '("margin", GtkA.WidgetMarginPropertyInfo), '("margin-bottom", GtkA.WidgetMarginBottomPropertyInfo), '("margin-end", GtkA.WidgetMarginEndPropertyInfo), '("margin-left", GtkA.WidgetMarginLeftPropertyInfo), '("margin-right", GtkA.WidgetMarginRightPropertyInfo), '("margin-start", GtkA.WidgetMarginStartPropertyInfo), '("margin-top", GtkA.WidgetMarginTopPropertyInfo), '("name", GtkA.WidgetNamePropertyInfo), '("no-show-all", GtkA.WidgetNoShowAllPropertyInfo), '("opacity", GtkA.WidgetOpacityPropertyInfo), '("parent", GtkA.WidgetParentPropertyInfo), '("paste-target-list", WebViewPasteTargetListPropertyInfo), '("progress", WebViewProgressPropertyInfo), '("receives-default", GtkA.WidgetReceivesDefaultPropertyInfo), '("resize-mode", GtkA.ContainerResizeModePropertyInfo), '("scale-factor", GtkA.WidgetScaleFactorPropertyInfo), '("self-scrolling", WebViewSelfScrollingPropertyInfo), '("sensitive", GtkA.WidgetSensitivePropertyInfo), '("settings", WebViewSettingsPropertyInfo), '("style", GtkA.WidgetStylePropertyInfo), '("title", WebViewTitlePropertyInfo), '("tooltip-markup", GtkA.WidgetTooltipMarkupPropertyInfo), '("tooltip-text", GtkA.WidgetTooltipTextPropertyInfo), '("transparent", WebViewTransparentPropertyInfo), '("uri", WebViewUriPropertyInfo), '("vadjustment", GtkA.ScrollableVadjustmentPropertyInfo), '("valign", GtkA.WidgetValignPropertyInfo), '("vexpand", GtkA.WidgetVexpandPropertyInfo), '("vexpand-set", GtkA.WidgetVexpandSetPropertyInfo), '("view-mode", WebViewViewModePropertyInfo), '("viewport-attributes", WebViewViewportAttributesPropertyInfo), '("visible", GtkA.WidgetVisiblePropertyInfo), '("vscroll-policy", GtkA.ScrollableVscrollPolicyPropertyInfo), '("web-inspector", WebViewWebInspectorPropertyInfo), '("width-request", GtkA.WidgetWidthRequestPropertyInfo), '("window", GtkA.WidgetWindowPropertyInfo), '("window-features", WebViewWindowFeaturesPropertyInfo), '("zoom-level", WebViewZoomLevelPropertyInfo)] -- VVV Prop "fullscreen" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebWindowFeaturesFullscreen :: (MonadIO m, WebWindowFeaturesK o) => o -> m Bool getWebWindowFeaturesFullscreen obj = liftIO $ getObjectPropertyBool obj "fullscreen" setWebWindowFeaturesFullscreen :: (MonadIO m, WebWindowFeaturesK o) => o -> Bool -> m () setWebWindowFeaturesFullscreen obj val = liftIO $ setObjectPropertyBool obj "fullscreen" val constructWebWindowFeaturesFullscreen :: Bool -> IO ([Char], GValue) constructWebWindowFeaturesFullscreen val = constructObjectPropertyBool "fullscreen" val data WebWindowFeaturesFullscreenPropertyInfo instance AttrInfo WebWindowFeaturesFullscreenPropertyInfo where type AttrAllowedOps WebWindowFeaturesFullscreenPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebWindowFeaturesFullscreenPropertyInfo = (~) Bool type AttrBaseTypeConstraint WebWindowFeaturesFullscreenPropertyInfo = WebWindowFeaturesK type AttrGetType WebWindowFeaturesFullscreenPropertyInfo = Bool type AttrLabel WebWindowFeaturesFullscreenPropertyInfo = "WebWindowFeatures::fullscreen" attrGet _ = getWebWindowFeaturesFullscreen attrSet _ = setWebWindowFeaturesFullscreen attrConstruct _ = constructWebWindowFeaturesFullscreen -- VVV Prop "height" -- Type: TBasicType TInt32 -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebWindowFeaturesHeight :: (MonadIO m, WebWindowFeaturesK o) => o -> m Int32 getWebWindowFeaturesHeight obj = liftIO $ getObjectPropertyCInt obj "height" setWebWindowFeaturesHeight :: (MonadIO m, WebWindowFeaturesK o) => o -> Int32 -> m () setWebWindowFeaturesHeight obj val = liftIO $ setObjectPropertyCInt obj "height" val constructWebWindowFeaturesHeight :: Int32 -> IO ([Char], GValue) constructWebWindowFeaturesHeight val = constructObjectPropertyCInt "height" val data WebWindowFeaturesHeightPropertyInfo instance AttrInfo WebWindowFeaturesHeightPropertyInfo where type AttrAllowedOps WebWindowFeaturesHeightPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebWindowFeaturesHeightPropertyInfo = (~) Int32 type AttrBaseTypeConstraint WebWindowFeaturesHeightPropertyInfo = WebWindowFeaturesK type AttrGetType WebWindowFeaturesHeightPropertyInfo = Int32 type AttrLabel WebWindowFeaturesHeightPropertyInfo = "WebWindowFeatures::height" attrGet _ = getWebWindowFeaturesHeight attrSet _ = setWebWindowFeaturesHeight attrConstruct _ = constructWebWindowFeaturesHeight -- VVV Prop "locationbar-visible" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebWindowFeaturesLocationbarVisible :: (MonadIO m, WebWindowFeaturesK o) => o -> m Bool getWebWindowFeaturesLocationbarVisible obj = liftIO $ getObjectPropertyBool obj "locationbar-visible" setWebWindowFeaturesLocationbarVisible :: (MonadIO m, WebWindowFeaturesK o) => o -> Bool -> m () setWebWindowFeaturesLocationbarVisible obj val = liftIO $ setObjectPropertyBool obj "locationbar-visible" val constructWebWindowFeaturesLocationbarVisible :: Bool -> IO ([Char], GValue) constructWebWindowFeaturesLocationbarVisible val = constructObjectPropertyBool "locationbar-visible" val data WebWindowFeaturesLocationbarVisiblePropertyInfo instance AttrInfo WebWindowFeaturesLocationbarVisiblePropertyInfo where type AttrAllowedOps WebWindowFeaturesLocationbarVisiblePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebWindowFeaturesLocationbarVisiblePropertyInfo = (~) Bool type AttrBaseTypeConstraint WebWindowFeaturesLocationbarVisiblePropertyInfo = WebWindowFeaturesK type AttrGetType WebWindowFeaturesLocationbarVisiblePropertyInfo = Bool type AttrLabel WebWindowFeaturesLocationbarVisiblePropertyInfo = "WebWindowFeatures::locationbar-visible" attrGet _ = getWebWindowFeaturesLocationbarVisible attrSet _ = setWebWindowFeaturesLocationbarVisible attrConstruct _ = constructWebWindowFeaturesLocationbarVisible -- VVV Prop "menubar-visible" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebWindowFeaturesMenubarVisible :: (MonadIO m, WebWindowFeaturesK o) => o -> m Bool getWebWindowFeaturesMenubarVisible obj = liftIO $ getObjectPropertyBool obj "menubar-visible" setWebWindowFeaturesMenubarVisible :: (MonadIO m, WebWindowFeaturesK o) => o -> Bool -> m () setWebWindowFeaturesMenubarVisible obj val = liftIO $ setObjectPropertyBool obj "menubar-visible" val constructWebWindowFeaturesMenubarVisible :: Bool -> IO ([Char], GValue) constructWebWindowFeaturesMenubarVisible val = constructObjectPropertyBool "menubar-visible" val data WebWindowFeaturesMenubarVisiblePropertyInfo instance AttrInfo WebWindowFeaturesMenubarVisiblePropertyInfo where type AttrAllowedOps WebWindowFeaturesMenubarVisiblePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebWindowFeaturesMenubarVisiblePropertyInfo = (~) Bool type AttrBaseTypeConstraint WebWindowFeaturesMenubarVisiblePropertyInfo = WebWindowFeaturesK type AttrGetType WebWindowFeaturesMenubarVisiblePropertyInfo = Bool type AttrLabel WebWindowFeaturesMenubarVisiblePropertyInfo = "WebWindowFeatures::menubar-visible" attrGet _ = getWebWindowFeaturesMenubarVisible attrSet _ = setWebWindowFeaturesMenubarVisible attrConstruct _ = constructWebWindowFeaturesMenubarVisible -- VVV Prop "scrollbar-visible" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebWindowFeaturesScrollbarVisible :: (MonadIO m, WebWindowFeaturesK o) => o -> m Bool getWebWindowFeaturesScrollbarVisible obj = liftIO $ getObjectPropertyBool obj "scrollbar-visible" setWebWindowFeaturesScrollbarVisible :: (MonadIO m, WebWindowFeaturesK o) => o -> Bool -> m () setWebWindowFeaturesScrollbarVisible obj val = liftIO $ setObjectPropertyBool obj "scrollbar-visible" val constructWebWindowFeaturesScrollbarVisible :: Bool -> IO ([Char], GValue) constructWebWindowFeaturesScrollbarVisible val = constructObjectPropertyBool "scrollbar-visible" val data WebWindowFeaturesScrollbarVisiblePropertyInfo instance AttrInfo WebWindowFeaturesScrollbarVisiblePropertyInfo where type AttrAllowedOps WebWindowFeaturesScrollbarVisiblePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebWindowFeaturesScrollbarVisiblePropertyInfo = (~) Bool type AttrBaseTypeConstraint WebWindowFeaturesScrollbarVisiblePropertyInfo = WebWindowFeaturesK type AttrGetType WebWindowFeaturesScrollbarVisiblePropertyInfo = Bool type AttrLabel WebWindowFeaturesScrollbarVisiblePropertyInfo = "WebWindowFeatures::scrollbar-visible" attrGet _ = getWebWindowFeaturesScrollbarVisible attrSet _ = setWebWindowFeaturesScrollbarVisible attrConstruct _ = constructWebWindowFeaturesScrollbarVisible -- VVV Prop "statusbar-visible" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebWindowFeaturesStatusbarVisible :: (MonadIO m, WebWindowFeaturesK o) => o -> m Bool getWebWindowFeaturesStatusbarVisible obj = liftIO $ getObjectPropertyBool obj "statusbar-visible" setWebWindowFeaturesStatusbarVisible :: (MonadIO m, WebWindowFeaturesK o) => o -> Bool -> m () setWebWindowFeaturesStatusbarVisible obj val = liftIO $ setObjectPropertyBool obj "statusbar-visible" val constructWebWindowFeaturesStatusbarVisible :: Bool -> IO ([Char], GValue) constructWebWindowFeaturesStatusbarVisible val = constructObjectPropertyBool "statusbar-visible" val data WebWindowFeaturesStatusbarVisiblePropertyInfo instance AttrInfo WebWindowFeaturesStatusbarVisiblePropertyInfo where type AttrAllowedOps WebWindowFeaturesStatusbarVisiblePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebWindowFeaturesStatusbarVisiblePropertyInfo = (~) Bool type AttrBaseTypeConstraint WebWindowFeaturesStatusbarVisiblePropertyInfo = WebWindowFeaturesK type AttrGetType WebWindowFeaturesStatusbarVisiblePropertyInfo = Bool type AttrLabel WebWindowFeaturesStatusbarVisiblePropertyInfo = "WebWindowFeatures::statusbar-visible" attrGet _ = getWebWindowFeaturesStatusbarVisible attrSet _ = setWebWindowFeaturesStatusbarVisible attrConstruct _ = constructWebWindowFeaturesStatusbarVisible -- VVV Prop "toolbar-visible" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebWindowFeaturesToolbarVisible :: (MonadIO m, WebWindowFeaturesK o) => o -> m Bool getWebWindowFeaturesToolbarVisible obj = liftIO $ getObjectPropertyBool obj "toolbar-visible" setWebWindowFeaturesToolbarVisible :: (MonadIO m, WebWindowFeaturesK o) => o -> Bool -> m () setWebWindowFeaturesToolbarVisible obj val = liftIO $ setObjectPropertyBool obj "toolbar-visible" val constructWebWindowFeaturesToolbarVisible :: Bool -> IO ([Char], GValue) constructWebWindowFeaturesToolbarVisible val = constructObjectPropertyBool "toolbar-visible" val data WebWindowFeaturesToolbarVisiblePropertyInfo instance AttrInfo WebWindowFeaturesToolbarVisiblePropertyInfo where type AttrAllowedOps WebWindowFeaturesToolbarVisiblePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebWindowFeaturesToolbarVisiblePropertyInfo = (~) Bool type AttrBaseTypeConstraint WebWindowFeaturesToolbarVisiblePropertyInfo = WebWindowFeaturesK type AttrGetType WebWindowFeaturesToolbarVisiblePropertyInfo = Bool type AttrLabel WebWindowFeaturesToolbarVisiblePropertyInfo = "WebWindowFeatures::toolbar-visible" attrGet _ = getWebWindowFeaturesToolbarVisible attrSet _ = setWebWindowFeaturesToolbarVisible attrConstruct _ = constructWebWindowFeaturesToolbarVisible -- VVV Prop "width" -- Type: TBasicType TInt32 -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebWindowFeaturesWidth :: (MonadIO m, WebWindowFeaturesK o) => o -> m Int32 getWebWindowFeaturesWidth obj = liftIO $ getObjectPropertyCInt obj "width" setWebWindowFeaturesWidth :: (MonadIO m, WebWindowFeaturesK o) => o -> Int32 -> m () setWebWindowFeaturesWidth obj val = liftIO $ setObjectPropertyCInt obj "width" val constructWebWindowFeaturesWidth :: Int32 -> IO ([Char], GValue) constructWebWindowFeaturesWidth val = constructObjectPropertyCInt "width" val data WebWindowFeaturesWidthPropertyInfo instance AttrInfo WebWindowFeaturesWidthPropertyInfo where type AttrAllowedOps WebWindowFeaturesWidthPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebWindowFeaturesWidthPropertyInfo = (~) Int32 type AttrBaseTypeConstraint WebWindowFeaturesWidthPropertyInfo = WebWindowFeaturesK type AttrGetType WebWindowFeaturesWidthPropertyInfo = Int32 type AttrLabel WebWindowFeaturesWidthPropertyInfo = "WebWindowFeatures::width" attrGet _ = getWebWindowFeaturesWidth attrSet _ = setWebWindowFeaturesWidth attrConstruct _ = constructWebWindowFeaturesWidth -- VVV Prop "x" -- Type: TBasicType TInt32 -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebWindowFeaturesX :: (MonadIO m, WebWindowFeaturesK o) => o -> m Int32 getWebWindowFeaturesX obj = liftIO $ getObjectPropertyCInt obj "x" setWebWindowFeaturesX :: (MonadIO m, WebWindowFeaturesK o) => o -> Int32 -> m () setWebWindowFeaturesX obj val = liftIO $ setObjectPropertyCInt obj "x" val constructWebWindowFeaturesX :: Int32 -> IO ([Char], GValue) constructWebWindowFeaturesX val = constructObjectPropertyCInt "x" val data WebWindowFeaturesXPropertyInfo instance AttrInfo WebWindowFeaturesXPropertyInfo where type AttrAllowedOps WebWindowFeaturesXPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebWindowFeaturesXPropertyInfo = (~) Int32 type AttrBaseTypeConstraint WebWindowFeaturesXPropertyInfo = WebWindowFeaturesK type AttrGetType WebWindowFeaturesXPropertyInfo = Int32 type AttrLabel WebWindowFeaturesXPropertyInfo = "WebWindowFeatures::x" attrGet _ = getWebWindowFeaturesX attrSet _ = setWebWindowFeaturesX attrConstruct _ = constructWebWindowFeaturesX -- VVV Prop "y" -- Type: TBasicType TInt32 -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getWebWindowFeaturesY :: (MonadIO m, WebWindowFeaturesK o) => o -> m Int32 getWebWindowFeaturesY obj = liftIO $ getObjectPropertyCInt obj "y" setWebWindowFeaturesY :: (MonadIO m, WebWindowFeaturesK o) => o -> Int32 -> m () setWebWindowFeaturesY obj val = liftIO $ setObjectPropertyCInt obj "y" val constructWebWindowFeaturesY :: Int32 -> IO ([Char], GValue) constructWebWindowFeaturesY val = constructObjectPropertyCInt "y" val data WebWindowFeaturesYPropertyInfo instance AttrInfo WebWindowFeaturesYPropertyInfo where type AttrAllowedOps WebWindowFeaturesYPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WebWindowFeaturesYPropertyInfo = (~) Int32 type AttrBaseTypeConstraint WebWindowFeaturesYPropertyInfo = WebWindowFeaturesK type AttrGetType WebWindowFeaturesYPropertyInfo = Int32 type AttrLabel WebWindowFeaturesYPropertyInfo = "WebWindowFeatures::y" attrGet _ = getWebWindowFeaturesY attrSet _ = setWebWindowFeaturesY attrConstruct _ = constructWebWindowFeaturesY type instance AttributeList WebWindowFeatures = '[ '("fullscreen", WebWindowFeaturesFullscreenPropertyInfo), '("height", WebWindowFeaturesHeightPropertyInfo), '("locationbar-visible", WebWindowFeaturesLocationbarVisiblePropertyInfo), '("menubar-visible", WebWindowFeaturesMenubarVisiblePropertyInfo), '("scrollbar-visible", WebWindowFeaturesScrollbarVisiblePropertyInfo), '("statusbar-visible", WebWindowFeaturesStatusbarVisiblePropertyInfo), '("toolbar-visible", WebWindowFeaturesToolbarVisiblePropertyInfo), '("width", WebWindowFeaturesWidthPropertyInfo), '("x", WebWindowFeaturesXPropertyInfo), '("y", WebWindowFeaturesYPropertyInfo)]