module Graphics.UI.Gtk.WebKit.DOM.DocumentType(
getName,
getEntities,
getNotations,
getPublicId,
getSystemId,
getInternalSubset,
DocumentType,
castToDocumentType,
gTypeDocumentType,
DocumentTypeClass,
toDocumentType,
) 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
import Graphics.UI.Gtk.WebKit.DOM.Enums
 
getName ::
        (MonadIO m, DocumentTypeClass self, GlibString string) =>
          self -> m string
getName self
  = liftIO
      (((\(DocumentType arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_type_get_name argPtr1)
          (toDocumentType self))
         >>=
         readUTFString)
 
getEntities ::
            (MonadIO m, DocumentTypeClass self) =>
              self -> m (Maybe NamedNodeMap)
getEntities self
  = liftIO
      (maybeNull (makeNewGObject mkNamedNodeMap)
         ((\(DocumentType arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_type_get_entities argPtr1)
            (toDocumentType self)))
 
getNotations ::
             (MonadIO m, DocumentTypeClass self) =>
               self -> m (Maybe NamedNodeMap)
getNotations self
  = liftIO
      (maybeNull (makeNewGObject mkNamedNodeMap)
         ((\(DocumentType arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_type_get_notations argPtr1)
            (toDocumentType self)))
 
getPublicId ::
            (MonadIO m, DocumentTypeClass self, GlibString string) =>
              self -> m (Maybe string)
getPublicId self
  = liftIO
      (((\(DocumentType arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_type_get_public_id argPtr1)
          (toDocumentType self))
         >>=
         maybePeek readUTFString)
 
getSystemId ::
            (MonadIO m, DocumentTypeClass self, GlibString string) =>
              self -> m (Maybe string)
getSystemId self
  = liftIO
      (((\(DocumentType arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_type_get_system_id argPtr1)
          (toDocumentType self))
         >>=
         maybePeek readUTFString)
 
getInternalSubset ::
                  (MonadIO m, DocumentTypeClass self, GlibString string) =>
                    self -> m (Maybe string)
getInternalSubset self
  = liftIO
      (((\(DocumentType arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_document_type_get_internal_subset argPtr1)
          (toDocumentType self))
         >>=
         maybePeek readUTFString)
foreign import ccall safe "webkit_dom_document_type_get_name"
  webkit_dom_document_type_get_name :: ((Ptr DocumentType) -> (IO (Ptr CChar)))
foreign import ccall safe "webkit_dom_document_type_get_entities"
  webkit_dom_document_type_get_entities :: ((Ptr DocumentType) -> (IO (Ptr NamedNodeMap)))
foreign import ccall safe "webkit_dom_document_type_get_notations"
  webkit_dom_document_type_get_notations :: ((Ptr DocumentType) -> (IO (Ptr NamedNodeMap)))
foreign import ccall safe "webkit_dom_document_type_get_public_id"
  webkit_dom_document_type_get_public_id :: ((Ptr DocumentType) -> (IO (Ptr CChar)))
foreign import ccall safe "webkit_dom_document_type_get_system_id"
  webkit_dom_document_type_get_system_id :: ((Ptr DocumentType) -> (IO (Ptr CChar)))
foreign import ccall safe "webkit_dom_document_type_get_internal_subset"
  webkit_dom_document_type_get_internal_subset :: ((Ptr DocumentType) -> (IO (Ptr CChar)))