module Graphics.UI.Gtk.WebKit.DOM.DOMImplementation
       (domImplementationHasFeature, domImplementationCreateDocumentType,
        domImplementationCreateDocument,
        domImplementationCreateCSSStyleSheet,
        domImplementationCreateHTMLDocument, DOMImplementation,
        DOMImplementationClass, castToDOMImplementation,
        gTypeDOMImplementation, toDOMImplementation)
       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
 
domImplementationHasFeature ::
                            (DOMImplementationClass self, GlibString string) =>
                              self -> string -> string -> IO Bool
domImplementationHasFeature self feature version
  = toBool <$>
      (withUTFString version $
         \ versionPtr ->
           withUTFString feature $
             \ featurePtr ->
               (\(DOMImplementation arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_implementation_has_feature argPtr1 arg2 arg3)
                 (toDOMImplementation self)
                 featurePtr
             versionPtr)
 
domImplementationCreateDocumentType ::
                                    (DOMImplementationClass self, GlibString string) =>
                                      self -> string -> string -> string -> IO (Maybe DocumentType)
domImplementationCreateDocumentType self qualifiedName publicId
  systemId
  = maybeNull (makeNewGObject mkDocumentType)
      (propagateGError $
         \ errorPtr_ ->
           withUTFString systemId $
             \ systemIdPtr ->
               withUTFString publicId $
                 \ publicIdPtr ->
                   withUTFString qualifiedName $
                     \ qualifiedNamePtr ->
                       (\(DOMImplementation arg1) arg2 arg3 arg4 arg5 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_implementation_create_document_type argPtr1 arg2 arg3 arg4 arg5)
                         (toDOMImplementation self)
                         qualifiedNamePtr
                     publicIdPtr
                 systemIdPtr
             errorPtr_)
 
domImplementationCreateDocument ::
                                (DOMImplementationClass self, DocumentTypeClass doctype,
                                 GlibString string) =>
                                  self -> string -> string -> Maybe doctype -> IO (Maybe Document)
domImplementationCreateDocument self namespaceURI qualifiedName
  doctype
  = maybeNull (makeNewGObject mkDocument)
      (propagateGError $
         \ errorPtr_ ->
           withUTFString qualifiedName $
             \ qualifiedNamePtr ->
               withUTFString namespaceURI $
                 \ namespaceURIPtr ->
                   (\(DOMImplementation arg1) arg2 arg3 (DocumentType arg4) arg5 -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg4 $ \argPtr4 ->webkit_dom_dom_implementation_create_document argPtr1 arg2 arg3 argPtr4 arg5)
                     (toDOMImplementation self)
                     namespaceURIPtr
                 qualifiedNamePtr
             (maybe (DocumentType nullForeignPtr) toDocumentType doctype)
             errorPtr_)
 
domImplementationCreateCSSStyleSheet ::
                                     (DOMImplementationClass self, GlibString string) =>
                                       self -> string -> string -> IO (Maybe CSSStyleSheet)
domImplementationCreateCSSStyleSheet self title media
  = maybeNull (makeNewGObject mkCSSStyleSheet)
      (propagateGError $
         \ errorPtr_ ->
           withUTFString media $
             \ mediaPtr ->
               withUTFString title $
                 \ titlePtr ->
                   (\(DOMImplementation arg1) arg2 arg3 arg4 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_implementation_create_css_style_sheet argPtr1 arg2 arg3 arg4)
                     (toDOMImplementation self)
                     titlePtr
                 mediaPtr
             errorPtr_)
 
domImplementationCreateHTMLDocument ::
                                    (DOMImplementationClass self, GlibString string) =>
                                      self -> string -> IO (Maybe HTMLDocument)
domImplementationCreateHTMLDocument self title
  = maybeNull (makeNewGObject mkHTMLDocument)
      (withUTFString title $
         \ titlePtr ->
           (\(DOMImplementation arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_implementation_create_html_document argPtr1 arg2)
             (toDOMImplementation self)
             titlePtr)
foreign import ccall safe "webkit_dom_dom_implementation_has_feature"
  webkit_dom_dom_implementation_has_feature :: ((Ptr DOMImplementation) -> ((Ptr CChar) -> ((Ptr CChar) -> (IO CInt))))
foreign import ccall safe "webkit_dom_dom_implementation_create_document_type"
  webkit_dom_dom_implementation_create_document_type :: ((Ptr DOMImplementation) -> ((Ptr CChar) -> ((Ptr CChar) -> ((Ptr CChar) -> ((Ptr (Ptr ())) -> (IO (Ptr DocumentType)))))))
foreign import ccall safe "webkit_dom_dom_implementation_create_document"
  webkit_dom_dom_implementation_create_document :: ((Ptr DOMImplementation) -> ((Ptr CChar) -> ((Ptr CChar) -> ((Ptr DocumentType) -> ((Ptr (Ptr ())) -> (IO (Ptr Document)))))))
foreign import ccall safe "webkit_dom_dom_implementation_create_css_style_sheet"
  webkit_dom_dom_implementation_create_css_style_sheet :: ((Ptr DOMImplementation) -> ((Ptr CChar) -> ((Ptr CChar) -> ((Ptr (Ptr ())) -> (IO (Ptr CSSStyleSheet))))))
foreign import ccall safe "webkit_dom_dom_implementation_create_html_document"
  webkit_dom_dom_implementation_create_html_document :: ((Ptr DOMImplementation) -> ((Ptr CChar) -> (IO (Ptr HTMLDocument))))