module GI.WebKit2WebExtension.Objects.DOMDocument
(
DOMDocument(..) ,
DOMDocumentK ,
toDOMDocument ,
noDOMDocument ,
dOMDocumentAdoptNode ,
dOMDocumentCreateAttribute ,
dOMDocumentCreateAttributeNs ,
dOMDocumentCreateCdataSection ,
dOMDocumentCreateComment ,
dOMDocumentCreateCssStyleDeclaration ,
dOMDocumentCreateDocumentFragment ,
dOMDocumentCreateElement ,
dOMDocumentCreateElementNs ,
dOMDocumentCreateEntityReference ,
dOMDocumentCreateEvent ,
dOMDocumentCreateExpression ,
dOMDocumentCreateNodeIterator ,
dOMDocumentCreateNsResolver ,
dOMDocumentCreateProcessingInstruction ,
dOMDocumentCreateRange ,
dOMDocumentCreateTextNode ,
dOMDocumentCreateTreeWalker ,
dOMDocumentElementFromPoint ,
dOMDocumentEvaluate ,
dOMDocumentExecCommand ,
dOMDocumentGetActiveElement ,
dOMDocumentGetAnchors ,
dOMDocumentGetApplets ,
dOMDocumentGetBody ,
dOMDocumentGetCharacterSet ,
dOMDocumentGetCharset ,
dOMDocumentGetCookie ,
dOMDocumentGetDefaultCharset ,
dOMDocumentGetDefaultView ,
dOMDocumentGetDoctype ,
dOMDocumentGetDocumentElement ,
dOMDocumentGetDocumentUri ,
dOMDocumentGetDomain ,
dOMDocumentGetElementById ,
dOMDocumentGetElementsByClassName ,
dOMDocumentGetElementsByName ,
dOMDocumentGetElementsByTagName ,
dOMDocumentGetElementsByTagNameNs ,
dOMDocumentGetForms ,
dOMDocumentGetHead ,
dOMDocumentGetImages ,
dOMDocumentGetImplementation ,
dOMDocumentGetInputEncoding ,
dOMDocumentGetLastModified ,
dOMDocumentGetLinks ,
dOMDocumentGetOverrideStyle ,
dOMDocumentGetPreferredStylesheetSet ,
dOMDocumentGetReadyState ,
dOMDocumentGetReferrer ,
dOMDocumentGetSelectedStylesheetSet ,
dOMDocumentGetStyleSheets ,
dOMDocumentGetTitle ,
dOMDocumentGetUrl ,
dOMDocumentGetXmlEncoding ,
dOMDocumentGetXmlStandalone ,
dOMDocumentGetXmlVersion ,
dOMDocumentHasFocus ,
dOMDocumentImportNode ,
dOMDocumentQueryCommandEnabled ,
dOMDocumentQueryCommandIndeterm ,
dOMDocumentQueryCommandState ,
dOMDocumentQueryCommandSupported ,
dOMDocumentQueryCommandValue ,
dOMDocumentQuerySelector ,
dOMDocumentQuerySelectorAll ,
dOMDocumentSetBody ,
dOMDocumentSetCharset ,
dOMDocumentSetCookie ,
dOMDocumentSetDocumentUri ,
dOMDocumentSetSelectedStylesheetSet ,
dOMDocumentSetTitle ,
dOMDocumentSetXmlStandalone ,
dOMDocumentSetXmlVersion ,
DOMDocumentActiveElementPropertyInfo ,
getDOMDocumentActiveElement ,
DOMDocumentAnchorsPropertyInfo ,
getDOMDocumentAnchors ,
DOMDocumentAppletsPropertyInfo ,
getDOMDocumentApplets ,
DOMDocumentBodyPropertyInfo ,
getDOMDocumentBody ,
DOMDocumentCharacterSetPropertyInfo ,
getDOMDocumentCharacterSet ,
DOMDocumentCharsetPropertyInfo ,
constructDOMDocumentCharset ,
getDOMDocumentCharset ,
setDOMDocumentCharset ,
DOMDocumentChildElementCountPropertyInfo,
getDOMDocumentChildElementCount ,
DOMDocumentChildrenPropertyInfo ,
getDOMDocumentChildren ,
DOMDocumentCompatModePropertyInfo ,
getDOMDocumentCompatMode ,
DOMDocumentContentTypePropertyInfo ,
getDOMDocumentContentType ,
DOMDocumentCookiePropertyInfo ,
constructDOMDocumentCookie ,
getDOMDocumentCookie ,
setDOMDocumentCookie ,
DOMDocumentCurrentScriptPropertyInfo ,
getDOMDocumentCurrentScript ,
DOMDocumentDefaultCharsetPropertyInfo ,
getDOMDocumentDefaultCharset ,
DOMDocumentDefaultViewPropertyInfo ,
getDOMDocumentDefaultView ,
DOMDocumentDoctypePropertyInfo ,
getDOMDocumentDoctype ,
DOMDocumentDocumentElementPropertyInfo ,
getDOMDocumentDocumentElement ,
DOMDocumentDocumentUriPropertyInfo ,
constructDOMDocumentDocumentUri ,
getDOMDocumentDocumentUri ,
setDOMDocumentDocumentUri ,
DOMDocumentDomainPropertyInfo ,
getDOMDocumentDomain ,
DOMDocumentFirstElementChildPropertyInfo,
getDOMDocumentFirstElementChild ,
DOMDocumentFormsPropertyInfo ,
getDOMDocumentForms ,
DOMDocumentHeadPropertyInfo ,
getDOMDocumentHead ,
DOMDocumentHiddenPropertyInfo ,
getDOMDocumentHidden ,
DOMDocumentImagesPropertyInfo ,
getDOMDocumentImages ,
DOMDocumentImplementationPropertyInfo ,
getDOMDocumentImplementation ,
DOMDocumentInputEncodingPropertyInfo ,
getDOMDocumentInputEncoding ,
DOMDocumentLastElementChildPropertyInfo ,
getDOMDocumentLastElementChild ,
DOMDocumentLastModifiedPropertyInfo ,
getDOMDocumentLastModified ,
DOMDocumentLinksPropertyInfo ,
getDOMDocumentLinks ,
DOMDocumentOriginPropertyInfo ,
getDOMDocumentOrigin ,
DOMDocumentPointerLockElementPropertyInfo,
getDOMDocumentPointerLockElement ,
DOMDocumentPreferredStylesheetSetPropertyInfo,
getDOMDocumentPreferredStylesheetSet ,
DOMDocumentReadyStatePropertyInfo ,
getDOMDocumentReadyState ,
DOMDocumentReferrerPropertyInfo ,
getDOMDocumentReferrer ,
DOMDocumentScrollingElementPropertyInfo ,
getDOMDocumentScrollingElement ,
DOMDocumentSelectedStylesheetSetPropertyInfo,
constructDOMDocumentSelectedStylesheetSet,
getDOMDocumentSelectedStylesheetSet ,
setDOMDocumentSelectedStylesheetSet ,
DOMDocumentStyleSheetsPropertyInfo ,
getDOMDocumentStyleSheets ,
DOMDocumentTitlePropertyInfo ,
constructDOMDocumentTitle ,
getDOMDocumentTitle ,
setDOMDocumentTitle ,
DOMDocumentUrlPropertyInfo ,
getDOMDocumentUrl ,
DOMDocumentVisibilityStatePropertyInfo ,
getDOMDocumentVisibilityState ,
DOMDocumentWebkitCurrentFullScreenElementPropertyInfo,
getDOMDocumentWebkitCurrentFullScreenElement,
DOMDocumentWebkitFullScreenKeyboardInputAllowedPropertyInfo,
getDOMDocumentWebkitFullScreenKeyboardInputAllowed,
DOMDocumentWebkitFullscreenElementPropertyInfo,
getDOMDocumentWebkitFullscreenElement ,
DOMDocumentWebkitFullscreenEnabledPropertyInfo,
getDOMDocumentWebkitFullscreenEnabled ,
DOMDocumentWebkitIsFullScreenPropertyInfo,
getDOMDocumentWebkitIsFullScreen ,
DOMDocumentXmlEncodingPropertyInfo ,
getDOMDocumentXmlEncoding ,
DOMDocumentXmlStandalonePropertyInfo ,
constructDOMDocumentXmlStandalone ,
getDOMDocumentXmlStandalone ,
setDOMDocumentXmlStandalone ,
DOMDocumentXmlVersionPropertyInfo ,
constructDOMDocumentXmlVersion ,
getDOMDocumentXmlVersion ,
setDOMDocumentXmlVersion ,
) where
import Prelude ()
import Data.GI.Base.ShortPrelude
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import GI.WebKit2WebExtension.Types
import GI.WebKit2WebExtension.Callbacks
import qualified GI.GObject as GObject
newtype DOMDocument = DOMDocument (ForeignPtr DOMDocument)
foreign import ccall "webkit_dom_document_get_type"
c_webkit_dom_document_get_type :: IO GType
type instance ParentTypes DOMDocument = DOMDocumentParentTypes
type DOMDocumentParentTypes = '[DOMNode, DOMObject, GObject.Object, DOMEventTarget]
instance GObject DOMDocument where
gobjectIsInitiallyUnowned _ = False
gobjectType _ = c_webkit_dom_document_get_type
class GObject o => DOMDocumentK o
instance (GObject o, IsDescendantOf DOMDocument o) => DOMDocumentK o
toDOMDocument :: DOMDocumentK o => o -> IO DOMDocument
toDOMDocument = unsafeCastTo DOMDocument
noDOMDocument :: Maybe DOMDocument
noDOMDocument = Nothing
getDOMDocumentActiveElement :: (MonadIO m, DOMDocumentK o) => o -> m DOMElement
getDOMDocumentActiveElement obj = liftIO $ getObjectPropertyObject obj "active-element" DOMElement
data DOMDocumentActiveElementPropertyInfo
instance AttrInfo DOMDocumentActiveElementPropertyInfo where
type AttrAllowedOps DOMDocumentActiveElementPropertyInfo = '[ 'AttrGet]
type AttrSetTypeConstraint DOMDocumentActiveElementPropertyInfo = (~) ()
type AttrBaseTypeConstraint DOMDocumentActiveElementPropertyInfo = DOMDocumentK
type AttrGetType DOMDocumentActiveElementPropertyInfo = DOMElement
type AttrLabel DOMDocumentActiveElementPropertyInfo = "DOMDocument::active-element"
attrGet _ = getDOMDocumentActiveElement
attrSet _ = undefined
attrConstruct _ = undefined
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
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
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
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
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
getDOMDocumentChildElementCount :: (MonadIO m, DOMDocumentK o) => o -> m Word64
getDOMDocumentChildElementCount obj = liftIO $ getObjectPropertyUInt64 obj "child-element-count"
data DOMDocumentChildElementCountPropertyInfo
instance AttrInfo DOMDocumentChildElementCountPropertyInfo where
type AttrAllowedOps DOMDocumentChildElementCountPropertyInfo = '[ 'AttrGet]
type AttrSetTypeConstraint DOMDocumentChildElementCountPropertyInfo = (~) ()
type AttrBaseTypeConstraint DOMDocumentChildElementCountPropertyInfo = DOMDocumentK
type AttrGetType DOMDocumentChildElementCountPropertyInfo = Word64
type AttrLabel DOMDocumentChildElementCountPropertyInfo = "DOMDocument::child-element-count"
attrGet _ = getDOMDocumentChildElementCount
attrSet _ = undefined
attrConstruct _ = undefined
getDOMDocumentChildren :: (MonadIO m, DOMDocumentK o) => o -> m DOMHTMLCollection
getDOMDocumentChildren obj = liftIO $ getObjectPropertyObject obj "children" DOMHTMLCollection
data DOMDocumentChildrenPropertyInfo
instance AttrInfo DOMDocumentChildrenPropertyInfo where
type AttrAllowedOps DOMDocumentChildrenPropertyInfo = '[ 'AttrGet]
type AttrSetTypeConstraint DOMDocumentChildrenPropertyInfo = (~) ()
type AttrBaseTypeConstraint DOMDocumentChildrenPropertyInfo = DOMDocumentK
type AttrGetType DOMDocumentChildrenPropertyInfo = DOMHTMLCollection
type AttrLabel DOMDocumentChildrenPropertyInfo = "DOMDocument::children"
attrGet _ = getDOMDocumentChildren
attrSet _ = undefined
attrConstruct _ = undefined
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
getDOMDocumentContentType :: (MonadIO m, DOMDocumentK o) => o -> m T.Text
getDOMDocumentContentType obj = liftIO $ getObjectPropertyString obj "content-type"
data DOMDocumentContentTypePropertyInfo
instance AttrInfo DOMDocumentContentTypePropertyInfo where
type AttrAllowedOps DOMDocumentContentTypePropertyInfo = '[ 'AttrGet]
type AttrSetTypeConstraint DOMDocumentContentTypePropertyInfo = (~) ()
type AttrBaseTypeConstraint DOMDocumentContentTypePropertyInfo = DOMDocumentK
type AttrGetType DOMDocumentContentTypePropertyInfo = T.Text
type AttrLabel DOMDocumentContentTypePropertyInfo = "DOMDocument::content-type"
attrGet _ = getDOMDocumentContentType
attrSet _ = undefined
attrConstruct _ = undefined
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
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
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
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
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
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
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
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
getDOMDocumentFirstElementChild :: (MonadIO m, DOMDocumentK o) => o -> m DOMElement
getDOMDocumentFirstElementChild obj = liftIO $ getObjectPropertyObject obj "first-element-child" DOMElement
data DOMDocumentFirstElementChildPropertyInfo
instance AttrInfo DOMDocumentFirstElementChildPropertyInfo where
type AttrAllowedOps DOMDocumentFirstElementChildPropertyInfo = '[ 'AttrGet]
type AttrSetTypeConstraint DOMDocumentFirstElementChildPropertyInfo = (~) ()
type AttrBaseTypeConstraint DOMDocumentFirstElementChildPropertyInfo = DOMDocumentK
type AttrGetType DOMDocumentFirstElementChildPropertyInfo = DOMElement
type AttrLabel DOMDocumentFirstElementChildPropertyInfo = "DOMDocument::first-element-child"
attrGet _ = getDOMDocumentFirstElementChild
attrSet _ = undefined
attrConstruct _ = undefined
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
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
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
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
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
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
getDOMDocumentLastElementChild :: (MonadIO m, DOMDocumentK o) => o -> m DOMElement
getDOMDocumentLastElementChild obj = liftIO $ getObjectPropertyObject obj "last-element-child" DOMElement
data DOMDocumentLastElementChildPropertyInfo
instance AttrInfo DOMDocumentLastElementChildPropertyInfo where
type AttrAllowedOps DOMDocumentLastElementChildPropertyInfo = '[ 'AttrGet]
type AttrSetTypeConstraint DOMDocumentLastElementChildPropertyInfo = (~) ()
type AttrBaseTypeConstraint DOMDocumentLastElementChildPropertyInfo = DOMDocumentK
type AttrGetType DOMDocumentLastElementChildPropertyInfo = DOMElement
type AttrLabel DOMDocumentLastElementChildPropertyInfo = "DOMDocument::last-element-child"
attrGet _ = getDOMDocumentLastElementChild
attrSet _ = undefined
attrConstruct _ = undefined
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
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
getDOMDocumentOrigin :: (MonadIO m, DOMDocumentK o) => o -> m T.Text
getDOMDocumentOrigin obj = liftIO $ getObjectPropertyString obj "origin"
data DOMDocumentOriginPropertyInfo
instance AttrInfo DOMDocumentOriginPropertyInfo where
type AttrAllowedOps DOMDocumentOriginPropertyInfo = '[ 'AttrGet]
type AttrSetTypeConstraint DOMDocumentOriginPropertyInfo = (~) ()
type AttrBaseTypeConstraint DOMDocumentOriginPropertyInfo = DOMDocumentK
type AttrGetType DOMDocumentOriginPropertyInfo = T.Text
type AttrLabel DOMDocumentOriginPropertyInfo = "DOMDocument::origin"
attrGet _ = getDOMDocumentOrigin
attrSet _ = undefined
attrConstruct _ = undefined
getDOMDocumentPointerLockElement :: (MonadIO m, DOMDocumentK o) => o -> m DOMElement
getDOMDocumentPointerLockElement obj = liftIO $ getObjectPropertyObject obj "pointer-lock-element" DOMElement
data DOMDocumentPointerLockElementPropertyInfo
instance AttrInfo DOMDocumentPointerLockElementPropertyInfo where
type AttrAllowedOps DOMDocumentPointerLockElementPropertyInfo = '[ 'AttrGet]
type AttrSetTypeConstraint DOMDocumentPointerLockElementPropertyInfo = (~) ()
type AttrBaseTypeConstraint DOMDocumentPointerLockElementPropertyInfo = DOMDocumentK
type AttrGetType DOMDocumentPointerLockElementPropertyInfo = DOMElement
type AttrLabel DOMDocumentPointerLockElementPropertyInfo = "DOMDocument::pointer-lock-element"
attrGet _ = getDOMDocumentPointerLockElement
attrSet _ = undefined
attrConstruct _ = undefined
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
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
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
getDOMDocumentScrollingElement :: (MonadIO m, DOMDocumentK o) => o -> m DOMElement
getDOMDocumentScrollingElement obj = liftIO $ getObjectPropertyObject obj "scrolling-element" DOMElement
data DOMDocumentScrollingElementPropertyInfo
instance AttrInfo DOMDocumentScrollingElementPropertyInfo where
type AttrAllowedOps DOMDocumentScrollingElementPropertyInfo = '[ 'AttrGet]
type AttrSetTypeConstraint DOMDocumentScrollingElementPropertyInfo = (~) ()
type AttrBaseTypeConstraint DOMDocumentScrollingElementPropertyInfo = DOMDocumentK
type AttrGetType DOMDocumentScrollingElementPropertyInfo = DOMElement
type AttrLabel DOMDocumentScrollingElementPropertyInfo = "DOMDocument::scrolling-element"
attrGet _ = getDOMDocumentScrollingElement
attrSet _ = undefined
attrConstruct _ = undefined
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
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
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
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
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
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
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
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
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
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
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
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
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 = DOMDocumentAttributeList
type DOMDocumentAttributeList = ('[ '("active-element", DOMDocumentActiveElementPropertyInfo), '("anchors", DOMDocumentAnchorsPropertyInfo), '("applets", DOMDocumentAppletsPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("body", DOMDocumentBodyPropertyInfo), '("character-set", DOMDocumentCharacterSetPropertyInfo), '("charset", DOMDocumentCharsetPropertyInfo), '("child-element-count", DOMDocumentChildElementCountPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("children", DOMDocumentChildrenPropertyInfo), '("compat-mode", DOMDocumentCompatModePropertyInfo), '("content-type", DOMDocumentContentTypePropertyInfo), '("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), '("first-element-child", DOMDocumentFirstElementChildPropertyInfo), '("forms", DOMDocumentFormsPropertyInfo), '("head", DOMDocumentHeadPropertyInfo), '("hidden", DOMDocumentHiddenPropertyInfo), '("images", DOMDocumentImagesPropertyInfo), '("implementation", DOMDocumentImplementationPropertyInfo), '("input-encoding", DOMDocumentInputEncodingPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-element-child", DOMDocumentLastElementChildPropertyInfo), '("last-modified", DOMDocumentLastModifiedPropertyInfo), '("links", DOMDocumentLinksPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("origin", DOMDocumentOriginPropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("pointer-lock-element", DOMDocumentPointerLockElementPropertyInfo), '("preferred-stylesheet-set", DOMDocumentPreferredStylesheetSetPropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("ready-state", DOMDocumentReadyStatePropertyInfo), '("referrer", DOMDocumentReferrerPropertyInfo), '("scrolling-element", DOMDocumentScrollingElementPropertyInfo), '("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), '("xml-encoding", DOMDocumentXmlEncodingPropertyInfo), '("xml-standalone", DOMDocumentXmlStandalonePropertyInfo), '("xml-version", DOMDocumentXmlVersionPropertyInfo)] :: [(Symbol, *)])
type instance SignalList DOMDocument = DOMDocumentSignalList
type DOMDocumentSignalList = ('[ '("notify", GObject.ObjectNotifySignalInfo), '("notify::[property]", GObjectNotifySignalInfo)] :: [(Symbol, *)])
foreign import ccall "webkit_dom_document_adopt_node" webkit_dom_document_adopt_node ::
Ptr DOMDocument ->
Ptr DOMNode ->
Ptr (Ptr GError) ->
IO (Ptr DOMNode)
dOMDocumentAdoptNode ::
(MonadIO m, DOMDocumentK a, DOMNodeK b) =>
a ->
b ->
m DOMNode
dOMDocumentAdoptNode _obj source = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
let source' = unsafeManagedPtrCastPtr source
onException (do
result <- propagateGError $ webkit_dom_document_adopt_node _obj' source'
checkUnexpectedReturnNULL "webkit_dom_document_adopt_node" result
result' <- (newObject DOMNode) result
touchManagedPtr _obj
touchManagedPtr source
return result'
) (do
return ()
)
foreign import ccall "webkit_dom_document_create_attribute" webkit_dom_document_create_attribute ::
Ptr DOMDocument ->
CString ->
Ptr (Ptr GError) ->
IO (Ptr DOMAttr)
dOMDocumentCreateAttribute ::
(MonadIO m, DOMDocumentK a) =>
a ->
T.Text ->
m DOMAttr
dOMDocumentCreateAttribute _obj name = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
name' <- textToCString name
onException (do
result <- propagateGError $ webkit_dom_document_create_attribute _obj' name'
checkUnexpectedReturnNULL "webkit_dom_document_create_attribute" result
result' <- (newObject DOMAttr) result
touchManagedPtr _obj
freeMem name'
return result'
) (do
freeMem name'
)
foreign import ccall "webkit_dom_document_create_attribute_ns" webkit_dom_document_create_attribute_ns ::
Ptr DOMDocument ->
CString ->
CString ->
Ptr (Ptr GError) ->
IO (Ptr DOMAttr)
dOMDocumentCreateAttributeNs ::
(MonadIO m, DOMDocumentK a) =>
a ->
Maybe (T.Text) ->
T.Text ->
m DOMAttr
dOMDocumentCreateAttributeNs _obj namespaceURI qualifiedName = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
maybeNamespaceURI <- case namespaceURI of
Nothing -> return nullPtr
Just jNamespaceURI -> do
jNamespaceURI' <- textToCString jNamespaceURI
return jNamespaceURI'
qualifiedName' <- textToCString qualifiedName
onException (do
result <- propagateGError $ webkit_dom_document_create_attribute_ns _obj' maybeNamespaceURI qualifiedName'
checkUnexpectedReturnNULL "webkit_dom_document_create_attribute_ns" result
result' <- (newObject DOMAttr) result
touchManagedPtr _obj
freeMem maybeNamespaceURI
freeMem qualifiedName'
return result'
) (do
freeMem maybeNamespaceURI
freeMem qualifiedName'
)
foreign import ccall "webkit_dom_document_create_cdata_section" webkit_dom_document_create_cdata_section ::
Ptr DOMDocument ->
CString ->
Ptr (Ptr GError) ->
IO (Ptr DOMCDATASection)
dOMDocumentCreateCdataSection ::
(MonadIO m, DOMDocumentK a) =>
a ->
T.Text ->
m DOMCDATASection
dOMDocumentCreateCdataSection _obj data_ = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
data_' <- textToCString data_
onException (do
result <- propagateGError $ webkit_dom_document_create_cdata_section _obj' data_'
checkUnexpectedReturnNULL "webkit_dom_document_create_cdata_section" result
result' <- (newObject DOMCDATASection) result
touchManagedPtr _obj
freeMem data_'
return result'
) (do
freeMem data_'
)
foreign import ccall "webkit_dom_document_create_comment" webkit_dom_document_create_comment ::
Ptr DOMDocument ->
CString ->
IO (Ptr DOMComment)
dOMDocumentCreateComment ::
(MonadIO m, DOMDocumentK a) =>
a ->
T.Text ->
m DOMComment
dOMDocumentCreateComment _obj data_ = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
data_' <- textToCString data_
result <- webkit_dom_document_create_comment _obj' data_'
checkUnexpectedReturnNULL "webkit_dom_document_create_comment" result
result' <- (newObject DOMComment) result
touchManagedPtr _obj
freeMem data_'
return result'
foreign import ccall "webkit_dom_document_create_css_style_declaration" webkit_dom_document_create_css_style_declaration ::
Ptr DOMDocument ->
IO (Ptr DOMCSSStyleDeclaration)
dOMDocumentCreateCssStyleDeclaration ::
(MonadIO m, DOMDocumentK a) =>
a ->
m DOMCSSStyleDeclaration
dOMDocumentCreateCssStyleDeclaration _obj = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
result <- webkit_dom_document_create_css_style_declaration _obj'
checkUnexpectedReturnNULL "webkit_dom_document_create_css_style_declaration" result
result' <- (wrapObject DOMCSSStyleDeclaration) result
touchManagedPtr _obj
return result'
foreign import ccall "webkit_dom_document_create_document_fragment" webkit_dom_document_create_document_fragment ::
Ptr DOMDocument ->
IO (Ptr DOMDocumentFragment)
dOMDocumentCreateDocumentFragment ::
(MonadIO m, DOMDocumentK a) =>
a ->
m DOMDocumentFragment
dOMDocumentCreateDocumentFragment _obj = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
result <- webkit_dom_document_create_document_fragment _obj'
checkUnexpectedReturnNULL "webkit_dom_document_create_document_fragment" result
result' <- (newObject DOMDocumentFragment) result
touchManagedPtr _obj
return result'
foreign import ccall "webkit_dom_document_create_element" webkit_dom_document_create_element ::
Ptr DOMDocument ->
CString ->
Ptr (Ptr GError) ->
IO (Ptr DOMElement)
dOMDocumentCreateElement ::
(MonadIO m, DOMDocumentK a) =>
a ->
T.Text ->
m DOMElement
dOMDocumentCreateElement _obj tagName = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
tagName' <- textToCString tagName
onException (do
result <- propagateGError $ webkit_dom_document_create_element _obj' tagName'
checkUnexpectedReturnNULL "webkit_dom_document_create_element" result
result' <- (newObject DOMElement) result
touchManagedPtr _obj
freeMem tagName'
return result'
) (do
freeMem tagName'
)
foreign import ccall "webkit_dom_document_create_element_ns" webkit_dom_document_create_element_ns ::
Ptr DOMDocument ->
CString ->
CString ->
Ptr (Ptr GError) ->
IO (Ptr DOMElement)
dOMDocumentCreateElementNs ::
(MonadIO m, DOMDocumentK a) =>
a ->
Maybe (T.Text) ->
T.Text ->
m DOMElement
dOMDocumentCreateElementNs _obj namespaceURI qualifiedName = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
maybeNamespaceURI <- case namespaceURI of
Nothing -> return nullPtr
Just jNamespaceURI -> do
jNamespaceURI' <- textToCString jNamespaceURI
return jNamespaceURI'
qualifiedName' <- textToCString qualifiedName
onException (do
result <- propagateGError $ webkit_dom_document_create_element_ns _obj' maybeNamespaceURI qualifiedName'
checkUnexpectedReturnNULL "webkit_dom_document_create_element_ns" result
result' <- (newObject DOMElement) result
touchManagedPtr _obj
freeMem maybeNamespaceURI
freeMem qualifiedName'
return result'
) (do
freeMem maybeNamespaceURI
freeMem qualifiedName'
)
foreign import ccall "webkit_dom_document_create_entity_reference" webkit_dom_document_create_entity_reference ::
Ptr DOMDocument ->
CString ->
Ptr (Ptr GError) ->
IO (Ptr DOMEntityReference)
dOMDocumentCreateEntityReference ::
(MonadIO m, DOMDocumentK a) =>
a ->
Maybe (T.Text) ->
m DOMEntityReference
dOMDocumentCreateEntityReference _obj name = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
maybeName <- case name of
Nothing -> return nullPtr
Just jName -> do
jName' <- textToCString jName
return jName'
onException (do
result <- propagateGError $ webkit_dom_document_create_entity_reference _obj' maybeName
checkUnexpectedReturnNULL "webkit_dom_document_create_entity_reference" result
result' <- (newObject DOMEntityReference) result
touchManagedPtr _obj
freeMem maybeName
return result'
) (do
freeMem maybeName
)
foreign import ccall "webkit_dom_document_create_event" webkit_dom_document_create_event ::
Ptr DOMDocument ->
CString ->
Ptr (Ptr GError) ->
IO (Ptr DOMEvent)
dOMDocumentCreateEvent ::
(MonadIO m, DOMDocumentK a) =>
a ->
T.Text ->
m DOMEvent
dOMDocumentCreateEvent _obj eventType = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
eventType' <- textToCString eventType
onException (do
result <- propagateGError $ webkit_dom_document_create_event _obj' eventType'
checkUnexpectedReturnNULL "webkit_dom_document_create_event" result
result' <- (wrapObject DOMEvent) result
touchManagedPtr _obj
freeMem eventType'
return result'
) (do
freeMem eventType'
)
foreign import ccall "webkit_dom_document_create_expression" webkit_dom_document_create_expression ::
Ptr DOMDocument ->
CString ->
Ptr DOMXPathNSResolver ->
Ptr (Ptr GError) ->
IO (Ptr DOMXPathExpression)
dOMDocumentCreateExpression ::
(MonadIO m, DOMDocumentK a, DOMXPathNSResolverK b) =>
a ->
T.Text ->
b ->
m DOMXPathExpression
dOMDocumentCreateExpression _obj expression resolver = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
expression' <- textToCString expression
let resolver' = unsafeManagedPtrCastPtr resolver
onException (do
result <- propagateGError $ webkit_dom_document_create_expression _obj' expression' resolver'
checkUnexpectedReturnNULL "webkit_dom_document_create_expression" result
result' <- (wrapObject DOMXPathExpression) result
touchManagedPtr _obj
touchManagedPtr resolver
freeMem expression'
return result'
) (do
freeMem expression'
)
foreign import ccall "webkit_dom_document_create_node_iterator" webkit_dom_document_create_node_iterator ::
Ptr DOMDocument ->
Ptr DOMNode ->
Word64 ->
Ptr DOMNodeFilter ->
CInt ->
Ptr (Ptr GError) ->
IO (Ptr DOMNodeIterator)
dOMDocumentCreateNodeIterator ::
(MonadIO m, DOMDocumentK a, DOMNodeK b, DOMNodeFilterK c) =>
a ->
b ->
Word64 ->
Maybe (c) ->
Bool ->
m DOMNodeIterator
dOMDocumentCreateNodeIterator _obj root whatToShow filter expandEntityReferences = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
let root' = unsafeManagedPtrCastPtr root
maybeFilter <- case filter of
Nothing -> return nullPtr
Just jFilter -> do
let jFilter' = unsafeManagedPtrCastPtr jFilter
return jFilter'
let expandEntityReferences' = (fromIntegral . fromEnum) expandEntityReferences
onException (do
result <- propagateGError $ webkit_dom_document_create_node_iterator _obj' root' whatToShow maybeFilter expandEntityReferences'
checkUnexpectedReturnNULL "webkit_dom_document_create_node_iterator" result
result' <- (wrapObject DOMNodeIterator) result
touchManagedPtr _obj
touchManagedPtr root
whenJust filter touchManagedPtr
return result'
) (do
return ()
)
foreign import ccall "webkit_dom_document_create_ns_resolver" webkit_dom_document_create_ns_resolver ::
Ptr DOMDocument ->
Ptr DOMNode ->
IO (Ptr DOMXPathNSResolver)
dOMDocumentCreateNsResolver ::
(MonadIO m, DOMDocumentK a, DOMNodeK b) =>
a ->
b ->
m DOMXPathNSResolver
dOMDocumentCreateNsResolver _obj nodeResolver = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
let nodeResolver' = unsafeManagedPtrCastPtr nodeResolver
result <- webkit_dom_document_create_ns_resolver _obj' nodeResolver'
checkUnexpectedReturnNULL "webkit_dom_document_create_ns_resolver" result
result' <- (wrapObject DOMXPathNSResolver) result
touchManagedPtr _obj
touchManagedPtr nodeResolver
return result'
foreign import ccall "webkit_dom_document_create_processing_instruction" webkit_dom_document_create_processing_instruction ::
Ptr DOMDocument ->
CString ->
CString ->
Ptr (Ptr GError) ->
IO (Ptr DOMProcessingInstruction)
dOMDocumentCreateProcessingInstruction ::
(MonadIO m, DOMDocumentK a) =>
a ->
T.Text ->
T.Text ->
m DOMProcessingInstruction
dOMDocumentCreateProcessingInstruction _obj target data_ = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
target' <- textToCString target
data_' <- textToCString data_
onException (do
result <- propagateGError $ webkit_dom_document_create_processing_instruction _obj' target' data_'
checkUnexpectedReturnNULL "webkit_dom_document_create_processing_instruction" result
result' <- (newObject DOMProcessingInstruction) result
touchManagedPtr _obj
freeMem target'
freeMem data_'
return result'
) (do
freeMem target'
freeMem data_'
)
foreign import ccall "webkit_dom_document_create_range" webkit_dom_document_create_range ::
Ptr DOMDocument ->
IO (Ptr DOMRange)
dOMDocumentCreateRange ::
(MonadIO m, DOMDocumentK a) =>
a ->
m DOMRange
dOMDocumentCreateRange _obj = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
result <- webkit_dom_document_create_range _obj'
checkUnexpectedReturnNULL "webkit_dom_document_create_range" result
result' <- (wrapObject DOMRange) result
touchManagedPtr _obj
return result'
foreign import ccall "webkit_dom_document_create_text_node" webkit_dom_document_create_text_node ::
Ptr DOMDocument ->
CString ->
IO (Ptr DOMText)
dOMDocumentCreateTextNode ::
(MonadIO m, DOMDocumentK a) =>
a ->
T.Text ->
m DOMText
dOMDocumentCreateTextNode _obj data_ = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
data_' <- textToCString data_
result <- webkit_dom_document_create_text_node _obj' data_'
checkUnexpectedReturnNULL "webkit_dom_document_create_text_node" result
result' <- (newObject DOMText) result
touchManagedPtr _obj
freeMem data_'
return result'
foreign import ccall "webkit_dom_document_create_tree_walker" webkit_dom_document_create_tree_walker ::
Ptr DOMDocument ->
Ptr DOMNode ->
Word64 ->
Ptr DOMNodeFilter ->
CInt ->
Ptr (Ptr GError) ->
IO (Ptr DOMTreeWalker)
dOMDocumentCreateTreeWalker ::
(MonadIO m, DOMDocumentK a, DOMNodeK b, DOMNodeFilterK c) =>
a ->
b ->
Word64 ->
Maybe (c) ->
Bool ->
m DOMTreeWalker
dOMDocumentCreateTreeWalker _obj root whatToShow filter expandEntityReferences = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
let root' = unsafeManagedPtrCastPtr root
maybeFilter <- case filter of
Nothing -> return nullPtr
Just jFilter -> do
let jFilter' = unsafeManagedPtrCastPtr jFilter
return jFilter'
let expandEntityReferences' = (fromIntegral . fromEnum) expandEntityReferences
onException (do
result <- propagateGError $ webkit_dom_document_create_tree_walker _obj' root' whatToShow maybeFilter expandEntityReferences'
checkUnexpectedReturnNULL "webkit_dom_document_create_tree_walker" result
result' <- (wrapObject DOMTreeWalker) result
touchManagedPtr _obj
touchManagedPtr root
whenJust filter touchManagedPtr
return result'
) (do
return ()
)
foreign import ccall "webkit_dom_document_element_from_point" webkit_dom_document_element_from_point ::
Ptr DOMDocument ->
Int64 ->
Int64 ->
IO (Ptr DOMElement)
dOMDocumentElementFromPoint ::
(MonadIO m, DOMDocumentK a) =>
a ->
Int64 ->
Int64 ->
m DOMElement
dOMDocumentElementFromPoint _obj x y = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
result <- webkit_dom_document_element_from_point _obj' x y
checkUnexpectedReturnNULL "webkit_dom_document_element_from_point" result
result' <- (newObject DOMElement) result
touchManagedPtr _obj
return result'
foreign import ccall "webkit_dom_document_evaluate" webkit_dom_document_evaluate ::
Ptr DOMDocument ->
CString ->
Ptr DOMNode ->
Ptr DOMXPathNSResolver ->
Word16 ->
Ptr DOMXPathResult ->
Ptr (Ptr GError) ->
IO (Ptr DOMXPathResult)
dOMDocumentEvaluate ::
(MonadIO m, DOMDocumentK a, DOMNodeK b, DOMXPathNSResolverK c, DOMXPathResultK d) =>
a ->
T.Text ->
b ->
Maybe (c) ->
Word16 ->
Maybe (d) ->
m DOMXPathResult
dOMDocumentEvaluate _obj expression contextNode resolver type_ inResult = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
expression' <- textToCString expression
let contextNode' = unsafeManagedPtrCastPtr contextNode
maybeResolver <- case resolver of
Nothing -> return nullPtr
Just jResolver -> do
let jResolver' = unsafeManagedPtrCastPtr jResolver
return jResolver'
maybeInResult <- case inResult of
Nothing -> return nullPtr
Just jInResult -> do
let jInResult' = unsafeManagedPtrCastPtr jInResult
return jInResult'
onException (do
result <- propagateGError $ webkit_dom_document_evaluate _obj' expression' contextNode' maybeResolver type_ maybeInResult
checkUnexpectedReturnNULL "webkit_dom_document_evaluate" result
result' <- (wrapObject DOMXPathResult) result
touchManagedPtr _obj
touchManagedPtr contextNode
whenJust resolver touchManagedPtr
whenJust inResult touchManagedPtr
freeMem expression'
return result'
) (do
freeMem expression'
)
foreign import ccall "webkit_dom_document_exec_command" webkit_dom_document_exec_command ::
Ptr DOMDocument ->
CString ->
CInt ->
CString ->
IO CInt
dOMDocumentExecCommand ::
(MonadIO m, DOMDocumentK a) =>
a ->
T.Text ->
Bool ->
T.Text ->
m Bool
dOMDocumentExecCommand _obj command userInterface value = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
command' <- textToCString command
let userInterface' = (fromIntegral . fromEnum) userInterface
value' <- textToCString value
result <- webkit_dom_document_exec_command _obj' command' userInterface' value'
let result' = (/= 0) result
touchManagedPtr _obj
freeMem command'
freeMem value'
return result'
foreign import ccall "webkit_dom_document_get_active_element" webkit_dom_document_get_active_element ::
Ptr DOMDocument ->
IO (Ptr DOMElement)
dOMDocumentGetActiveElement ::
(MonadIO m, DOMDocumentK a) =>
a ->
m DOMElement
dOMDocumentGetActiveElement _obj = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
result <- webkit_dom_document_get_active_element _obj'
checkUnexpectedReturnNULL "webkit_dom_document_get_active_element" result
result' <- (newObject DOMElement) result
touchManagedPtr _obj
return result'
foreign import ccall "webkit_dom_document_get_anchors" webkit_dom_document_get_anchors ::
Ptr DOMDocument ->
IO (Ptr DOMHTMLCollection)
dOMDocumentGetAnchors ::
(MonadIO m, DOMDocumentK a) =>
a ->
m DOMHTMLCollection
dOMDocumentGetAnchors _obj = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
result <- webkit_dom_document_get_anchors _obj'
checkUnexpectedReturnNULL "webkit_dom_document_get_anchors" result
result' <- (wrapObject DOMHTMLCollection) result
touchManagedPtr _obj
return result'
foreign import ccall "webkit_dom_document_get_applets" webkit_dom_document_get_applets ::
Ptr DOMDocument ->
IO (Ptr DOMHTMLCollection)
dOMDocumentGetApplets ::
(MonadIO m, DOMDocumentK a) =>
a ->
m DOMHTMLCollection
dOMDocumentGetApplets _obj = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
result <- webkit_dom_document_get_applets _obj'
checkUnexpectedReturnNULL "webkit_dom_document_get_applets" result
result' <- (wrapObject DOMHTMLCollection) result
touchManagedPtr _obj
return result'
foreign import ccall "webkit_dom_document_get_body" webkit_dom_document_get_body ::
Ptr DOMDocument ->
IO (Ptr DOMHTMLElement)
dOMDocumentGetBody ::
(MonadIO m, DOMDocumentK a) =>
a ->
m DOMHTMLElement
dOMDocumentGetBody _obj = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
result <- webkit_dom_document_get_body _obj'
checkUnexpectedReturnNULL "webkit_dom_document_get_body" result
result' <- (newObject DOMHTMLElement) result
touchManagedPtr _obj
return result'
foreign import ccall "webkit_dom_document_get_character_set" webkit_dom_document_get_character_set ::
Ptr DOMDocument ->
IO CString
dOMDocumentGetCharacterSet ::
(MonadIO m, DOMDocumentK a) =>
a ->
m T.Text
dOMDocumentGetCharacterSet _obj = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
result <- webkit_dom_document_get_character_set _obj'
checkUnexpectedReturnNULL "webkit_dom_document_get_character_set" result
result' <- cstringToText result
freeMem result
touchManagedPtr _obj
return result'
foreign import ccall "webkit_dom_document_get_charset" webkit_dom_document_get_charset ::
Ptr DOMDocument ->
IO CString
dOMDocumentGetCharset ::
(MonadIO m, DOMDocumentK a) =>
a ->
m T.Text
dOMDocumentGetCharset _obj = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
result <- webkit_dom_document_get_charset _obj'
checkUnexpectedReturnNULL "webkit_dom_document_get_charset" result
result' <- cstringToText result
freeMem result
touchManagedPtr _obj
return result'
foreign import ccall "webkit_dom_document_get_cookie" webkit_dom_document_get_cookie ::
Ptr DOMDocument ->
Ptr (Ptr GError) ->
IO CString
dOMDocumentGetCookie ::
(MonadIO m, DOMDocumentK a) =>
a ->
m T.Text
dOMDocumentGetCookie _obj = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
onException (do
result <- propagateGError $ webkit_dom_document_get_cookie _obj'
checkUnexpectedReturnNULL "webkit_dom_document_get_cookie" result
result' <- cstringToText result
freeMem result
touchManagedPtr _obj
return result'
) (do
return ()
)
foreign import ccall "webkit_dom_document_get_default_charset" webkit_dom_document_get_default_charset ::
Ptr DOMDocument ->
IO CString
dOMDocumentGetDefaultCharset ::
(MonadIO m, DOMDocumentK a) =>
a ->
m T.Text
dOMDocumentGetDefaultCharset _obj = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
result <- webkit_dom_document_get_default_charset _obj'
checkUnexpectedReturnNULL "webkit_dom_document_get_default_charset" result
result' <- cstringToText result
freeMem result
touchManagedPtr _obj
return result'
foreign import ccall "webkit_dom_document_get_default_view" webkit_dom_document_get_default_view ::
Ptr DOMDocument ->
IO (Ptr DOMDOMWindow)
dOMDocumentGetDefaultView ::
(MonadIO m, DOMDocumentK a) =>
a ->
m DOMDOMWindow
dOMDocumentGetDefaultView _obj = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
result <- webkit_dom_document_get_default_view _obj'
checkUnexpectedReturnNULL "webkit_dom_document_get_default_view" result
result' <- (wrapObject DOMDOMWindow) result
touchManagedPtr _obj
return result'
foreign import ccall "webkit_dom_document_get_doctype" webkit_dom_document_get_doctype ::
Ptr DOMDocument ->
IO (Ptr DOMDocumentType)
dOMDocumentGetDoctype ::
(MonadIO m, DOMDocumentK a) =>
a ->
m DOMDocumentType
dOMDocumentGetDoctype _obj = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
result <- webkit_dom_document_get_doctype _obj'
checkUnexpectedReturnNULL "webkit_dom_document_get_doctype" result
result' <- (newObject DOMDocumentType) result
touchManagedPtr _obj
return result'
foreign import ccall "webkit_dom_document_get_document_element" webkit_dom_document_get_document_element ::
Ptr DOMDocument ->
IO (Ptr DOMElement)
dOMDocumentGetDocumentElement ::
(MonadIO m, DOMDocumentK a) =>
a ->
m DOMElement
dOMDocumentGetDocumentElement _obj = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
result <- webkit_dom_document_get_document_element _obj'
checkUnexpectedReturnNULL "webkit_dom_document_get_document_element" result
result' <- (newObject DOMElement) result
touchManagedPtr _obj
return result'
foreign import ccall "webkit_dom_document_get_document_uri" webkit_dom_document_get_document_uri ::
Ptr DOMDocument ->
IO CString
dOMDocumentGetDocumentUri ::
(MonadIO m, DOMDocumentK a) =>
a ->
m T.Text
dOMDocumentGetDocumentUri _obj = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
result <- webkit_dom_document_get_document_uri _obj'
checkUnexpectedReturnNULL "webkit_dom_document_get_document_uri" result
result' <- cstringToText result
freeMem result
touchManagedPtr _obj
return result'
foreign import ccall "webkit_dom_document_get_domain" webkit_dom_document_get_domain ::
Ptr DOMDocument ->
IO CString
dOMDocumentGetDomain ::
(MonadIO m, DOMDocumentK a) =>
a ->
m T.Text
dOMDocumentGetDomain _obj = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
result <- webkit_dom_document_get_domain _obj'
checkUnexpectedReturnNULL "webkit_dom_document_get_domain" result
result' <- cstringToText result
freeMem result
touchManagedPtr _obj
return result'
foreign import ccall "webkit_dom_document_get_element_by_id" webkit_dom_document_get_element_by_id ::
Ptr DOMDocument ->
CString ->
IO (Ptr DOMElement)
dOMDocumentGetElementById ::
(MonadIO m, DOMDocumentK a) =>
a ->
T.Text ->
m DOMElement
dOMDocumentGetElementById _obj elementId = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
elementId' <- textToCString elementId
result <- webkit_dom_document_get_element_by_id _obj' elementId'
checkUnexpectedReturnNULL "webkit_dom_document_get_element_by_id" result
result' <- (newObject DOMElement) result
touchManagedPtr _obj
freeMem elementId'
return result'
foreign import ccall "webkit_dom_document_get_elements_by_class_name" webkit_dom_document_get_elements_by_class_name ::
Ptr DOMDocument ->
CString ->
IO (Ptr DOMNodeList)
dOMDocumentGetElementsByClassName ::
(MonadIO m, DOMDocumentK a) =>
a ->
T.Text ->
m DOMNodeList
dOMDocumentGetElementsByClassName _obj classNames = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
classNames' <- textToCString classNames
result <- webkit_dom_document_get_elements_by_class_name _obj' classNames'
checkUnexpectedReturnNULL "webkit_dom_document_get_elements_by_class_name" result
result' <- (wrapObject DOMNodeList) result
touchManagedPtr _obj
freeMem classNames'
return result'
foreign import ccall "webkit_dom_document_get_elements_by_name" webkit_dom_document_get_elements_by_name ::
Ptr DOMDocument ->
CString ->
IO (Ptr DOMNodeList)
dOMDocumentGetElementsByName ::
(MonadIO m, DOMDocumentK a) =>
a ->
T.Text ->
m DOMNodeList
dOMDocumentGetElementsByName _obj elementName = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
elementName' <- textToCString elementName
result <- webkit_dom_document_get_elements_by_name _obj' elementName'
checkUnexpectedReturnNULL "webkit_dom_document_get_elements_by_name" result
result' <- (wrapObject DOMNodeList) result
touchManagedPtr _obj
freeMem elementName'
return result'
foreign import ccall "webkit_dom_document_get_elements_by_tag_name" webkit_dom_document_get_elements_by_tag_name ::
Ptr DOMDocument ->
CString ->
IO (Ptr DOMNodeList)
dOMDocumentGetElementsByTagName ::
(MonadIO m, DOMDocumentK a) =>
a ->
T.Text ->
m DOMNodeList
dOMDocumentGetElementsByTagName _obj tagname = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
tagname' <- textToCString tagname
result <- webkit_dom_document_get_elements_by_tag_name _obj' tagname'
checkUnexpectedReturnNULL "webkit_dom_document_get_elements_by_tag_name" result
result' <- (wrapObject DOMNodeList) result
touchManagedPtr _obj
freeMem tagname'
return result'
foreign import ccall "webkit_dom_document_get_elements_by_tag_name_ns" webkit_dom_document_get_elements_by_tag_name_ns ::
Ptr DOMDocument ->
CString ->
CString ->
IO (Ptr DOMNodeList)
dOMDocumentGetElementsByTagNameNs ::
(MonadIO m, DOMDocumentK a) =>
a ->
T.Text ->
T.Text ->
m DOMNodeList
dOMDocumentGetElementsByTagNameNs _obj namespaceURI localName = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
namespaceURI' <- textToCString namespaceURI
localName' <- textToCString localName
result <- webkit_dom_document_get_elements_by_tag_name_ns _obj' namespaceURI' localName'
checkUnexpectedReturnNULL "webkit_dom_document_get_elements_by_tag_name_ns" result
result' <- (wrapObject DOMNodeList) result
touchManagedPtr _obj
freeMem namespaceURI'
freeMem localName'
return result'
foreign import ccall "webkit_dom_document_get_forms" webkit_dom_document_get_forms ::
Ptr DOMDocument ->
IO (Ptr DOMHTMLCollection)
dOMDocumentGetForms ::
(MonadIO m, DOMDocumentK a) =>
a ->
m DOMHTMLCollection
dOMDocumentGetForms _obj = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
result <- webkit_dom_document_get_forms _obj'
checkUnexpectedReturnNULL "webkit_dom_document_get_forms" result
result' <- (wrapObject DOMHTMLCollection) result
touchManagedPtr _obj
return result'
foreign import ccall "webkit_dom_document_get_head" webkit_dom_document_get_head ::
Ptr DOMDocument ->
IO (Ptr DOMHTMLHeadElement)
dOMDocumentGetHead ::
(MonadIO m, DOMDocumentK a) =>
a ->
m DOMHTMLHeadElement
dOMDocumentGetHead _obj = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
result <- webkit_dom_document_get_head _obj'
checkUnexpectedReturnNULL "webkit_dom_document_get_head" result
result' <- (newObject DOMHTMLHeadElement) result
touchManagedPtr _obj
return result'
foreign import ccall "webkit_dom_document_get_images" webkit_dom_document_get_images ::
Ptr DOMDocument ->
IO (Ptr DOMHTMLCollection)
dOMDocumentGetImages ::
(MonadIO m, DOMDocumentK a) =>
a ->
m DOMHTMLCollection
dOMDocumentGetImages _obj = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
result <- webkit_dom_document_get_images _obj'
checkUnexpectedReturnNULL "webkit_dom_document_get_images" result
result' <- (wrapObject DOMHTMLCollection) result
touchManagedPtr _obj
return result'
foreign import ccall "webkit_dom_document_get_implementation" webkit_dom_document_get_implementation ::
Ptr DOMDocument ->
IO (Ptr DOMDOMImplementation)
dOMDocumentGetImplementation ::
(MonadIO m, DOMDocumentK a) =>
a ->
m DOMDOMImplementation
dOMDocumentGetImplementation _obj = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
result <- webkit_dom_document_get_implementation _obj'
checkUnexpectedReturnNULL "webkit_dom_document_get_implementation" result
result' <- (wrapObject DOMDOMImplementation) result
touchManagedPtr _obj
return result'
foreign import ccall "webkit_dom_document_get_input_encoding" webkit_dom_document_get_input_encoding ::
Ptr DOMDocument ->
IO CString
dOMDocumentGetInputEncoding ::
(MonadIO m, DOMDocumentK a) =>
a ->
m T.Text
dOMDocumentGetInputEncoding _obj = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
result <- webkit_dom_document_get_input_encoding _obj'
checkUnexpectedReturnNULL "webkit_dom_document_get_input_encoding" result
result' <- cstringToText result
freeMem result
touchManagedPtr _obj
return result'
foreign import ccall "webkit_dom_document_get_last_modified" webkit_dom_document_get_last_modified ::
Ptr DOMDocument ->
IO CString
dOMDocumentGetLastModified ::
(MonadIO m, DOMDocumentK a) =>
a ->
m T.Text
dOMDocumentGetLastModified _obj = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
result <- webkit_dom_document_get_last_modified _obj'
checkUnexpectedReturnNULL "webkit_dom_document_get_last_modified" result
result' <- cstringToText result
freeMem result
touchManagedPtr _obj
return result'
foreign import ccall "webkit_dom_document_get_links" webkit_dom_document_get_links ::
Ptr DOMDocument ->
IO (Ptr DOMHTMLCollection)
dOMDocumentGetLinks ::
(MonadIO m, DOMDocumentK a) =>
a ->
m DOMHTMLCollection
dOMDocumentGetLinks _obj = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
result <- webkit_dom_document_get_links _obj'
checkUnexpectedReturnNULL "webkit_dom_document_get_links" result
result' <- (wrapObject DOMHTMLCollection) result
touchManagedPtr _obj
return result'
foreign import ccall "webkit_dom_document_get_override_style" webkit_dom_document_get_override_style ::
Ptr DOMDocument ->
Ptr DOMElement ->
CString ->
IO (Ptr DOMCSSStyleDeclaration)
dOMDocumentGetOverrideStyle ::
(MonadIO m, DOMDocumentK a, DOMElementK b) =>
a ->
b ->
Maybe (T.Text) ->
m DOMCSSStyleDeclaration
dOMDocumentGetOverrideStyle _obj element pseudoElement = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
let element' = unsafeManagedPtrCastPtr element
maybePseudoElement <- case pseudoElement of
Nothing -> return nullPtr
Just jPseudoElement -> do
jPseudoElement' <- textToCString jPseudoElement
return jPseudoElement'
result <- webkit_dom_document_get_override_style _obj' element' maybePseudoElement
checkUnexpectedReturnNULL "webkit_dom_document_get_override_style" result
result' <- (wrapObject DOMCSSStyleDeclaration) result
touchManagedPtr _obj
touchManagedPtr element
freeMem maybePseudoElement
return result'
foreign import ccall "webkit_dom_document_get_preferred_stylesheet_set" webkit_dom_document_get_preferred_stylesheet_set ::
Ptr DOMDocument ->
IO CString
dOMDocumentGetPreferredStylesheetSet ::
(MonadIO m, DOMDocumentK a) =>
a ->
m T.Text
dOMDocumentGetPreferredStylesheetSet _obj = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
result <- webkit_dom_document_get_preferred_stylesheet_set _obj'
checkUnexpectedReturnNULL "webkit_dom_document_get_preferred_stylesheet_set" result
result' <- cstringToText result
freeMem result
touchManagedPtr _obj
return result'
foreign import ccall "webkit_dom_document_get_ready_state" webkit_dom_document_get_ready_state ::
Ptr DOMDocument ->
IO CString
dOMDocumentGetReadyState ::
(MonadIO m, DOMDocumentK a) =>
a ->
m T.Text
dOMDocumentGetReadyState _obj = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
result <- webkit_dom_document_get_ready_state _obj'
checkUnexpectedReturnNULL "webkit_dom_document_get_ready_state" result
result' <- cstringToText result
freeMem result
touchManagedPtr _obj
return result'
foreign import ccall "webkit_dom_document_get_referrer" webkit_dom_document_get_referrer ::
Ptr DOMDocument ->
IO CString
dOMDocumentGetReferrer ::
(MonadIO m, DOMDocumentK a) =>
a ->
m T.Text
dOMDocumentGetReferrer _obj = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
result <- webkit_dom_document_get_referrer _obj'
checkUnexpectedReturnNULL "webkit_dom_document_get_referrer" result
result' <- cstringToText result
freeMem result
touchManagedPtr _obj
return result'
foreign import ccall "webkit_dom_document_get_selected_stylesheet_set" webkit_dom_document_get_selected_stylesheet_set ::
Ptr DOMDocument ->
IO CString
dOMDocumentGetSelectedStylesheetSet ::
(MonadIO m, DOMDocumentK a) =>
a ->
m T.Text
dOMDocumentGetSelectedStylesheetSet _obj = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
result <- webkit_dom_document_get_selected_stylesheet_set _obj'
checkUnexpectedReturnNULL "webkit_dom_document_get_selected_stylesheet_set" result
result' <- cstringToText result
freeMem result
touchManagedPtr _obj
return result'
foreign import ccall "webkit_dom_document_get_style_sheets" webkit_dom_document_get_style_sheets ::
Ptr DOMDocument ->
IO (Ptr DOMStyleSheetList)
dOMDocumentGetStyleSheets ::
(MonadIO m, DOMDocumentK a) =>
a ->
m DOMStyleSheetList
dOMDocumentGetStyleSheets _obj = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
result <- webkit_dom_document_get_style_sheets _obj'
checkUnexpectedReturnNULL "webkit_dom_document_get_style_sheets" result
result' <- (newObject DOMStyleSheetList) result
touchManagedPtr _obj
return result'
foreign import ccall "webkit_dom_document_get_title" webkit_dom_document_get_title ::
Ptr DOMDocument ->
IO CString
dOMDocumentGetTitle ::
(MonadIO m, DOMDocumentK a) =>
a ->
m T.Text
dOMDocumentGetTitle _obj = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
result <- webkit_dom_document_get_title _obj'
checkUnexpectedReturnNULL "webkit_dom_document_get_title" result
result' <- cstringToText result
freeMem result
touchManagedPtr _obj
return result'
foreign import ccall "webkit_dom_document_get_url" webkit_dom_document_get_url ::
Ptr DOMDocument ->
IO CString
dOMDocumentGetUrl ::
(MonadIO m, DOMDocumentK a) =>
a ->
m T.Text
dOMDocumentGetUrl _obj = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
result <- webkit_dom_document_get_url _obj'
checkUnexpectedReturnNULL "webkit_dom_document_get_url" result
result' <- cstringToText result
freeMem result
touchManagedPtr _obj
return result'
foreign import ccall "webkit_dom_document_get_xml_encoding" webkit_dom_document_get_xml_encoding ::
Ptr DOMDocument ->
IO CString
dOMDocumentGetXmlEncoding ::
(MonadIO m, DOMDocumentK a) =>
a ->
m T.Text
dOMDocumentGetXmlEncoding _obj = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
result <- webkit_dom_document_get_xml_encoding _obj'
checkUnexpectedReturnNULL "webkit_dom_document_get_xml_encoding" result
result' <- cstringToText result
freeMem result
touchManagedPtr _obj
return result'
foreign import ccall "webkit_dom_document_get_xml_standalone" webkit_dom_document_get_xml_standalone ::
Ptr DOMDocument ->
IO CInt
dOMDocumentGetXmlStandalone ::
(MonadIO m, DOMDocumentK a) =>
a ->
m Bool
dOMDocumentGetXmlStandalone _obj = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
result <- webkit_dom_document_get_xml_standalone _obj'
let result' = (/= 0) result
touchManagedPtr _obj
return result'
foreign import ccall "webkit_dom_document_get_xml_version" webkit_dom_document_get_xml_version ::
Ptr DOMDocument ->
IO CString
dOMDocumentGetXmlVersion ::
(MonadIO m, DOMDocumentK a) =>
a ->
m T.Text
dOMDocumentGetXmlVersion _obj = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
result <- webkit_dom_document_get_xml_version _obj'
checkUnexpectedReturnNULL "webkit_dom_document_get_xml_version" result
result' <- cstringToText result
freeMem result
touchManagedPtr _obj
return result'
foreign import ccall "webkit_dom_document_has_focus" webkit_dom_document_has_focus ::
Ptr DOMDocument ->
IO CInt
dOMDocumentHasFocus ::
(MonadIO m, DOMDocumentK a) =>
a ->
m Bool
dOMDocumentHasFocus _obj = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
result <- webkit_dom_document_has_focus _obj'
let result' = (/= 0) result
touchManagedPtr _obj
return result'
foreign import ccall "webkit_dom_document_import_node" webkit_dom_document_import_node ::
Ptr DOMDocument ->
Ptr DOMNode ->
CInt ->
Ptr (Ptr GError) ->
IO (Ptr DOMNode)
dOMDocumentImportNode ::
(MonadIO m, DOMDocumentK a, DOMNodeK b) =>
a ->
b ->
Bool ->
m DOMNode
dOMDocumentImportNode _obj importedNode deep = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
let importedNode' = unsafeManagedPtrCastPtr importedNode
let deep' = (fromIntegral . fromEnum) deep
onException (do
result <- propagateGError $ webkit_dom_document_import_node _obj' importedNode' deep'
checkUnexpectedReturnNULL "webkit_dom_document_import_node" result
result' <- (newObject DOMNode) result
touchManagedPtr _obj
touchManagedPtr importedNode
return result'
) (do
return ()
)
foreign import ccall "webkit_dom_document_query_command_enabled" webkit_dom_document_query_command_enabled ::
Ptr DOMDocument ->
CString ->
IO CInt
dOMDocumentQueryCommandEnabled ::
(MonadIO m, DOMDocumentK a) =>
a ->
T.Text ->
m Bool
dOMDocumentQueryCommandEnabled _obj command = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
command' <- textToCString command
result <- webkit_dom_document_query_command_enabled _obj' command'
let result' = (/= 0) result
touchManagedPtr _obj
freeMem command'
return result'
foreign import ccall "webkit_dom_document_query_command_indeterm" webkit_dom_document_query_command_indeterm ::
Ptr DOMDocument ->
CString ->
IO CInt
dOMDocumentQueryCommandIndeterm ::
(MonadIO m, DOMDocumentK a) =>
a ->
T.Text ->
m Bool
dOMDocumentQueryCommandIndeterm _obj command = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
command' <- textToCString command
result <- webkit_dom_document_query_command_indeterm _obj' command'
let result' = (/= 0) result
touchManagedPtr _obj
freeMem command'
return result'
foreign import ccall "webkit_dom_document_query_command_state" webkit_dom_document_query_command_state ::
Ptr DOMDocument ->
CString ->
IO CInt
dOMDocumentQueryCommandState ::
(MonadIO m, DOMDocumentK a) =>
a ->
T.Text ->
m Bool
dOMDocumentQueryCommandState _obj command = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
command' <- textToCString command
result <- webkit_dom_document_query_command_state _obj' command'
let result' = (/= 0) result
touchManagedPtr _obj
freeMem command'
return result'
foreign import ccall "webkit_dom_document_query_command_supported" webkit_dom_document_query_command_supported ::
Ptr DOMDocument ->
CString ->
IO CInt
dOMDocumentQueryCommandSupported ::
(MonadIO m, DOMDocumentK a) =>
a ->
T.Text ->
m Bool
dOMDocumentQueryCommandSupported _obj command = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
command' <- textToCString command
result <- webkit_dom_document_query_command_supported _obj' command'
let result' = (/= 0) result
touchManagedPtr _obj
freeMem command'
return result'
foreign import ccall "webkit_dom_document_query_command_value" webkit_dom_document_query_command_value ::
Ptr DOMDocument ->
CString ->
IO CString
dOMDocumentQueryCommandValue ::
(MonadIO m, DOMDocumentK a) =>
a ->
T.Text ->
m T.Text
dOMDocumentQueryCommandValue _obj command = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
command' <- textToCString command
result <- webkit_dom_document_query_command_value _obj' command'
checkUnexpectedReturnNULL "webkit_dom_document_query_command_value" result
result' <- cstringToText result
freeMem result
touchManagedPtr _obj
freeMem command'
return result'
foreign import ccall "webkit_dom_document_query_selector" webkit_dom_document_query_selector ::
Ptr DOMDocument ->
CString ->
Ptr (Ptr GError) ->
IO (Ptr DOMElement)
dOMDocumentQuerySelector ::
(MonadIO m, DOMDocumentK a) =>
a ->
T.Text ->
m DOMElement
dOMDocumentQuerySelector _obj selectors = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
selectors' <- textToCString selectors
onException (do
result <- propagateGError $ webkit_dom_document_query_selector _obj' selectors'
checkUnexpectedReturnNULL "webkit_dom_document_query_selector" result
result' <- (newObject DOMElement) result
touchManagedPtr _obj
freeMem selectors'
return result'
) (do
freeMem selectors'
)
foreign import ccall "webkit_dom_document_query_selector_all" webkit_dom_document_query_selector_all ::
Ptr DOMDocument ->
CString ->
Ptr (Ptr GError) ->
IO (Ptr DOMNodeList)
dOMDocumentQuerySelectorAll ::
(MonadIO m, DOMDocumentK a) =>
a ->
T.Text ->
m DOMNodeList
dOMDocumentQuerySelectorAll _obj selectors = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
selectors' <- textToCString selectors
onException (do
result <- propagateGError $ webkit_dom_document_query_selector_all _obj' selectors'
checkUnexpectedReturnNULL "webkit_dom_document_query_selector_all" result
result' <- (wrapObject DOMNodeList) result
touchManagedPtr _obj
freeMem selectors'
return result'
) (do
freeMem selectors'
)
foreign import ccall "webkit_dom_document_set_body" webkit_dom_document_set_body ::
Ptr DOMDocument ->
Ptr DOMHTMLElement ->
Ptr (Ptr GError) ->
IO ()
dOMDocumentSetBody ::
(MonadIO m, DOMDocumentK a, DOMHTMLElementK b) =>
a ->
b ->
m ()
dOMDocumentSetBody _obj value = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
let value' = unsafeManagedPtrCastPtr value
onException (do
propagateGError $ webkit_dom_document_set_body _obj' value'
touchManagedPtr _obj
touchManagedPtr value
return ()
) (do
return ()
)
foreign import ccall "webkit_dom_document_set_charset" webkit_dom_document_set_charset ::
Ptr DOMDocument ->
CString ->
IO ()
dOMDocumentSetCharset ::
(MonadIO m, DOMDocumentK a) =>
a ->
T.Text ->
m ()
dOMDocumentSetCharset _obj value = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
value' <- textToCString value
webkit_dom_document_set_charset _obj' value'
touchManagedPtr _obj
freeMem value'
return ()
foreign import ccall "webkit_dom_document_set_cookie" webkit_dom_document_set_cookie ::
Ptr DOMDocument ->
CString ->
Ptr (Ptr GError) ->
IO ()
dOMDocumentSetCookie ::
(MonadIO m, DOMDocumentK a) =>
a ->
T.Text ->
m ()
dOMDocumentSetCookie _obj value = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
value' <- textToCString value
onException (do
propagateGError $ webkit_dom_document_set_cookie _obj' value'
touchManagedPtr _obj
freeMem value'
return ()
) (do
freeMem value'
)
foreign import ccall "webkit_dom_document_set_document_uri" webkit_dom_document_set_document_uri ::
Ptr DOMDocument ->
CString ->
IO ()
dOMDocumentSetDocumentUri ::
(MonadIO m, DOMDocumentK a) =>
a ->
T.Text ->
m ()
dOMDocumentSetDocumentUri _obj value = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
value' <- textToCString value
webkit_dom_document_set_document_uri _obj' value'
touchManagedPtr _obj
freeMem value'
return ()
foreign import ccall "webkit_dom_document_set_selected_stylesheet_set" webkit_dom_document_set_selected_stylesheet_set ::
Ptr DOMDocument ->
CString ->
IO ()
dOMDocumentSetSelectedStylesheetSet ::
(MonadIO m, DOMDocumentK a) =>
a ->
T.Text ->
m ()
dOMDocumentSetSelectedStylesheetSet _obj value = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
value' <- textToCString value
webkit_dom_document_set_selected_stylesheet_set _obj' value'
touchManagedPtr _obj
freeMem value'
return ()
foreign import ccall "webkit_dom_document_set_title" webkit_dom_document_set_title ::
Ptr DOMDocument ->
CString ->
IO ()
dOMDocumentSetTitle ::
(MonadIO m, DOMDocumentK a) =>
a ->
T.Text ->
m ()
dOMDocumentSetTitle _obj value = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
value' <- textToCString value
webkit_dom_document_set_title _obj' value'
touchManagedPtr _obj
freeMem value'
return ()
foreign import ccall "webkit_dom_document_set_xml_standalone" webkit_dom_document_set_xml_standalone ::
Ptr DOMDocument ->
CInt ->
Ptr (Ptr GError) ->
IO ()
dOMDocumentSetXmlStandalone ::
(MonadIO m, DOMDocumentK a) =>
a ->
Bool ->
m ()
dOMDocumentSetXmlStandalone _obj value = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
let value' = (fromIntegral . fromEnum) value
onException (do
propagateGError $ webkit_dom_document_set_xml_standalone _obj' value'
touchManagedPtr _obj
return ()
) (do
return ()
)
foreign import ccall "webkit_dom_document_set_xml_version" webkit_dom_document_set_xml_version ::
Ptr DOMDocument ->
CString ->
Ptr (Ptr GError) ->
IO ()
dOMDocumentSetXmlVersion ::
(MonadIO m, DOMDocumentK a) =>
a ->
T.Text ->
m ()
dOMDocumentSetXmlVersion _obj value = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
value' <- textToCString value
onException (do
propagateGError $ webkit_dom_document_set_xml_version _obj' value'
touchManagedPtr _obj
freeMem value'
return ()
) (do
freeMem value'
)