-- GENERATED by C->Haskell Compiler, version 0.13.13 (gtk2hs branch) "Bin IO", 27 May 2012 (Haskell)
-- Edit the ORIGNAL .chs file instead!


{-# LINE 1 "./Graphics/UI/Gtk/WebKit/DOM/Document.chs" #-}
module Graphics.UI.Gtk.WebKit.DOM.Document(
createElement,
createDocumentFragment,
createTextNode,
createComment,
createCDATASection,
createProcessingInstruction,
createAttribute,
createEntityReference,
getElementsByTagName,
importNode,
createElementNS,
createAttributeNS,
getElementsByTagNameNS,
getElementById,
adoptNode,
createEvent,
createRange,
createNodeIterator,
createTreeWalker,
getOverrideStyle,
createExpression,
createNSResolver,
evaluate,
execCommand,
queryCommandEnabled,
queryCommandIndeterm,
queryCommandState,
queryCommandSupported,
queryCommandValue,
getElementsByName,
elementFromPoint,
caretRangeFromPoint,
createCSSStyleDeclaration,
getElementsByClassName,
querySelector,
querySelectorAll,
webkitCancelFullScreen,
webkitExitFullscreen,
webkitGetNamedFlows,
createTouch,
getDoctype,
getImplementation,
getDocumentElement,
getInputEncoding,
getXmlEncoding,
setXmlVersion,
getXmlVersion,
setXmlStandalone,
getXmlStandalone,
getDocumentURI,
getDefaultView,
getStyleSheets,
setTitle,
getTitle,
getReferrer,
getDomain,
setCookie,
getCookie,
setBody,
getBody,
getHead,
getImages,
getApplets,
getLinks,
getForms,
getAnchors,
getLastModified,
setCharset,
getCharset,
getDefaultCharset,
getReadyState,
getCharacterSet,
getPreferredStylesheetSet,
setSelectedStylesheetSet,
getSelectedStylesheetSet,
getCompatMode,
getWebkitIsFullScreen,
getWebkitFullScreenKeyboardInputAllowed,
getWebkitCurrentFullScreenElement,
getWebkitFullscreenEnabled,
getWebkitFullscreenElement,
abort,
blur,
change,
click,
contextMenu,
dblClick,
drag,
dragEnd,
dragEnter,
dragLeave,
dragOver,
dragStart,
drop,
error,
focus,
input,
invalid,
keyDown,
keyPress,
keyUp,
load,
mouseDown,
mouseEnter,
mouseLeave,
mouseMove,
mouseOut,
mouseOver,
mouseUp,
mouseWheel,
readyStateChange,
scroll,
select,
submit,
wheel,
beforeCut,
cut,
beforeCopy,
copy,
beforePaste,
paste,
reset,
search,
selectStart,
selectionchange,
touchStart,
touchMove,
touchEnd,
touchCancel,
webKitFullscreenChange,
webKitFullscreenError,
pointerlockchange,
pointerlockerror,
securitypolicyviolation,
webKitWillRevealBottom,
webKitWillRevealLeft,
webKitWillRevealRight,
webKitWillRevealTop,
getVisibilityState,
getHidden,
getSecurityPolicy,
getCurrentScript,
Document,
castToDocument,
gTypeDocument,
DocumentClass,
toDocument,
) where
import Prelude hiding (drop, error, print)
import Data.Typeable (Typeable)
import Foreign.Marshal (maybePeek, maybeWith)
import System.Glib.FFI (maybeNull, withForeignPtr, nullForeignPtr, Ptr, nullPtr, castPtr, Word, Int64, Word64, CChar(..), CInt(..), CUInt(..), CLong(..), CULong(..), CLLong(..), CULLong(..), CShort(..), CUShort(..), CFloat(..), CDouble(..), toBool, fromBool)
import System.Glib.UTFString (GlibString(..), readUTFString)
import Control.Applicative ((<$>))
import Control.Monad (void)
import Control.Monad.IO.Class (MonadIO(..))
import System.Glib.GError
import Graphics.UI.Gtk.WebKit.DOM.EventTargetClosures
import Graphics.UI.Gtk.WebKit.DOM.EventM
import Graphics.UI.Gtk.WebKit.Types
{-# LINE 178 "./Graphics/UI/Gtk/WebKit/DOM/Document.chs" #-}
import Graphics.UI.Gtk.WebKit.DOM.Enums

 
createElement ::
              (MonadIO m, DocumentClass self, GlibString string) =>
                self -> (Maybe string) -> m (Maybe Element)
createElement self tagName
  = liftIO
      (maybeNull (makeNewGObject mkElement)
         (propagateGError $
            \ errorPtr_ ->
              maybeWith withUTFString tagName $
                \ tagNamePtr ->
                  (\(Document arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_create_element argPtr1 arg2 arg3) (toDocument self)
                    tagNamePtr
                errorPtr_))
 
createDocumentFragment ::
                       (MonadIO m, DocumentClass self) =>
                         self -> m (Maybe DocumentFragment)
createDocumentFragment self
  = liftIO
      (maybeNull (makeNewGObject mkDocumentFragment)
         ((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_create_document_fragment argPtr1)
{-# LINE 202 "./Graphics/UI/Gtk/WebKit/DOM/Document.chs" #-}
            (toDocument self)))
 
createTextNode ::
               (MonadIO m, DocumentClass self, GlibString string) =>
                 self -> string -> m (Maybe Text)
createTextNode self data'
  = liftIO
      (maybeNull (makeNewGObject mkText)
         (withUTFString data' $
            \ dataPtr ->
              (\(Document arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_create_text_node argPtr1 arg2) (toDocument self)
                dataPtr))
 
createComment ::
              (MonadIO m, DocumentClass self, GlibString string) =>
                self -> string -> m (Maybe Comment)
createComment self data'
  = liftIO
      (maybeNull (makeNewGObject mkComment)
         (withUTFString data' $
            \ dataPtr ->
              (\(Document arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_create_comment argPtr1 arg2) (toDocument self)
                dataPtr))
 
createCDATASection ::
                   (MonadIO m, DocumentClass self, GlibString string) =>
                     self -> string -> m (Maybe CDATASection)
createCDATASection self data'
  = liftIO
      (maybeNull (makeNewGObject mkCDATASection)
         (propagateGError $
            \ errorPtr_ ->
              withUTFString data' $
                \ dataPtr ->
                  (\(Document arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_create_cdata_section argPtr1 arg2 arg3)
{-# LINE 237 "./Graphics/UI/Gtk/WebKit/DOM/Document.chs" #-}
                    (toDocument self)
                    dataPtr
                errorPtr_))
 
createProcessingInstruction ::
                            (MonadIO m, DocumentClass self, GlibString string) =>
                              self -> string -> string -> m (Maybe ProcessingInstruction)
createProcessingInstruction self target data'
  = liftIO
      (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)
{-# LINE 254 "./Graphics/UI/Gtk/WebKit/DOM/Document.chs" #-}
                        (toDocument self)
                        targetPtr
                    dataPtr
                errorPtr_))
 
createAttribute ::
                (MonadIO m, DocumentClass self, GlibString string) =>
                  self -> string -> m (Maybe Attr)
createAttribute self name
  = liftIO
      (maybeNull (makeNewGObject mkAttr)
         (propagateGError $
            \ errorPtr_ ->
              withUTFString name $
                \ namePtr ->
                  (\(Document arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_create_attribute argPtr1 arg2 arg3) (toDocument self)
                    namePtr
                errorPtr_))
 
createEntityReference ::
                      (MonadIO m, DocumentClass self, GlibString string) =>
                        self -> string -> m (Maybe EntityReference)
createEntityReference self name
  = liftIO
      (maybeNull (makeNewGObject mkEntityReference)
         (propagateGError $
            \ errorPtr_ ->
              withUTFString name $
                \ namePtr ->
                  (\(Document arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_create_entity_reference argPtr1 arg2 arg3)
{-# LINE 284 "./Graphics/UI/Gtk/WebKit/DOM/Document.chs" #-}
                    (toDocument self)
                    namePtr
                errorPtr_))
 
getElementsByTagName ::
                     (MonadIO m, DocumentClass self, GlibString string) =>
                       self -> string -> m (Maybe NodeList)
getElementsByTagName self tagname
  = liftIO
      (maybeNull (makeNewGObject mkNodeList)
         (withUTFString tagname $
            \ tagnamePtr ->
              (\(Document arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_elements_by_tag_name argPtr1 arg2)
{-# LINE 297 "./Graphics/UI/Gtk/WebKit/DOM/Document.chs" #-}
                (toDocument self)
                tagnamePtr))
 
importNode ::
           (MonadIO m, DocumentClass self, NodeClass importedNode) =>
             self -> Maybe importedNode -> Bool -> m (Maybe Node)
importNode self importedNode deep
  = liftIO
      (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_))
 
createElementNS ::
                (MonadIO m, DocumentClass self, GlibString string) =>
                  self -> (Maybe string) -> (Maybe string) -> m (Maybe Element)
createElementNS self namespaceURI qualifiedName
  = liftIO
      (maybeNull (makeNewGObject mkElement)
         (propagateGError $
            \ errorPtr_ ->
              maybeWith withUTFString qualifiedName $
                \ qualifiedNamePtr ->
                  maybeWith 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_))
 
createAttributeNS ::
                  (MonadIO m, DocumentClass self, GlibString string) =>
                    self -> (Maybe string) -> (Maybe string) -> m (Maybe Attr)
createAttributeNS self namespaceURI qualifiedName
  = liftIO
      (maybeNull (makeNewGObject mkAttr)
         (propagateGError $
            \ errorPtr_ ->
              maybeWith withUTFString qualifiedName $
                \ qualifiedNamePtr ->
                  maybeWith withUTFString namespaceURI $
                    \ namespaceURIPtr ->
                      (\(Document arg1) arg2 arg3 arg4 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_create_attribute_ns argPtr1 arg2 arg3 arg4)
{-# LINE 343 "./Graphics/UI/Gtk/WebKit/DOM/Document.chs" #-}
                        (toDocument self)
                        namespaceURIPtr
                    qualifiedNamePtr
                errorPtr_))
 
getElementsByTagNameNS ::
                       (MonadIO m, DocumentClass self, GlibString string) =>
                         self -> (Maybe string) -> string -> m (Maybe NodeList)
getElementsByTagNameNS self namespaceURI localName
  = liftIO
      (maybeNull (makeNewGObject mkNodeList)
         (withUTFString localName $
            \ localNamePtr ->
              maybeWith withUTFString namespaceURI $
                \ namespaceURIPtr ->
                  (\(Document arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_elements_by_tag_name_ns argPtr1 arg2 arg3)
{-# LINE 359 "./Graphics/UI/Gtk/WebKit/DOM/Document.chs" #-}
                    (toDocument self)
                    namespaceURIPtr
                localNamePtr))
 
getElementById ::
               (MonadIO m, DocumentClass self, GlibString string) =>
                 self -> string -> m (Maybe Element)
getElementById self elementId
  = liftIO
      (maybeNull (makeNewGObject mkElement)
         (withUTFString elementId $
            \ elementIdPtr ->
              (\(Document arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_element_by_id argPtr1 arg2) (toDocument self)
                elementIdPtr))
 
adoptNode ::
          (MonadIO m, DocumentClass self, NodeClass source) =>
            self -> Maybe source -> m (Maybe Node)
adoptNode self source
  = liftIO
      (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_))
 
createEvent ::
            (MonadIO m, DocumentClass self, GlibString string) =>
              self -> string -> m (Maybe Event)
createEvent self eventType
  = liftIO
      (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_))
 
createRange ::
            (MonadIO m, DocumentClass self) => self -> m (Maybe Range)
createRange self
  = liftIO
      (maybeNull (makeNewGObject mkRange)
         ((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_create_range argPtr1) (toDocument self)))
 
createNodeIterator ::
                   (MonadIO m, DocumentClass self, NodeClass root,
                    NodeFilterClass filter) =>
                     self ->
                       Maybe root ->
                         Word -> Maybe filter -> Bool -> m (Maybe NodeIterator)
createNodeIterator self root whatToShow filter
  expandEntityReferences
  = liftIO
      (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)
{-# LINE 420 "./Graphics/UI/Gtk/WebKit/DOM/Document.chs" #-}
                (toDocument self)
                (maybe (Node nullForeignPtr) toNode root)
                (fromIntegral whatToShow)
                (maybe (NodeFilter nullForeignPtr) toNodeFilter filter)
                (fromBool expandEntityReferences)
                errorPtr_))
 
createTreeWalker ::
                 (MonadIO m, DocumentClass self, NodeClass root,
                  NodeFilterClass filter) =>
                   self ->
                     Maybe root -> Word -> Maybe filter -> Bool -> m (Maybe TreeWalker)
createTreeWalker self root whatToShow filter expandEntityReferences
  = liftIO
      (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_))
 
getOverrideStyle ::
                 (MonadIO m, DocumentClass self, ElementClass element,
                  GlibString string) =>
                   self -> Maybe element -> string -> m (Maybe CSSStyleDeclaration)
getOverrideStyle self element pseudoElement
  = liftIO
      (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))
 
createExpression ::
                 (MonadIO m, DocumentClass self, XPathNSResolverClass resolver,
                  GlibString string) =>
                   self -> string -> Maybe resolver -> m (Maybe XPathExpression)
createExpression self expression resolver
  = liftIO
      (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_))
 
createNSResolver ::
                 (MonadIO m, DocumentClass self, NodeClass nodeResolver) =>
                   self -> Maybe nodeResolver -> m (Maybe XPathNSResolver)
createNSResolver self nodeResolver
  = liftIO
      (maybeNull (makeNewGObject mkXPathNSResolver)
         ((\(Document arg1) (Node arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->webkit_dom_document_create_ns_resolver argPtr1 argPtr2)
{-# LINE 480 "./Graphics/UI/Gtk/WebKit/DOM/Document.chs" #-}
            (toDocument self)
            (maybe (Node nullForeignPtr) toNode nodeResolver)))
 
evaluate ::
         (MonadIO m, DocumentClass self, NodeClass contextNode,
          XPathNSResolverClass resolver, XPathResultClass inResult,
          GlibString string) =>
           self ->
             string ->
               Maybe contextNode ->
                 Maybe resolver -> Word -> Maybe inResult -> m (Maybe XPathResult)
evaluate self expression contextNode resolver type' inResult
  = liftIO
      (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_))
 
execCommand ::
            (MonadIO m, DocumentClass self, GlibString string) =>
              self -> string -> Bool -> (Maybe string) -> m Bool
execCommand self command userInterface value
  = liftIO
      (toBool <$>
         (maybeWith 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))
 
queryCommandEnabled ::
                    (MonadIO m, DocumentClass self, GlibString string) =>
                      self -> string -> m Bool
queryCommandEnabled self command
  = liftIO
      (toBool <$>
         (withUTFString command $
            \ commandPtr ->
              (\(Document arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_query_command_enabled argPtr1 arg2)
{-# LINE 530 "./Graphics/UI/Gtk/WebKit/DOM/Document.chs" #-}
                (toDocument self)
                commandPtr))
 
queryCommandIndeterm ::
                     (MonadIO m, DocumentClass self, GlibString string) =>
                       self -> string -> m Bool
queryCommandIndeterm self command
  = liftIO
      (toBool <$>
         (withUTFString command $
            \ commandPtr ->
              (\(Document arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_query_command_indeterm argPtr1 arg2)
{-# LINE 542 "./Graphics/UI/Gtk/WebKit/DOM/Document.chs" #-}
                (toDocument self)
                commandPtr))
 
queryCommandState ::
                  (MonadIO m, DocumentClass self, GlibString string) =>
                    self -> string -> m Bool
queryCommandState self command
  = liftIO
      (toBool <$>
         (withUTFString command $
            \ commandPtr ->
              (\(Document arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_query_command_state argPtr1 arg2)
{-# LINE 554 "./Graphics/UI/Gtk/WebKit/DOM/Document.chs" #-}
                (toDocument self)
                commandPtr))
 
queryCommandSupported ::
                      (MonadIO m, DocumentClass self, GlibString string) =>
                        self -> string -> m Bool
queryCommandSupported self command
  = liftIO
      (toBool <$>
         (withUTFString command $
            \ commandPtr ->
              (\(Document arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_query_command_supported argPtr1 arg2)
{-# LINE 566 "./Graphics/UI/Gtk/WebKit/DOM/Document.chs" #-}
                (toDocument self)
                commandPtr))
 
queryCommandValue ::
                  (MonadIO m, DocumentClass self, GlibString string) =>
                    self -> string -> m string
queryCommandValue self command
  = liftIO
      ((withUTFString command $
          \ commandPtr ->
            (\(Document arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_query_command_value argPtr1 arg2)
{-# LINE 577 "./Graphics/UI/Gtk/WebKit/DOM/Document.chs" #-}
              (toDocument self)
              commandPtr)
         >>=
         readUTFString)
 
getElementsByName ::
                  (MonadIO m, DocumentClass self, GlibString string) =>
                    self -> string -> m (Maybe NodeList)
getElementsByName self elementName
  = liftIO
      (maybeNull (makeNewGObject mkNodeList)
         (withUTFString elementName $
            \ elementNamePtr ->
              (\(Document arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_elements_by_name argPtr1 arg2)
{-# LINE 591 "./Graphics/UI/Gtk/WebKit/DOM/Document.chs" #-}
                (toDocument self)
                elementNamePtr))
 
elementFromPoint ::
                 (MonadIO m, DocumentClass self) =>
                   self -> Int -> Int -> m (Maybe Element)
elementFromPoint self x y
  = liftIO
      (maybeNull (makeNewGObject mkElement)
         ((\(Document arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_element_from_point argPtr1 arg2 arg3)
{-# LINE 601 "./Graphics/UI/Gtk/WebKit/DOM/Document.chs" #-}
            (toDocument self)
            (fromIntegral x)
            (fromIntegral y)))
 
caretRangeFromPoint ::
                    (MonadIO m, DocumentClass self) =>
                      self -> Int -> Int -> m (Maybe Range)
caretRangeFromPoint self x y
  = liftIO
      (maybeNull (makeNewGObject mkRange)
         ((\(Document arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_caret_range_from_point argPtr1 arg2 arg3)
{-# LINE 612 "./Graphics/UI/Gtk/WebKit/DOM/Document.chs" #-}
            (toDocument self)
            (fromIntegral x)
            (fromIntegral y)))
 
createCSSStyleDeclaration ::
                          (MonadIO m, DocumentClass self) =>
                            self -> m (Maybe CSSStyleDeclaration)
createCSSStyleDeclaration self
  = liftIO
      (maybeNull (makeNewGObject mkCSSStyleDeclaration)
         ((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_create_css_style_declaration argPtr1)
{-# LINE 623 "./Graphics/UI/Gtk/WebKit/DOM/Document.chs" #-}
            (toDocument self)))
 
getElementsByClassName ::
                       (MonadIO m, DocumentClass self, GlibString string) =>
                         self -> string -> m (Maybe NodeList)
getElementsByClassName self tagname
  = liftIO
      (maybeNull (makeNewGObject mkNodeList)
         (withUTFString tagname $
            \ tagnamePtr ->
              (\(Document arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_elements_by_class_name argPtr1 arg2)
{-# LINE 634 "./Graphics/UI/Gtk/WebKit/DOM/Document.chs" #-}
                (toDocument self)
                tagnamePtr))

 
querySelector ::
              (MonadIO m, DocumentClass self, GlibString string) =>
                self -> string -> m (Maybe Element)
querySelector self selectors
  = liftIO
      (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_))
 
querySelectorAll ::
                 (MonadIO m, DocumentClass self, GlibString string) =>
                   self -> string -> m (Maybe NodeList)
querySelectorAll self selectors
  = liftIO
      (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_))
 
webkitCancelFullScreen ::
                       (MonadIO m, DocumentClass self) => self -> m ()
webkitCancelFullScreen self
  = liftIO
      ((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_webkit_cancel_full_screen argPtr1)
{-# LINE 678 "./Graphics/UI/Gtk/WebKit/DOM/Document.chs" #-}
         (toDocument self))

webkitExitFullscreen ::
                     (MonadIO m, DocumentClass self) => self -> m ()
webkitExitFullscreen self
  = liftIO
      ((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_webkit_exit_fullscreen argPtr1)
{-# LINE 686 "./Graphics/UI/Gtk/WebKit/DOM/Document.chs" #-}
         (toDocument self))
 
webkitGetNamedFlows ::
                    (MonadIO m, DocumentClass self) =>
                      self -> m (Maybe DOMNamedFlowCollection)
webkitGetNamedFlows self
  = liftIO
      (maybeNull (makeNewGObject mkDOMNamedFlowCollection)
         ((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_webkit_get_named_flows argPtr1)
{-# LINE 695 "./Graphics/UI/Gtk/WebKit/DOM/Document.chs" #-}
            (toDocument self)))

createTouch ::
            (MonadIO m, DocumentClass self, WindowClass window,
             EventTargetClass target) =>
              self ->
                Maybe window ->
                  Maybe target ->
                    Int ->
                      Int ->
                        Int ->
                          Int -> Int -> Int -> Int -> Float -> Float -> m (Maybe Touch)
createTouch self window target identifier pageX pageY screenX
  screenY webkitRadiusX webkitRadiusY webkitRotationAngle webkitForce
  = liftIO
      (maybeNull (makeNewGObject mkTouch)
         (propagateGError $
            \ errorPtr_ ->
              (\(Document arg1) (Window arg2) (EventTarget arg3) arg4 arg5 arg6 arg7 arg8 arg9 arg10 arg11 arg12 arg13 -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->withForeignPtr arg3 $ \argPtr3 ->webkit_dom_document_create_touch argPtr1 argPtr2 argPtr3 arg4 arg5 arg6 arg7 arg8 arg9 arg10 arg11 arg12 arg13) (toDocument self)
                (maybe (Window nullForeignPtr) toWindow window)
                (maybe (EventTarget nullForeignPtr) toEventTarget target)
                (fromIntegral identifier)
                (fromIntegral pageX)
                (fromIntegral pageY)
                (fromIntegral screenX)
                (fromIntegral screenY)
                (fromIntegral webkitRadiusX)
                (fromIntegral webkitRadiusY)
                (realToFrac webkitRotationAngle)
                (realToFrac webkitForce)
                errorPtr_))
 
getDoctype ::
           (MonadIO m, DocumentClass self) => self -> m (Maybe DocumentType)
getDoctype self
  = liftIO
      (maybeNull (makeNewGObject mkDocumentType)
         ((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_doctype argPtr1) (toDocument self)))
 
getImplementation ::
                  (MonadIO m, DocumentClass self) =>
                    self -> m (Maybe DOMImplementation)
getImplementation self
  = liftIO
      (maybeNull (makeNewGObject mkDOMImplementation)
         ((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_implementation argPtr1)
{-# LINE 744 "./Graphics/UI/Gtk/WebKit/DOM/Document.chs" #-}
            (toDocument self)))
 
getDocumentElement ::
                   (MonadIO m, DocumentClass self) => self -> m (Maybe Element)
getDocumentElement self
  = liftIO
      (maybeNull (makeNewGObject mkElement)
         ((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_document_element argPtr1)
{-# LINE 752 "./Graphics/UI/Gtk/WebKit/DOM/Document.chs" #-}
            (toDocument self)))
 
getInputEncoding ::
                 (MonadIO m, DocumentClass self, GlibString string) =>
                   self -> m (Maybe string)
getInputEncoding self
  = liftIO
      (((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_input_encoding argPtr1)
{-# LINE 760 "./Graphics/UI/Gtk/WebKit/DOM/Document.chs" #-}
          (toDocument self))
         >>=
         maybePeek readUTFString)
 
getXmlEncoding ::
               (MonadIO m, DocumentClass self, GlibString string) =>
                 self -> m (Maybe string)
getXmlEncoding self
  = liftIO
      (((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_xml_encoding argPtr1)
{-# LINE 770 "./Graphics/UI/Gtk/WebKit/DOM/Document.chs" #-}
          (toDocument self))
         >>=
         maybePeek readUTFString)
 
setXmlVersion ::
              (MonadIO m, DocumentClass self, GlibString string) =>
                self -> (Maybe string) -> m ()
setXmlVersion self val
  = liftIO
      (propagateGError $
         \ errorPtr_ ->
           maybeWith withUTFString val $
             \ valPtr ->
               (\(Document arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_set_xml_version argPtr1 arg2 arg3) (toDocument self)
                 valPtr
             errorPtr_)
 
getXmlVersion ::
              (MonadIO m, DocumentClass self, GlibString string) =>
                self -> m (Maybe string)
getXmlVersion self
  = liftIO
      (((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_xml_version argPtr1) (toDocument self))
         >>=
         maybePeek readUTFString)
 
setXmlStandalone ::
                 (MonadIO m, DocumentClass self) => self -> Bool -> m ()
setXmlStandalone self val
  = liftIO
      (propagateGError $
         \ errorPtr_ ->
           (\(Document arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_set_xml_standalone argPtr1 arg2 arg3) (toDocument self)
             (fromBool val)
             errorPtr_)
 
getXmlStandalone ::
                 (MonadIO m, DocumentClass self) => self -> m Bool
getXmlStandalone self
  = liftIO
      (toBool <$>
         ((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_xml_standalone argPtr1)
{-# LINE 812 "./Graphics/UI/Gtk/WebKit/DOM/Document.chs" #-}
            (toDocument self)))
 
getDocumentURI ::
               (MonadIO m, DocumentClass self, GlibString string) =>
                 self -> m (Maybe string)
getDocumentURI self
  = liftIO
      (((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_document_uri argPtr1)
{-# LINE 820 "./Graphics/UI/Gtk/WebKit/DOM/Document.chs" #-}
          (toDocument self))
         >>=
         maybePeek readUTFString)
 
getDefaultView ::
               (MonadIO m, DocumentClass self) => self -> m (Maybe Window)
getDefaultView self
  = liftIO
      (maybeNull (makeNewGObject mkWindow)
         ((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_default_view argPtr1)
{-# LINE 830 "./Graphics/UI/Gtk/WebKit/DOM/Document.chs" #-}
            (toDocument self)))
 
getStyleSheets ::
               (MonadIO m, DocumentClass self) => self -> m (Maybe StyleSheetList)
getStyleSheets self
  = liftIO
      (maybeNull (makeNewGObject mkStyleSheetList)
         ((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_style_sheets argPtr1)
{-# LINE 838 "./Graphics/UI/Gtk/WebKit/DOM/Document.chs" #-}
            (toDocument self)))
 
setTitle ::
         (MonadIO m, DocumentClass self, GlibString string) =>
           self -> (Maybe string) -> m ()
setTitle self val
  = liftIO
      (maybeWith withUTFString val $
         \ valPtr ->
           (\(Document arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_set_title argPtr1 arg2) (toDocument self) valPtr)
 
getTitle ::
         (MonadIO m, DocumentClass self, GlibString string) =>
           self -> m (Maybe string)
getTitle self
  = liftIO
      (((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_title argPtr1) (toDocument self)) >>=
         maybePeek readUTFString)
 
getReferrer ::
            (MonadIO m, DocumentClass self, GlibString string) =>
              self -> m string
getReferrer self
  = liftIO
      (((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_referrer argPtr1) (toDocument self))
         >>=
         readUTFString)
 
getDomain ::
          (MonadIO m, DocumentClass self, GlibString string) =>
            self -> m string
getDomain self
  = liftIO
      (((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_domain argPtr1) (toDocument self)) >>=
         readUTFString)
 
setCookie ::
          (MonadIO m, DocumentClass self, GlibString string) =>
            self -> (Maybe string) -> m ()
setCookie self val
  = liftIO
      (propagateGError $
         \ errorPtr_ ->
           maybeWith withUTFString val $
             \ valPtr ->
               (\(Document arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_set_cookie argPtr1 arg2 arg3) (toDocument self) valPtr
             errorPtr_)
 
getCookie ::
          (MonadIO m, DocumentClass self, GlibString string) =>
            self -> m (Maybe string)
getCookie self
  = liftIO
      ((propagateGError $
          \ errorPtr_ ->
            (\(Document arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_cookie argPtr1 arg2) (toDocument self)
              errorPtr_)
         >>=
         maybePeek readUTFString)
 
setBody ::
        (MonadIO m, HTMLElementClass val, DocumentClass self) =>
          self -> Maybe val -> m ()
setBody self val
  = liftIO
      (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_)
 
getBody ::
        (MonadIO m, DocumentClass self) => self -> m (Maybe HTMLElement)
getBody self
  = liftIO
      (maybeNull (makeNewGObject mkHTMLElement)
         ((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_body argPtr1) (toDocument self)))
 
getHead ::
        (MonadIO m, DocumentClass self) =>
          self -> m (Maybe HTMLHeadElement)
getHead self
  = liftIO
      (maybeNull (makeNewGObject mkHTMLHeadElement)
         ((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_head argPtr1) (toDocument self)))
 
getImages ::
          (MonadIO m, DocumentClass self) => self -> m (Maybe HTMLCollection)
getImages self
  = liftIO
      (maybeNull (makeNewGObject mkHTMLCollection)
         ((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_images argPtr1) (toDocument self)))
 
getApplets ::
           (MonadIO m, DocumentClass self) => self -> m (Maybe HTMLCollection)
getApplets self
  = liftIO
      (maybeNull (makeNewGObject mkHTMLCollection)
         ((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_applets argPtr1) (toDocument self)))
 
getLinks ::
         (MonadIO m, DocumentClass self) => self -> m (Maybe HTMLCollection)
getLinks self
  = liftIO
      (maybeNull (makeNewGObject mkHTMLCollection)
         ((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_links argPtr1) (toDocument self)))
 
getForms ::
         (MonadIO m, DocumentClass self) => self -> m (Maybe HTMLCollection)
getForms self
  = liftIO
      (maybeNull (makeNewGObject mkHTMLCollection)
         ((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_forms argPtr1) (toDocument self)))
 
getAnchors ::
           (MonadIO m, DocumentClass self) => self -> m (Maybe HTMLCollection)
getAnchors self
  = liftIO
      (maybeNull (makeNewGObject mkHTMLCollection)
         ((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_anchors argPtr1) (toDocument self)))
 
getLastModified ::
                (MonadIO m, DocumentClass self, GlibString string) =>
                  self -> m string
getLastModified self
  = liftIO
      (((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_last_modified argPtr1)
{-# LINE 965 "./Graphics/UI/Gtk/WebKit/DOM/Document.chs" #-}
          (toDocument self))
         >>=
         readUTFString)
 
setCharset ::
           (MonadIO m, DocumentClass self, GlibString string) =>
             self -> (Maybe string) -> m ()
setCharset self val
  = liftIO
      (maybeWith withUTFString val $
         \ valPtr ->
           (\(Document arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_set_charset argPtr1 arg2) (toDocument self)
             valPtr)
 
getCharset ::
           (MonadIO m, DocumentClass self, GlibString string) =>
             self -> m (Maybe string)
getCharset self
  = liftIO
      (((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_charset argPtr1) (toDocument self)) >>=
         maybePeek readUTFString)
 
getDefaultCharset ::
                  (MonadIO m, DocumentClass self, GlibString string) =>
                    self -> m (Maybe string)
getDefaultCharset self
  = liftIO
      (((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_default_charset argPtr1)
{-# LINE 993 "./Graphics/UI/Gtk/WebKit/DOM/Document.chs" #-}
          (toDocument self))
         >>=
         maybePeek readUTFString)
 
getReadyState ::
              (MonadIO m, DocumentClass self, GlibString string) =>
                self -> m (Maybe string)
getReadyState self
  = liftIO
      (((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_ready_state argPtr1) (toDocument self))
         >>=
         maybePeek readUTFString)
 
getCharacterSet ::
                (MonadIO m, DocumentClass self, GlibString string) =>
                  self -> m (Maybe string)
getCharacterSet self
  = liftIO
      (((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_character_set argPtr1)
{-# LINE 1012 "./Graphics/UI/Gtk/WebKit/DOM/Document.chs" #-}
          (toDocument self))
         >>=
         maybePeek readUTFString)
 
getPreferredStylesheetSet ::
                          (MonadIO m, DocumentClass self, GlibString string) =>
                            self -> m (Maybe string)
getPreferredStylesheetSet self
  = liftIO
      (((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_preferred_stylesheet_set argPtr1)
{-# LINE 1022 "./Graphics/UI/Gtk/WebKit/DOM/Document.chs" #-}
          (toDocument self))
         >>=
         maybePeek readUTFString)
 
setSelectedStylesheetSet ::
                         (MonadIO m, DocumentClass self, GlibString string) =>
                           self -> (Maybe string) -> m ()
setSelectedStylesheetSet self val
  = liftIO
      (maybeWith withUTFString val $
         \ valPtr ->
           (\(Document arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_set_selected_stylesheet_set argPtr1 arg2)
{-# LINE 1034 "./Graphics/UI/Gtk/WebKit/DOM/Document.chs" #-}
             (toDocument self)
             valPtr)
 
getSelectedStylesheetSet ::
                         (MonadIO m, DocumentClass self, GlibString string) =>
                           self -> m (Maybe string)
getSelectedStylesheetSet self
  = liftIO
      (((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_selected_stylesheet_set argPtr1)
{-# LINE 1043 "./Graphics/UI/Gtk/WebKit/DOM/Document.chs" #-}
          (toDocument self))
         >>=
         maybePeek readUTFString)
 
getCompatMode ::
              (MonadIO m, DocumentClass self, GlibString string) =>
                self -> m string
getCompatMode self
  = liftIO
      (((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_compat_mode argPtr1) (toDocument self))
         >>=
         readUTFString)
 
getWebkitIsFullScreen ::
                      (MonadIO m, DocumentClass self) => self -> m Bool
getWebkitIsFullScreen self
  = liftIO
      (toBool <$>
         ((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_webkit_is_full_screen argPtr1)
{-# LINE 1062 "./Graphics/UI/Gtk/WebKit/DOM/Document.chs" #-}
            (toDocument self)))
 
getWebkitFullScreenKeyboardInputAllowed ::
                                        (MonadIO m, DocumentClass self) => self -> m Bool
getWebkitFullScreenKeyboardInputAllowed self
  = liftIO
      (toBool <$>
         ((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_webkit_full_screen_keyboard_input_allowed argPtr1)
{-# LINE 1072 "./Graphics/UI/Gtk/WebKit/DOM/Document.chs" #-}
            (toDocument self)))
 
getWebkitCurrentFullScreenElement ::
                                  (MonadIO m, DocumentClass self) => self -> m (Maybe Element)
getWebkitCurrentFullScreenElement self
  = liftIO
      (maybeNull (makeNewGObject mkElement)
         ((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_webkit_current_full_screen_element argPtr1)
{-# LINE 1081 "./Graphics/UI/Gtk/WebKit/DOM/Document.chs" #-}
            (toDocument self)))

getWebkitFullscreenEnabled ::
                           (MonadIO m, DocumentClass self) => self -> m Bool
getWebkitFullscreenEnabled self
  = liftIO
      (toBool <$>
         ((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_webkit_fullscreen_enabled argPtr1)
{-# LINE 1090 "./Graphics/UI/Gtk/WebKit/DOM/Document.chs" #-}
            (toDocument self)))
 
getWebkitFullscreenElement ::
                           (MonadIO m, DocumentClass self) => self -> m (Maybe Element)
getWebkitFullscreenElement self
  = liftIO
      (maybeNull (makeNewGObject mkElement)
         ((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_webkit_fullscreen_element argPtr1)
{-# LINE 1098 "./Graphics/UI/Gtk/WebKit/DOM/Document.chs" #-}
            (toDocument self)))
 
abort :: (DocumentClass self) => EventName self UIEvent
abort = EventName "abort"
 
blur :: (DocumentClass self) => EventName self UIEvent
blur = EventName "blur"
 
change :: (DocumentClass self) => EventName self Event
change = EventName "change"
 
click :: (DocumentClass self) => EventName self MouseEvent
click = EventName "click"
 
contextMenu :: (DocumentClass self) => EventName self MouseEvent
contextMenu = EventName "contextmenu"
 
dblClick :: (DocumentClass self) => EventName self MouseEvent
dblClick = EventName "dblclick"
 
drag :: (DocumentClass self) => EventName self MouseEvent
drag = EventName "drag"
 
dragEnd :: (DocumentClass self) => EventName self MouseEvent
dragEnd = EventName "dragend"
 
dragEnter :: (DocumentClass self) => EventName self MouseEvent
dragEnter = EventName "dragenter"
 
dragLeave :: (DocumentClass self) => EventName self MouseEvent
dragLeave = EventName "dragleave"
 
dragOver :: (DocumentClass self) => EventName self MouseEvent
dragOver = EventName "dragover"
 
dragStart :: (DocumentClass self) => EventName self MouseEvent
dragStart = EventName "dragstart"
 
drop :: (DocumentClass self) => EventName self MouseEvent
drop = EventName "drop"
 
error :: (DocumentClass self) => EventName self UIEvent
error = EventName "error"
 
focus :: (DocumentClass self) => EventName self UIEvent
focus = EventName "focus"
 
input :: (DocumentClass self) => EventName self Event
input = EventName "input"
 
invalid :: (DocumentClass self) => EventName self Event
invalid = EventName "invalid"

keyDown :: (DocumentClass self) => EventName self KeyboardEvent
keyDown = EventName "keydown"
 
keyPress :: (DocumentClass self) => EventName self KeyboardEvent
keyPress = EventName "keypress"
 
keyUp :: (DocumentClass self) => EventName self KeyboardEvent
keyUp = EventName "keyup"
 
load :: (DocumentClass self) => EventName self UIEvent
load = EventName "load"
 
mouseDown :: (DocumentClass self) => EventName self MouseEvent
mouseDown = EventName "mousedown"
 
mouseEnter :: (DocumentClass self) => EventName self MouseEvent
mouseEnter = EventName "mouseenter"
 
mouseLeave :: (DocumentClass self) => EventName self MouseEvent
mouseLeave = EventName "mouseleave"
 
mouseMove :: (DocumentClass self) => EventName self MouseEvent
mouseMove = EventName "mousemove"
 
mouseOut :: (DocumentClass self) => EventName self MouseEvent
mouseOut = EventName "mouseout"
 
mouseOver :: (DocumentClass self) => EventName self MouseEvent
mouseOver = EventName "mouseover"
 
mouseUp :: (DocumentClass self) => EventName self MouseEvent
mouseUp = EventName "mouseup"
 
mouseWheel :: (DocumentClass self) => EventName self MouseEvent
mouseWheel = EventName "mousewheel"
 
readyStateChange :: (DocumentClass self) => EventName self Event
readyStateChange = EventName "readystatechange"
 
scroll :: (DocumentClass self) => EventName self UIEvent
scroll = EventName "scroll"
 
select :: (DocumentClass self) => EventName self UIEvent
select = EventName "select"
 
submit :: (DocumentClass self) => EventName self Event
submit = EventName "submit"

wheel :: (DocumentClass self) => EventName self WheelEvent
wheel = EventName "wheel"
 
beforeCut :: (DocumentClass self) => EventName self Event
beforeCut = EventName "beforecut"
 
cut :: (DocumentClass self) => EventName self Event
cut = EventName "cut"
 
beforeCopy :: (DocumentClass self) => EventName self Event
beforeCopy = EventName "beforecopy"
 
copy :: (DocumentClass self) => EventName self Event
copy = EventName "copy"
 
beforePaste :: (DocumentClass self) => EventName self Event
beforePaste = EventName "beforepaste"
 
paste :: (DocumentClass self) => EventName self Event
paste = EventName "paste"
 
reset :: (DocumentClass self) => EventName self Event
reset = EventName "reset"
 
search :: (DocumentClass self) => EventName self Event
search = EventName "search"
 
selectStart :: (DocumentClass self) => EventName self Event
selectStart = EventName "selectstart"
 
selectionchange :: (DocumentClass self) => EventName self Event
selectionchange = EventName "selectionchange"
 
touchStart :: (DocumentClass self) => EventName self UIEvent
touchStart = EventName "touchstart"
 
touchMove :: (DocumentClass self) => EventName self UIEvent
touchMove = EventName "touchmove"
 
touchEnd :: (DocumentClass self) => EventName self UIEvent
touchEnd = EventName "touchend"
 
touchCancel :: (DocumentClass self) => EventName self UIEvent
touchCancel = EventName "touchcancel"
 
webKitFullscreenChange ::
                       (DocumentClass self) => EventName self Event
webKitFullscreenChange = EventName "webkitfullscreenchange"
 
webKitFullscreenError ::
                      (DocumentClass self) => EventName self Event
webKitFullscreenError = EventName "webkitfullscreenerror"
 
pointerlockchange :: (DocumentClass self) => EventName self Event
pointerlockchange = EventName "pointerlockchange"
 
pointerlockerror :: (DocumentClass self) => EventName self Event
pointerlockerror = EventName "pointerlockerror"
 
securitypolicyviolation ::
                        (DocumentClass self) => EventName self Event
securitypolicyviolation = EventName "securitypolicyviolation"
 
webKitWillRevealBottom ::
                       (DocumentClass self) => EventName self Event
webKitWillRevealBottom = EventName "webkitwillrevealbottom"
 
webKitWillRevealLeft ::
                     (DocumentClass self) => EventName self Event
webKitWillRevealLeft = EventName "webkitwillrevealleft"
 
webKitWillRevealRight ::
                      (DocumentClass self) => EventName self Event
webKitWillRevealRight = EventName "webkitwillrevealright"
 
webKitWillRevealTop :: (DocumentClass self) => EventName self Event
webKitWillRevealTop = EventName "webkitwillrevealtop"
 
getVisibilityState ::
                   (MonadIO m, DocumentClass self, GlibString string) =>
                     self -> m string
getVisibilityState self
  = liftIO
      (((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_visibility_state argPtr1)
{-# LINE 1292 "./Graphics/UI/Gtk/WebKit/DOM/Document.chs" #-}
          (toDocument self))
         >>=
         readUTFString)
 
getHidden :: (MonadIO m, DocumentClass self) => self -> m Bool
getHidden self
  = liftIO
      (toBool <$>
         ((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_hidden argPtr1) (toDocument self)))

getSecurityPolicy ::
                  (MonadIO m, DocumentClass self) => self -> m (Maybe SecurityPolicy)
getSecurityPolicy self
  = liftIO
      (maybeNull (makeNewGObject mkSecurityPolicy)
         ((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_security_policy argPtr1)
{-# LINE 1313 "./Graphics/UI/Gtk/WebKit/DOM/Document.chs" #-}
            (toDocument self)))

getCurrentScript ::
                 (MonadIO m, DocumentClass self) =>
                   self -> m (Maybe HTMLScriptElement)
getCurrentScript self
  = liftIO
      (maybeNull (makeNewGObject mkHTMLScriptElement)
         ((\(Document arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_get_current_script argPtr1)
{-# LINE 1324 "./Graphics/UI/Gtk/WebKit/DOM/Document.chs" #-}
            (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 Attr)))))

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 Attr))))))

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 Range)))

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 Range)))))

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_cancel_full_screen"
  webkit_dom_document_webkit_cancel_full_screen :: ((Ptr Document) -> (IO ()))

foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_webkit_exit_fullscreen"
  webkit_dom_document_webkit_exit_fullscreen :: ((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_create_touch"
  webkit_dom_document_create_touch :: ((Ptr Document) -> ((Ptr Window) -> ((Ptr EventTarget) -> (CLong -> (CLong -> (CLong -> (CLong -> (CLong -> (CLong -> (CLong -> (CFloat -> (CFloat -> ((Ptr (Ptr ())) -> (IO (Ptr Touch)))))))))))))))

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_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 Window)))

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_is_full_screen"
  webkit_dom_document_get_webkit_is_full_screen :: ((Ptr Document) -> (IO CInt))

foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_get_webkit_full_screen_keyboard_input_allowed"
  webkit_dom_document_get_webkit_full_screen_keyboard_input_allowed :: ((Ptr Document) -> (IO CInt))

foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_get_webkit_current_full_screen_element"
  webkit_dom_document_get_webkit_current_full_screen_element :: ((Ptr Document) -> (IO (Ptr Element)))

foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_get_webkit_fullscreen_enabled"
  webkit_dom_document_get_webkit_fullscreen_enabled :: ((Ptr Document) -> (IO CInt))

foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Document.h webkit_dom_document_get_webkit_fullscreen_element"
  webkit_dom_document_get_webkit_fullscreen_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 SecurityPolicy)))

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)))