module Graphics.UI.Gtk.WebKit.DOM.Document
(documentCreateElement, documentCreateDocumentFragment,
documentCreateTextNode, documentCreateComment,
documentCreateCDATASection, documentCreateProcessingInstruction,
documentCreateAttribute, documentCreateEntityReference,
documentGetElementsByTagName, documentImportNode,
documentCreateElementNS, documentCreateAttributeNS,
documentGetElementsByTagNameNS, documentGetElementById,
documentAdoptNode, documentCreateEvent, documentCreateRange,
documentCreateNodeIterator, documentCreateTreeWalker,
documentGetOverrideStyle, documentCreateExpression,
documentCreateNSResolver, documentEvaluate, documentExecCommand,
documentQueryCommandEnabled, documentQueryCommandIndeterm,
documentQueryCommandState, documentQueryCommandSupported,
documentQueryCommandValue, documentGetElementsByName,
documentElementFromPoint, documentCaretRangeFromPoint,
documentCreateCSSStyleDeclaration, documentGetElementsByClassName,
documentQuerySelector, documentQuerySelectorAll,
documentWebkitExitPointerLock, documentWebkitGetNamedFlows,
documentGetDoctype, documentGetImplementation,
documentGetDocumentElement, documentGetInputEncoding,
documentGetXmlEncoding, documentSetXmlVersion,
documentGetXmlVersion, documentSetXmlStandalone,
documentGetXmlStandalone, documentSetDocumentURI,
documentGetDocumentURI, documentGetDefaultView,
documentGetStyleSheets, documentSetTitle, documentGetTitle,
documentGetReferrer, documentGetDomain, documentSetCookie,
documentGetCookie, documentSetBody, documentGetBody,
documentGetHead, documentGetImages, documentGetApplets,
documentGetLinks, documentGetForms, documentGetAnchors,
documentGetLastModified, documentSetCharset, documentGetCharset,
documentGetDefaultCharset, documentGetReadyState,
documentGetCharacterSet, documentGetPreferredStylesheetSet,
documentSetSelectedStylesheetSet, documentGetSelectedStylesheetSet,
documentGetCompatMode,
documentGetWebkitPointerLockElement,
documentOnabort, documentOnblur, documentOnchange, documentOnclick,
documentOncontextmenu, documentOndblclick, documentOndrag,
documentOndragend, documentOndragenter, documentOndragleave,
documentOndragover, documentOndragstart, documentOndrop,
documentOnerror, documentOnfocus, documentOninput,
documentOninvalid, documentOnkeydown, documentOnkeypress,
documentOnkeyup, documentOnload, documentOnmousedown,
documentOnmouseenter, documentOnmouseleave,
documentOnmousemove, documentOnmouseout, documentOnmouseover,
documentOnmouseup, documentOnmousewheel,
documentOnreadystatechange, documentOnscroll, documentOnselect,
documentOnsubmit, documentOnbeforecut, documentOncut,
documentOnbeforecopy, documentOncopy, documentOnbeforepaste,
documentOnpaste, documentOnreset, documentOnsearch,
documentOnselectstart, documentOnselectionchange,
documentOntouchstart, documentOntouchmove, documentOntouchend,
documentOntouchcancel, documentOnwebkitfullscreenchange,
documentOnwebkitfullscreenerror,
documentOnwebkitpointerlockchange, documentOnwebkitpointerlockerror,
documentOnsecuritypolicyviolation,
documentGetVisibilityState,
documentGetHidden,
documentGetSecurityPolicy,
documentGetCurrentScript,
Document, DocumentClass, castToDocument, gTypeDocument, toDocument)
where
import System.Glib.FFI
import System.Glib.UTFString
import Control.Applicative
import Graphics.UI.Gtk.WebKit.Types
import System.Glib.GError
import Graphics.UI.Gtk.WebKit.DOM.EventM
documentCreateElement ::
(DocumentClass self, GlibString string) =>
self -> string -> IO (Maybe Element)
documentCreateElement self tagName
= maybeNull (makeNewGObject mkElement)
(propagateGError $
\ errorPtr_ ->
withUTFString tagName $
\ tagNamePtr ->
(\(Document arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_create_element argPtr1 arg2 arg3) (toDocument self)
tagNamePtr
errorPtr_)
documentCreateDocumentFragment ::
(DocumentClass self) => self -> IO (Maybe DocumentFragment)
documentCreateDocumentFragment self
= maybeNull (makeNewGObject mkDocumentFragment)
((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_create_document_fragment argPtr1)
(toDocument self))
documentCreateTextNode ::
(DocumentClass self, GlibString string) =>
self -> string -> IO (Maybe Text)
documentCreateTextNode self data'
= maybeNull (makeNewGObject mkText)
(withUTFString data' $
\ dataPtr ->
(\(Document arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_create_text_node argPtr1 arg2) (toDocument self)
dataPtr)
documentCreateComment ::
(DocumentClass self, GlibString string) =>
self -> string -> IO (Maybe Comment)
documentCreateComment self data'
= maybeNull (makeNewGObject mkComment)
(withUTFString data' $
\ dataPtr ->
(\(Document arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_create_comment argPtr1 arg2) (toDocument self)
dataPtr)
documentCreateCDATASection ::
(DocumentClass self, GlibString string) =>
self -> string -> IO (Maybe CDATASection)
documentCreateCDATASection self data'
= maybeNull (makeNewGObject mkCDATASection)
(propagateGError $
\ errorPtr_ ->
withUTFString data' $
\ dataPtr ->
(\(Document arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_create_cdata_section argPtr1 arg2 arg3)
(toDocument self)
dataPtr
errorPtr_)
documentCreateProcessingInstruction ::
(DocumentClass self, GlibString string) =>
self -> string -> string -> IO (Maybe ProcessingInstruction)
documentCreateProcessingInstruction self target data'
= maybeNull (makeNewGObject mkProcessingInstruction)
(propagateGError $
\ errorPtr_ ->
withUTFString data' $
\ dataPtr ->
withUTFString target $
\ targetPtr ->
(\(Document arg1) arg2 arg3 arg4 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_create_processing_instruction argPtr1 arg2 arg3 arg4)
(toDocument self)
targetPtr
dataPtr
errorPtr_)
documentCreateAttribute ::
(DocumentClass self, GlibString string) =>
self -> string -> IO (Maybe DOMAttr)
documentCreateAttribute self name
= maybeNull (makeNewGObject mkDOMAttr)
(propagateGError $
\ errorPtr_ ->
withUTFString name $
\ namePtr ->
(\(Document arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_create_attribute argPtr1 arg2 arg3) (toDocument self)
namePtr
errorPtr_)
documentCreateEntityReference ::
(DocumentClass self, GlibString string) =>
self -> string -> IO (Maybe EntityReference)
documentCreateEntityReference self name
= maybeNull (makeNewGObject mkEntityReference)
(propagateGError $
\ errorPtr_ ->
withUTFString name $
\ namePtr ->
(\(Document arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_create_entity_reference argPtr1 arg2 arg3)
(toDocument self)
namePtr
errorPtr_)
documentGetElementsByTagName ::
(DocumentClass self, GlibString string) =>
self -> string -> IO (Maybe NodeList)
documentGetElementsByTagName self tagname
= maybeNull (makeNewGObject mkNodeList)
(withUTFString tagname $
\ tagnamePtr ->
(\(Document arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_elements_by_tag_name argPtr1 arg2)
(toDocument self)
tagnamePtr)
documentImportNode ::
(DocumentClass self, NodeClass importedNode) =>
self -> Maybe importedNode -> Bool -> IO (Maybe Node)
documentImportNode self importedNode deep
= maybeNull (makeNewGObject mkNode)
(propagateGError $
\ errorPtr_ ->
(\(Document arg1) (Node arg2) arg3 arg4 -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->webkit_dom_document_import_node argPtr1 argPtr2 arg3 arg4) (toDocument self)
(maybe (Node nullForeignPtr) toNode importedNode)
(fromBool deep)
errorPtr_)
documentCreateElementNS ::
(DocumentClass self, GlibString string) =>
self -> string -> string -> IO (Maybe Element)
documentCreateElementNS self namespaceURI qualifiedName
= maybeNull (makeNewGObject mkElement)
(propagateGError $
\ errorPtr_ ->
withUTFString qualifiedName $
\ qualifiedNamePtr ->
withUTFString namespaceURI $
\ namespaceURIPtr ->
(\(Document arg1) arg2 arg3 arg4 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_create_element_ns argPtr1 arg2 arg3 arg4) (toDocument self)
namespaceURIPtr
qualifiedNamePtr
errorPtr_)
documentCreateAttributeNS ::
(DocumentClass self, GlibString string) =>
self -> string -> string -> IO (Maybe DOMAttr)
documentCreateAttributeNS self namespaceURI qualifiedName
= maybeNull (makeNewGObject mkDOMAttr)
(propagateGError $
\ errorPtr_ ->
withUTFString qualifiedName $
\ qualifiedNamePtr ->
withUTFString namespaceURI $
\ namespaceURIPtr ->
(\(Document arg1) arg2 arg3 arg4 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_create_attribute_ns argPtr1 arg2 arg3 arg4)
(toDocument self)
namespaceURIPtr
qualifiedNamePtr
errorPtr_)
documentGetElementsByTagNameNS ::
(DocumentClass self, GlibString string) =>
self -> string -> string -> IO (Maybe NodeList)
documentGetElementsByTagNameNS self namespaceURI localName
= maybeNull (makeNewGObject mkNodeList)
(withUTFString localName $
\ localNamePtr ->
withUTFString namespaceURI $
\ namespaceURIPtr ->
(\(Document arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_elements_by_tag_name_ns argPtr1 arg2 arg3)
(toDocument self)
namespaceURIPtr
localNamePtr)
documentGetElementById ::
(DocumentClass self, GlibString string) =>
self -> string -> IO (Maybe Element)
documentGetElementById self elementId
= maybeNull (makeNewGObject mkElement)
(withUTFString elementId $
\ elementIdPtr ->
(\(Document arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_element_by_id argPtr1 arg2) (toDocument self)
elementIdPtr)
documentAdoptNode ::
(DocumentClass self, NodeClass source) =>
self -> Maybe source -> IO (Maybe Node)
documentAdoptNode self source
= maybeNull (makeNewGObject mkNode)
(propagateGError $
\ errorPtr_ ->
(\(Document arg1) (Node arg2) arg3 -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->webkit_dom_document_adopt_node argPtr1 argPtr2 arg3) (toDocument self)
(maybe (Node nullForeignPtr) toNode source)
errorPtr_)
documentCreateEvent ::
(DocumentClass self, GlibString string) =>
self -> string -> IO (Maybe Event)
documentCreateEvent self eventType
= maybeNull (makeNewGObject mkEvent)
(propagateGError $
\ errorPtr_ ->
withUTFString eventType $
\ eventTypePtr ->
(\(Document arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_create_event argPtr1 arg2 arg3) (toDocument self)
eventTypePtr
errorPtr_)
documentCreateRange ::
(DocumentClass self) => self -> IO (Maybe DOMRange)
documentCreateRange self
= maybeNull (makeNewGObject mkDOMRange)
((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_create_range argPtr1) (toDocument self))
documentCreateNodeIterator ::
(DocumentClass self, NodeClass root, NodeFilterClass filter) =>
self ->
Maybe root ->
Word -> Maybe filter -> Bool -> IO (Maybe NodeIterator)
documentCreateNodeIterator self root whatToShow filter
expandEntityReferences
= maybeNull (makeNewGObject mkNodeIterator)
(propagateGError $
\ errorPtr_ ->
(\(Document arg1) (Node arg2) arg3 (NodeFilter arg4) arg5 arg6 -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->withForeignPtr arg4 $ \argPtr4 ->webkit_dom_document_create_node_iterator argPtr1 argPtr2 arg3 argPtr4 arg5 arg6)
(toDocument self)
(maybe (Node nullForeignPtr) toNode root)
(fromIntegral whatToShow)
(maybe (NodeFilter nullForeignPtr) toNodeFilter filter)
(fromBool expandEntityReferences)
errorPtr_)
documentCreateTreeWalker ::
(DocumentClass self, NodeClass root, NodeFilterClass filter) =>
self ->
Maybe root -> Word -> Maybe filter -> Bool -> IO (Maybe TreeWalker)
documentCreateTreeWalker self root whatToShow filter
expandEntityReferences
= maybeNull (makeNewGObject mkTreeWalker)
(propagateGError $
\ errorPtr_ ->
(\(Document arg1) (Node arg2) arg3 (NodeFilter arg4) arg5 arg6 -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->withForeignPtr arg4 $ \argPtr4 ->webkit_dom_document_create_tree_walker argPtr1 argPtr2 arg3 argPtr4 arg5 arg6) (toDocument self)
(maybe (Node nullForeignPtr) toNode root)
(fromIntegral whatToShow)
(maybe (NodeFilter nullForeignPtr) toNodeFilter filter)
(fromBool expandEntityReferences)
errorPtr_)
documentGetOverrideStyle ::
(DocumentClass self, ElementClass element, GlibString string) =>
self -> Maybe element -> string -> IO (Maybe CSSStyleDeclaration)
documentGetOverrideStyle self element pseudoElement
= maybeNull (makeNewGObject mkCSSStyleDeclaration)
(withUTFString pseudoElement $
\ pseudoElementPtr ->
(\(Document arg1) (Element arg2) arg3 -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->webkit_dom_document_get_override_style argPtr1 argPtr2 arg3) (toDocument self)
(maybe (Element nullForeignPtr) toElement element)
pseudoElementPtr)
documentCreateExpression ::
(DocumentClass self, XPathNSResolverClass resolver,
GlibString string) =>
self -> string -> Maybe resolver -> IO (Maybe XPathExpression)
documentCreateExpression self expression resolver
= maybeNull (makeNewGObject mkXPathExpression)
(propagateGError $
\ errorPtr_ ->
withUTFString expression $
\ expressionPtr ->
(\(Document arg1) arg2 (XPathNSResolver arg3) arg4 -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg3 $ \argPtr3 ->webkit_dom_document_create_expression argPtr1 arg2 argPtr3 arg4) (toDocument self)
expressionPtr
(maybe (XPathNSResolver nullForeignPtr) toXPathNSResolver resolver)
errorPtr_)
documentCreateNSResolver ::
(DocumentClass self, NodeClass nodeResolver) =>
self -> Maybe nodeResolver -> IO (Maybe XPathNSResolver)
documentCreateNSResolver self nodeResolver
= maybeNull (makeNewGObject mkXPathNSResolver)
((\(Document arg1) (Node arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->webkit_dom_document_create_ns_resolver argPtr1 argPtr2)
(toDocument self)
(maybe (Node nullForeignPtr) toNode nodeResolver))
documentEvaluate ::
(DocumentClass self, NodeClass contextNode,
XPathNSResolverClass resolver, XPathResultClass inResult,
GlibString string) =>
self ->
string ->
Maybe contextNode ->
Maybe resolver -> Word -> Maybe inResult -> IO (Maybe XPathResult)
documentEvaluate self expression contextNode resolver type'
inResult
= maybeNull (makeNewGObject mkXPathResult)
(propagateGError $
\ errorPtr_ ->
withUTFString expression $
\ expressionPtr ->
(\(Document arg1) arg2 (Node arg3) (XPathNSResolver arg4) arg5 (XPathResult arg6) arg7 -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg3 $ \argPtr3 ->withForeignPtr arg4 $ \argPtr4 ->withForeignPtr arg6 $ \argPtr6 ->webkit_dom_document_evaluate argPtr1 arg2 argPtr3 argPtr4 arg5 argPtr6 arg7) (toDocument self)
expressionPtr
(maybe (Node nullForeignPtr) toNode contextNode)
(maybe (XPathNSResolver nullForeignPtr) toXPathNSResolver resolver)
(fromIntegral type')
(maybe (XPathResult nullForeignPtr) toXPathResult inResult)
errorPtr_)
documentExecCommand ::
(DocumentClass self, GlibString string) =>
self -> string -> Bool -> string -> IO Bool
documentExecCommand self command userInterface value
= toBool <$>
(withUTFString value $
\ valuePtr ->
withUTFString command $
\ commandPtr ->
(\(Document arg1) arg2 arg3 arg4 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_exec_command argPtr1 arg2 arg3 arg4) (toDocument self)
commandPtr
(fromBool userInterface)
valuePtr)
documentQueryCommandEnabled ::
(DocumentClass self, GlibString string) =>
self -> string -> IO Bool
documentQueryCommandEnabled self command
= toBool <$>
(withUTFString command $
\ commandPtr ->
(\(Document arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_query_command_enabled argPtr1 arg2)
(toDocument self)
commandPtr)
documentQueryCommandIndeterm ::
(DocumentClass self, GlibString string) =>
self -> string -> IO Bool
documentQueryCommandIndeterm self command
= toBool <$>
(withUTFString command $
\ commandPtr ->
(\(Document arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_query_command_indeterm argPtr1 arg2)
(toDocument self)
commandPtr)
documentQueryCommandState ::
(DocumentClass self, GlibString string) =>
self -> string -> IO Bool
documentQueryCommandState self command
= toBool <$>
(withUTFString command $
\ commandPtr ->
(\(Document arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_query_command_state argPtr1 arg2)
(toDocument self)
commandPtr)
documentQueryCommandSupported ::
(DocumentClass self, GlibString string) =>
self -> string -> IO Bool
documentQueryCommandSupported self command
= toBool <$>
(withUTFString command $
\ commandPtr ->
(\(Document arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_query_command_supported argPtr1 arg2)
(toDocument self)
commandPtr)
documentQueryCommandValue ::
(DocumentClass self, GlibString string) =>
self -> string -> IO string
documentQueryCommandValue self command
= (withUTFString command $
\ commandPtr ->
(\(Document arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_query_command_value argPtr1 arg2)
(toDocument self)
commandPtr)
>>=
readUTFString
documentGetElementsByName ::
(DocumentClass self, GlibString string) =>
self -> string -> IO (Maybe NodeList)
documentGetElementsByName self elementName
= maybeNull (makeNewGObject mkNodeList)
(withUTFString elementName $
\ elementNamePtr ->
(\(Document arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_elements_by_name argPtr1 arg2)
(toDocument self)
elementNamePtr)
documentElementFromPoint ::
(DocumentClass self) => self -> Int -> Int -> IO (Maybe Element)
documentElementFromPoint self x y
= maybeNull (makeNewGObject mkElement)
((\(Document arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_element_from_point argPtr1 arg2 arg3)
(toDocument self)
(fromIntegral x)
(fromIntegral y))
documentCaretRangeFromPoint ::
(DocumentClass self) => self -> Int -> Int -> IO (Maybe DOMRange)
documentCaretRangeFromPoint self x y
= maybeNull (makeNewGObject mkDOMRange)
((\(Document arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_caret_range_from_point argPtr1 arg2 arg3)
(toDocument self)
(fromIntegral x)
(fromIntegral y))
documentCreateCSSStyleDeclaration ::
(DocumentClass self) => self -> IO (Maybe CSSStyleDeclaration)
documentCreateCSSStyleDeclaration self
= maybeNull (makeNewGObject mkCSSStyleDeclaration)
((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_create_css_style_declaration argPtr1)
(toDocument self))
documentGetElementsByClassName ::
(DocumentClass self, GlibString string) =>
self -> string -> IO (Maybe NodeList)
documentGetElementsByClassName self tagname
= maybeNull (makeNewGObject mkNodeList)
(withUTFString tagname $
\ tagnamePtr ->
(\(Document arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_elements_by_class_name argPtr1 arg2)
(toDocument self)
tagnamePtr)
documentQuerySelector ::
(DocumentClass self, GlibString string) =>
self -> string -> IO (Maybe Element)
documentQuerySelector self selectors
= maybeNull (makeNewGObject mkElement)
(propagateGError $
\ errorPtr_ ->
withUTFString selectors $
\ selectorsPtr ->
(\(Document arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_query_selector argPtr1 arg2 arg3) (toDocument self)
selectorsPtr
errorPtr_)
documentQuerySelectorAll ::
(DocumentClass self, GlibString string) =>
self -> string -> IO (Maybe NodeList)
documentQuerySelectorAll self selectors
= maybeNull (makeNewGObject mkNodeList)
(propagateGError $
\ errorPtr_ ->
withUTFString selectors $
\ selectorsPtr ->
(\(Document arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_query_selector_all argPtr1 arg2 arg3) (toDocument self)
selectorsPtr
errorPtr_)
documentWebkitExitPointerLock ::
(DocumentClass self) => self -> IO ()
documentWebkitExitPointerLock self
= (\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_webkit_exit_pointer_lock argPtr1)
(toDocument self)
documentWebkitGetNamedFlows ::
(DocumentClass self) => self -> IO (Maybe DOMNamedFlowCollection)
documentWebkitGetNamedFlows self
= maybeNull (makeNewGObject mkDOMNamedFlowCollection)
((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_webkit_get_named_flows argPtr1)
(toDocument self))
documentGetDoctype ::
(DocumentClass self) => self -> IO (Maybe DocumentType)
documentGetDoctype self
= maybeNull (makeNewGObject mkDocumentType)
((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_doctype argPtr1) (toDocument self))
documentGetImplementation ::
(DocumentClass self) => self -> IO (Maybe DOMImplementation)
documentGetImplementation self
= maybeNull (makeNewGObject mkDOMImplementation)
((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_implementation argPtr1)
(toDocument self))
documentGetDocumentElement ::
(DocumentClass self) => self -> IO (Maybe Element)
documentGetDocumentElement self
= maybeNull (makeNewGObject mkElement)
((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_document_element argPtr1)
(toDocument self))
documentGetInputEncoding ::
(DocumentClass self, GlibString string) => self -> IO string
documentGetInputEncoding self
= ((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_input_encoding argPtr1)
(toDocument self))
>>=
readUTFString
documentGetXmlEncoding ::
(DocumentClass self, GlibString string) => self -> IO string
documentGetXmlEncoding self
= ((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_xml_encoding argPtr1)
(toDocument self))
>>=
readUTFString
documentSetXmlVersion ::
(DocumentClass self, GlibString string) => self -> string -> IO ()
documentSetXmlVersion self val
= propagateGError $
\ errorPtr_ ->
withUTFString val $
\ valPtr ->
(\(Document arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_set_xml_version argPtr1 arg2 arg3) (toDocument self)
valPtr
errorPtr_
documentGetXmlVersion ::
(DocumentClass self, GlibString string) => self -> IO string
documentGetXmlVersion self
= ((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_xml_version argPtr1)
(toDocument self))
>>=
readUTFString
documentSetXmlStandalone ::
(DocumentClass self) => self -> Bool -> IO ()
documentSetXmlStandalone self val
= propagateGError $
\ errorPtr_ ->
(\(Document arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_set_xml_standalone argPtr1 arg2 arg3) (toDocument self)
(fromBool val)
errorPtr_
documentGetXmlStandalone :: (DocumentClass self) => self -> IO Bool
documentGetXmlStandalone self
= toBool <$>
((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_xml_standalone argPtr1)
(toDocument self))
documentSetDocumentURI ::
(DocumentClass self, GlibString string) => self -> string -> IO ()
documentSetDocumentURI self val
= withUTFString val $
\ valPtr ->
(\(Document arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_set_document_uri argPtr1 arg2) (toDocument self)
valPtr
documentGetDocumentURI ::
(DocumentClass self, GlibString string) => self -> IO string
documentGetDocumentURI self
= ((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_document_uri argPtr1)
(toDocument self))
>>=
readUTFString
documentGetDefaultView ::
(DocumentClass self) => self -> IO (Maybe DOMWindow)
documentGetDefaultView self
= maybeNull (makeNewGObject mkDOMWindow)
((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_default_view argPtr1) (toDocument self))
documentGetStyleSheets ::
(DocumentClass self) => self -> IO (Maybe StyleSheetList)
documentGetStyleSheets self
= maybeNull (makeNewGObject mkStyleSheetList)
((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_style_sheets argPtr1) (toDocument self))
documentSetTitle ::
(DocumentClass self, GlibString string) => self -> string -> IO ()
documentSetTitle self val
= withUTFString val $
\ valPtr ->
(\(Document arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_set_title argPtr1 arg2) (toDocument self) valPtr
documentGetTitle ::
(DocumentClass self, GlibString string) => self -> IO string
documentGetTitle self
= ((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_title argPtr1) (toDocument self)) >>=
readUTFString
documentGetReferrer ::
(DocumentClass self, GlibString string) => self -> IO string
documentGetReferrer self
= ((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_referrer argPtr1) (toDocument self))
>>=
readUTFString
documentGetDomain ::
(DocumentClass self, GlibString string) => self -> IO string
documentGetDomain self
= ((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_domain argPtr1) (toDocument self)) >>=
readUTFString
documentSetCookie ::
(DocumentClass self, GlibString string) => self -> string -> IO ()
documentSetCookie self val
= propagateGError $
\ errorPtr_ ->
withUTFString val $
\ valPtr ->
(\(Document arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_set_cookie argPtr1 arg2 arg3) (toDocument self) valPtr
errorPtr_
documentGetCookie ::
(DocumentClass self, GlibString string) => self -> IO string
documentGetCookie self
= (propagateGError $
\ errorPtr_ ->
(\(Document arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_cookie argPtr1 arg2) (toDocument self)
errorPtr_)
>>=
readUTFString
documentSetBody ::
(HTMLElementClass val, DocumentClass self) =>
self -> Maybe val -> IO ()
documentSetBody self val
= propagateGError $
\ errorPtr_ ->
(\(Document arg1) (HTMLElement arg2) arg3 -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->webkit_dom_document_set_body argPtr1 argPtr2 arg3) (toDocument self)
(maybe (HTMLElement nullForeignPtr) toHTMLElement val)
errorPtr_
documentGetBody ::
(DocumentClass self) => self -> IO (Maybe HTMLElement)
documentGetBody self
= maybeNull (makeNewGObject mkHTMLElement)
((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_body argPtr1) (toDocument self))
documentGetHead ::
(DocumentClass self) => self -> IO (Maybe HTMLHeadElement)
documentGetHead self
= maybeNull (makeNewGObject mkHTMLHeadElement)
((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_head argPtr1) (toDocument self))
documentGetImages ::
(DocumentClass self) => self -> IO (Maybe HTMLCollection)
documentGetImages self
= maybeNull (makeNewGObject mkHTMLCollection)
((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_images argPtr1) (toDocument self))
documentGetApplets ::
(DocumentClass self) => self -> IO (Maybe HTMLCollection)
documentGetApplets self
= maybeNull (makeNewGObject mkHTMLCollection)
((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_applets argPtr1) (toDocument self))
documentGetLinks ::
(DocumentClass self) => self -> IO (Maybe HTMLCollection)
documentGetLinks self
= maybeNull (makeNewGObject mkHTMLCollection)
((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_links argPtr1) (toDocument self))
documentGetForms ::
(DocumentClass self) => self -> IO (Maybe HTMLCollection)
documentGetForms self
= maybeNull (makeNewGObject mkHTMLCollection)
((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_forms argPtr1) (toDocument self))
documentGetAnchors ::
(DocumentClass self) => self -> IO (Maybe HTMLCollection)
documentGetAnchors self
= maybeNull (makeNewGObject mkHTMLCollection)
((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_anchors argPtr1) (toDocument self))
documentGetLastModified ::
(DocumentClass self, GlibString string) => self -> IO string
documentGetLastModified self
= ((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_last_modified argPtr1)
(toDocument self))
>>=
readUTFString
documentSetCharset ::
(DocumentClass self, GlibString string) => self -> string -> IO ()
documentSetCharset self val
= withUTFString val $
\ valPtr ->
(\(Document arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_set_charset argPtr1 arg2) (toDocument self) valPtr
documentGetCharset ::
(DocumentClass self, GlibString string) => self -> IO string
documentGetCharset self
= ((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_charset argPtr1) (toDocument self))
>>=
readUTFString
documentGetDefaultCharset ::
(DocumentClass self, GlibString string) => self -> IO string
documentGetDefaultCharset self
= ((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_default_charset argPtr1)
(toDocument self))
>>=
readUTFString
documentGetReadyState ::
(DocumentClass self, GlibString string) => self -> IO string
documentGetReadyState self
= ((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_ready_state argPtr1)
(toDocument self))
>>=
readUTFString
documentGetCharacterSet ::
(DocumentClass self, GlibString string) => self -> IO string
documentGetCharacterSet self
= ((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_character_set argPtr1)
(toDocument self))
>>=
readUTFString
documentGetPreferredStylesheetSet ::
(DocumentClass self, GlibString string) => self -> IO string
documentGetPreferredStylesheetSet self
= ((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_preferred_stylesheet_set argPtr1)
(toDocument self))
>>=
readUTFString
documentSetSelectedStylesheetSet ::
(DocumentClass self, GlibString string) => self -> string -> IO ()
documentSetSelectedStylesheetSet self val
= withUTFString val $
\ valPtr ->
(\(Document arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_set_selected_stylesheet_set argPtr1 arg2)
(toDocument self)
valPtr
documentGetSelectedStylesheetSet ::
(DocumentClass self, GlibString string) => self -> IO string
documentGetSelectedStylesheetSet self
= ((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_selected_stylesheet_set argPtr1)
(toDocument self))
>>=
readUTFString
documentGetCompatMode ::
(DocumentClass self, GlibString string) => self -> IO string
documentGetCompatMode self
= ((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_compat_mode argPtr1)
(toDocument self))
>>=
readUTFString
documentGetWebkitPointerLockElement ::
(DocumentClass self) => self -> IO (Maybe Element)
documentGetWebkitPointerLockElement self
= maybeNull (makeNewGObject mkElement)
((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_webkit_pointer_lock_element argPtr1)
(toDocument self))
documentOnabort ::
(DocumentClass self) => Signal self (EventM UIEvent self ())
documentOnabort = (connect "abort")
documentOnblur ::
(DocumentClass self) => Signal self (EventM UIEvent self ())
documentOnblur = (connect "blur")
documentOnchange ::
(DocumentClass self) => Signal self (EventM UIEvent self ())
documentOnchange = (connect "change")
documentOnclick ::
(DocumentClass self) => Signal self (EventM MouseEvent self ())
documentOnclick = (connect "click")
documentOncontextmenu ::
(DocumentClass self) => Signal self (EventM MouseEvent self ())
documentOncontextmenu = (connect "contextmenu")
documentOndblclick ::
(DocumentClass self) => Signal self (EventM MouseEvent self ())
documentOndblclick = (connect "dblclick")
documentOndrag ::
(DocumentClass self) => Signal self (EventM MouseEvent self ())
documentOndrag = (connect "drag")
documentOndragend ::
(DocumentClass self) => Signal self (EventM MouseEvent self ())
documentOndragend = (connect "dragend")
documentOndragenter ::
(DocumentClass self) => Signal self (EventM MouseEvent self ())
documentOndragenter = (connect "dragenter")
documentOndragleave ::
(DocumentClass self) => Signal self (EventM MouseEvent self ())
documentOndragleave = (connect "dragleave")
documentOndragover ::
(DocumentClass self) => Signal self (EventM MouseEvent self ())
documentOndragover = (connect "dragover")
documentOndragstart ::
(DocumentClass self) => Signal self (EventM MouseEvent self ())
documentOndragstart = (connect "dragstart")
documentOndrop ::
(DocumentClass self) => Signal self (EventM MouseEvent self ())
documentOndrop = (connect "drop")
documentOnerror ::
(DocumentClass self) => Signal self (EventM UIEvent self ())
documentOnerror = (connect "error")
documentOnfocus ::
(DocumentClass self) => Signal self (EventM UIEvent self ())
documentOnfocus = (connect "focus")
documentOninput ::
(DocumentClass self) => Signal self (EventM UIEvent self ())
documentOninput = (connect "input")
documentOninvalid ::
(DocumentClass self) => Signal self (EventM UIEvent self ())
documentOninvalid = (connect "invalid")
documentOnkeydown ::
(DocumentClass self) => Signal self (EventM UIEvent self ())
documentOnkeydown = (connect "keydown")
documentOnkeypress ::
(DocumentClass self) => Signal self (EventM UIEvent self ())
documentOnkeypress = (connect "keypress")
documentOnkeyup ::
(DocumentClass self) => Signal self (EventM UIEvent self ())
documentOnkeyup = (connect "keyup")
documentOnload ::
(DocumentClass self) => Signal self (EventM UIEvent self ())
documentOnload = (connect "load")
documentOnmousedown ::
(DocumentClass self) => Signal self (EventM MouseEvent self ())
documentOnmousedown = (connect "mousedown")
documentOnmouseenter ::
(DocumentClass self) => Signal self (EventM UIEvent self ())
documentOnmouseenter = (connect "mouseenter")
documentOnmouseleave ::
(DocumentClass self) => Signal self (EventM UIEvent self ())
documentOnmouseleave = (connect "mouseleave")
documentOnmousemove ::
(DocumentClass self) => Signal self (EventM MouseEvent self ())
documentOnmousemove = (connect "mousemove")
documentOnmouseout ::
(DocumentClass self) => Signal self (EventM MouseEvent self ())
documentOnmouseout = (connect "mouseout")
documentOnmouseover ::
(DocumentClass self) => Signal self (EventM MouseEvent self ())
documentOnmouseover = (connect "mouseover")
documentOnmouseup ::
(DocumentClass self) => Signal self (EventM MouseEvent self ())
documentOnmouseup = (connect "mouseup")
documentOnmousewheel ::
(DocumentClass self) => Signal self (EventM MouseEvent self ())
documentOnmousewheel = (connect "mousewheel")
documentOnreadystatechange ::
(DocumentClass self) => Signal self (EventM UIEvent self ())
documentOnreadystatechange = (connect "readystatechange")
documentOnscroll ::
(DocumentClass self) => Signal self (EventM UIEvent self ())
documentOnscroll = (connect "scroll")
documentOnselect ::
(DocumentClass self) => Signal self (EventM UIEvent self ())
documentOnselect = (connect "select")
documentOnsubmit ::
(DocumentClass self) => Signal self (EventM UIEvent self ())
documentOnsubmit = (connect "submit")
documentOnbeforecut ::
(DocumentClass self) => Signal self (EventM UIEvent self ())
documentOnbeforecut = (connect "beforecut")
documentOncut ::
(DocumentClass self) => Signal self (EventM UIEvent self ())
documentOncut = (connect "cut")
documentOnbeforecopy ::
(DocumentClass self) => Signal self (EventM UIEvent self ())
documentOnbeforecopy = (connect "beforecopy")
documentOncopy ::
(DocumentClass self) => Signal self (EventM UIEvent self ())
documentOncopy = (connect "copy")
documentOnbeforepaste ::
(DocumentClass self) => Signal self (EventM UIEvent self ())
documentOnbeforepaste = (connect "beforepaste")
documentOnpaste ::
(DocumentClass self) => Signal self (EventM UIEvent self ())
documentOnpaste = (connect "paste")
documentOnreset ::
(DocumentClass self) => Signal self (EventM UIEvent self ())
documentOnreset = (connect "reset")
documentOnsearch ::
(DocumentClass self) => Signal self (EventM UIEvent self ())
documentOnsearch = (connect "search")
documentOnselectstart ::
(DocumentClass self) => Signal self (EventM UIEvent self ())
documentOnselectstart = (connect "selectstart")
documentOnselectionchange ::
(DocumentClass self) => Signal self (EventM UIEvent self ())
documentOnselectionchange = (connect "selectionchange")
documentOntouchstart ::
(DocumentClass self) => Signal self (EventM UIEvent self ())
documentOntouchstart = (connect "touchstart")
documentOntouchmove ::
(DocumentClass self) => Signal self (EventM UIEvent self ())
documentOntouchmove = (connect "touchmove")
documentOntouchend ::
(DocumentClass self) => Signal self (EventM UIEvent self ())
documentOntouchend = (connect "touchend")
documentOntouchcancel ::
(DocumentClass self) => Signal self (EventM UIEvent self ())
documentOntouchcancel = (connect "touchcancel")
documentOnwebkitfullscreenchange ::
(DocumentClass self) => Signal self (EventM UIEvent self ())
documentOnwebkitfullscreenchange
= (connect "webkitfullscreenchange")
documentOnwebkitfullscreenerror ::
(DocumentClass self) => Signal self (EventM UIEvent self ())
documentOnwebkitfullscreenerror = (connect "webkitfullscreenerror")
documentOnwebkitpointerlockchange ::
(DocumentClass self) => Signal self (EventM UIEvent self ())
documentOnwebkitpointerlockchange
= (connect "webkitpointerlockchange")
documentOnwebkitpointerlockerror ::
(DocumentClass self) => Signal self (EventM UIEvent self ())
documentOnwebkitpointerlockerror
= (connect "webkitpointerlockerror")
documentOnsecuritypolicyviolation ::
(DocumentClass self) => Signal self (EventM UIEvent self ())
documentOnsecuritypolicyviolation
= (connect "securitypolicyviolation")
documentGetVisibilityState ::
(DocumentClass self, GlibString string) => self -> IO string
documentGetVisibilityState self
= ((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_visibility_state argPtr1)
(toDocument self))
>>=
readUTFString
documentGetHidden :: (DocumentClass self) => self -> IO Bool
documentGetHidden self
= toBool <$>
((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_hidden argPtr1) (toDocument self))
documentGetSecurityPolicy ::
(DocumentClass self) => self -> IO (Maybe DOMSecurityPolicy)
documentGetSecurityPolicy self
= maybeNull (makeNewGObject mkDOMSecurityPolicy)
((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_security_policy argPtr1)
(toDocument self))
documentGetCurrentScript ::
(DocumentClass self) => self -> IO (Maybe HTMLScriptElement)
documentGetCurrentScript self
= maybeNull (makeNewGObject mkHTMLScriptElement)
((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_current_script argPtr1)
(toDocument self))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_create_element"
webkit_dom_document_create_element :: ((Ptr Document) -> ((Ptr CChar) -> ((Ptr (Ptr ())) -> (IO (Ptr Element)))))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_create_document_fragment"
webkit_dom_document_create_document_fragment :: ((Ptr Document) -> (IO (Ptr DocumentFragment)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_create_text_node"
webkit_dom_document_create_text_node :: ((Ptr Document) -> ((Ptr CChar) -> (IO (Ptr Text))))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_create_comment"
webkit_dom_document_create_comment :: ((Ptr Document) -> ((Ptr CChar) -> (IO (Ptr Comment))))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_create_cdata_section"
webkit_dom_document_create_cdata_section :: ((Ptr Document) -> ((Ptr CChar) -> ((Ptr (Ptr ())) -> (IO (Ptr CDATASection)))))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_create_processing_instruction"
webkit_dom_document_create_processing_instruction :: ((Ptr Document) -> ((Ptr CChar) -> ((Ptr CChar) -> ((Ptr (Ptr ())) -> (IO (Ptr ProcessingInstruction))))))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_create_attribute"
webkit_dom_document_create_attribute :: ((Ptr Document) -> ((Ptr CChar) -> ((Ptr (Ptr ())) -> (IO (Ptr DOMAttr)))))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_create_entity_reference"
webkit_dom_document_create_entity_reference :: ((Ptr Document) -> ((Ptr CChar) -> ((Ptr (Ptr ())) -> (IO (Ptr EntityReference)))))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_get_elements_by_tag_name"
webkit_dom_document_get_elements_by_tag_name :: ((Ptr Document) -> ((Ptr CChar) -> (IO (Ptr NodeList))))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_import_node"
webkit_dom_document_import_node :: ((Ptr Document) -> ((Ptr Node) -> (CInt -> ((Ptr (Ptr ())) -> (IO (Ptr Node))))))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_create_element_ns"
webkit_dom_document_create_element_ns :: ((Ptr Document) -> ((Ptr CChar) -> ((Ptr CChar) -> ((Ptr (Ptr ())) -> (IO (Ptr Element))))))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_create_attribute_ns"
webkit_dom_document_create_attribute_ns :: ((Ptr Document) -> ((Ptr CChar) -> ((Ptr CChar) -> ((Ptr (Ptr ())) -> (IO (Ptr DOMAttr))))))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_get_elements_by_tag_name_ns"
webkit_dom_document_get_elements_by_tag_name_ns :: ((Ptr Document) -> ((Ptr CChar) -> ((Ptr CChar) -> (IO (Ptr NodeList)))))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_get_element_by_id"
webkit_dom_document_get_element_by_id :: ((Ptr Document) -> ((Ptr CChar) -> (IO (Ptr Element))))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_adopt_node"
webkit_dom_document_adopt_node :: ((Ptr Document) -> ((Ptr Node) -> ((Ptr (Ptr ())) -> (IO (Ptr Node)))))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_create_event"
webkit_dom_document_create_event :: ((Ptr Document) -> ((Ptr CChar) -> ((Ptr (Ptr ())) -> (IO (Ptr Event)))))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_create_range"
webkit_dom_document_create_range :: ((Ptr Document) -> (IO (Ptr DOMRange)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_create_node_iterator"
webkit_dom_document_create_node_iterator :: ((Ptr Document) -> ((Ptr Node) -> (CULong -> ((Ptr NodeFilter) -> (CInt -> ((Ptr (Ptr ())) -> (IO (Ptr NodeIterator))))))))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_create_tree_walker"
webkit_dom_document_create_tree_walker :: ((Ptr Document) -> ((Ptr Node) -> (CULong -> ((Ptr NodeFilter) -> (CInt -> ((Ptr (Ptr ())) -> (IO (Ptr TreeWalker))))))))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_get_override_style"
webkit_dom_document_get_override_style :: ((Ptr Document) -> ((Ptr Element) -> ((Ptr CChar) -> (IO (Ptr CSSStyleDeclaration)))))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_create_expression"
webkit_dom_document_create_expression :: ((Ptr Document) -> ((Ptr CChar) -> ((Ptr XPathNSResolver) -> ((Ptr (Ptr ())) -> (IO (Ptr XPathExpression))))))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_create_ns_resolver"
webkit_dom_document_create_ns_resolver :: ((Ptr Document) -> ((Ptr Node) -> (IO (Ptr XPathNSResolver))))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_evaluate"
webkit_dom_document_evaluate :: ((Ptr Document) -> ((Ptr CChar) -> ((Ptr Node) -> ((Ptr XPathNSResolver) -> (CUShort -> ((Ptr XPathResult) -> ((Ptr (Ptr ())) -> (IO (Ptr XPathResult)))))))))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_exec_command"
webkit_dom_document_exec_command :: ((Ptr Document) -> ((Ptr CChar) -> (CInt -> ((Ptr CChar) -> (IO CInt)))))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_query_command_enabled"
webkit_dom_document_query_command_enabled :: ((Ptr Document) -> ((Ptr CChar) -> (IO CInt)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_query_command_indeterm"
webkit_dom_document_query_command_indeterm :: ((Ptr Document) -> ((Ptr CChar) -> (IO CInt)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_query_command_state"
webkit_dom_document_query_command_state :: ((Ptr Document) -> ((Ptr CChar) -> (IO CInt)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_query_command_supported"
webkit_dom_document_query_command_supported :: ((Ptr Document) -> ((Ptr CChar) -> (IO CInt)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_query_command_value"
webkit_dom_document_query_command_value :: ((Ptr Document) -> ((Ptr CChar) -> (IO (Ptr CChar))))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_get_elements_by_name"
webkit_dom_document_get_elements_by_name :: ((Ptr Document) -> ((Ptr CChar) -> (IO (Ptr NodeList))))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_element_from_point"
webkit_dom_document_element_from_point :: ((Ptr Document) -> (CLong -> (CLong -> (IO (Ptr Element)))))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_caret_range_from_point"
webkit_dom_document_caret_range_from_point :: ((Ptr Document) -> (CLong -> (CLong -> (IO (Ptr DOMRange)))))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_create_css_style_declaration"
webkit_dom_document_create_css_style_declaration :: ((Ptr Document) -> (IO (Ptr CSSStyleDeclaration)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_get_elements_by_class_name"
webkit_dom_document_get_elements_by_class_name :: ((Ptr Document) -> ((Ptr CChar) -> (IO (Ptr NodeList))))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_query_selector"
webkit_dom_document_query_selector :: ((Ptr Document) -> ((Ptr CChar) -> ((Ptr (Ptr ())) -> (IO (Ptr Element)))))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_query_selector_all"
webkit_dom_document_query_selector_all :: ((Ptr Document) -> ((Ptr CChar) -> ((Ptr (Ptr ())) -> (IO (Ptr NodeList)))))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_webkit_exit_pointer_lock"
webkit_dom_document_webkit_exit_pointer_lock :: ((Ptr Document) -> (IO ()))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_webkit_get_named_flows"
webkit_dom_document_webkit_get_named_flows :: ((Ptr Document) -> (IO (Ptr DOMNamedFlowCollection)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_get_doctype"
webkit_dom_document_get_doctype :: ((Ptr Document) -> (IO (Ptr DocumentType)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_get_implementation"
webkit_dom_document_get_implementation :: ((Ptr Document) -> (IO (Ptr DOMImplementation)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_get_document_element"
webkit_dom_document_get_document_element :: ((Ptr Document) -> (IO (Ptr Element)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_get_input_encoding"
webkit_dom_document_get_input_encoding :: ((Ptr Document) -> (IO (Ptr CChar)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_get_xml_encoding"
webkit_dom_document_get_xml_encoding :: ((Ptr Document) -> (IO (Ptr CChar)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_set_xml_version"
webkit_dom_document_set_xml_version :: ((Ptr Document) -> ((Ptr CChar) -> ((Ptr (Ptr ())) -> (IO ()))))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_get_xml_version"
webkit_dom_document_get_xml_version :: ((Ptr Document) -> (IO (Ptr CChar)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_set_xml_standalone"
webkit_dom_document_set_xml_standalone :: ((Ptr Document) -> (CInt -> ((Ptr (Ptr ())) -> (IO ()))))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_get_xml_standalone"
webkit_dom_document_get_xml_standalone :: ((Ptr Document) -> (IO CInt))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_set_document_uri"
webkit_dom_document_set_document_uri :: ((Ptr Document) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_get_document_uri"
webkit_dom_document_get_document_uri :: ((Ptr Document) -> (IO (Ptr CChar)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_get_default_view"
webkit_dom_document_get_default_view :: ((Ptr Document) -> (IO (Ptr DOMWindow)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_get_style_sheets"
webkit_dom_document_get_style_sheets :: ((Ptr Document) -> (IO (Ptr StyleSheetList)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_set_title"
webkit_dom_document_set_title :: ((Ptr Document) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_get_title"
webkit_dom_document_get_title :: ((Ptr Document) -> (IO (Ptr CChar)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_get_referrer"
webkit_dom_document_get_referrer :: ((Ptr Document) -> (IO (Ptr CChar)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_get_domain"
webkit_dom_document_get_domain :: ((Ptr Document) -> (IO (Ptr CChar)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_set_cookie"
webkit_dom_document_set_cookie :: ((Ptr Document) -> ((Ptr CChar) -> ((Ptr (Ptr ())) -> (IO ()))))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_get_cookie"
webkit_dom_document_get_cookie :: ((Ptr Document) -> ((Ptr (Ptr ())) -> (IO (Ptr CChar))))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_set_body"
webkit_dom_document_set_body :: ((Ptr Document) -> ((Ptr HTMLElement) -> ((Ptr (Ptr ())) -> (IO ()))))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_get_body"
webkit_dom_document_get_body :: ((Ptr Document) -> (IO (Ptr HTMLElement)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_get_head"
webkit_dom_document_get_head :: ((Ptr Document) -> (IO (Ptr HTMLHeadElement)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_get_images"
webkit_dom_document_get_images :: ((Ptr Document) -> (IO (Ptr HTMLCollection)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_get_applets"
webkit_dom_document_get_applets :: ((Ptr Document) -> (IO (Ptr HTMLCollection)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_get_links"
webkit_dom_document_get_links :: ((Ptr Document) -> (IO (Ptr HTMLCollection)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_get_forms"
webkit_dom_document_get_forms :: ((Ptr Document) -> (IO (Ptr HTMLCollection)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_get_anchors"
webkit_dom_document_get_anchors :: ((Ptr Document) -> (IO (Ptr HTMLCollection)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_get_last_modified"
webkit_dom_document_get_last_modified :: ((Ptr Document) -> (IO (Ptr CChar)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_set_charset"
webkit_dom_document_set_charset :: ((Ptr Document) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_get_charset"
webkit_dom_document_get_charset :: ((Ptr Document) -> (IO (Ptr CChar)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_get_default_charset"
webkit_dom_document_get_default_charset :: ((Ptr Document) -> (IO (Ptr CChar)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_get_ready_state"
webkit_dom_document_get_ready_state :: ((Ptr Document) -> (IO (Ptr CChar)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_get_character_set"
webkit_dom_document_get_character_set :: ((Ptr Document) -> (IO (Ptr CChar)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_get_preferred_stylesheet_set"
webkit_dom_document_get_preferred_stylesheet_set :: ((Ptr Document) -> (IO (Ptr CChar)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_set_selected_stylesheet_set"
webkit_dom_document_set_selected_stylesheet_set :: ((Ptr Document) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_get_selected_stylesheet_set"
webkit_dom_document_get_selected_stylesheet_set :: ((Ptr Document) -> (IO (Ptr CChar)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_get_compat_mode"
webkit_dom_document_get_compat_mode :: ((Ptr Document) -> (IO (Ptr CChar)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_get_webkit_pointer_lock_element"
webkit_dom_document_get_webkit_pointer_lock_element :: ((Ptr Document) -> (IO (Ptr Element)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_get_visibility_state"
webkit_dom_document_get_visibility_state :: ((Ptr Document) -> (IO (Ptr CChar)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_get_hidden"
webkit_dom_document_get_hidden :: ((Ptr Document) -> (IO CInt))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_get_security_policy"
webkit_dom_document_get_security_policy :: ((Ptr Document) -> (IO (Ptr DOMSecurityPolicy)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_get_current_script"
webkit_dom_document_get_current_script :: ((Ptr Document) -> (IO (Ptr HTMLScriptElement)))