{-# LANGUAGE PatternSynonyms, ForeignFunctionInterface, JavaScriptFFI #-} module GHCJS.DOM.JSFFI.Generated.DocumentType (js_getName, getName, js_getEntities, getEntities, getEntitiesUnchecked, js_getNotations, getNotations, getNotationsUnchecked, js_getPublicId, getPublicId, getPublicIdUnchecked, js_getSystemId, getSystemId, getSystemIdUnchecked, js_getInternalSubset, getInternalSubset, getInternalSubsetUnchecked, DocumentType, castToDocumentType, gTypeDocumentType) where import Prelude ((.), (==), (>>=), return, IO, Int, Float, Double, Bool(..), Maybe, maybe, fromIntegral, round, fmap, Show, Read, Eq, Ord) import Data.Typeable (Typeable) import GHCJS.Types (JSVal(..), JSString) import GHCJS.Foreign (jsNull) import GHCJS.Foreign.Callback (syncCallback, asyncCallback, syncCallback1, asyncCallback1, syncCallback2, asyncCallback2, OnBlocked(..)) import GHCJS.Marshal (ToJSVal(..), FromJSVal(..)) import GHCJS.Marshal.Pure (PToJSVal(..), PFromJSVal(..)) import Control.Monad (void) import Control.Monad.IO.Class (MonadIO(..)) import Data.Int (Int64) import Data.Word (Word, Word64) import Data.Maybe (fromJust) import GHCJS.DOM.Types import Control.Applicative ((<$>)) import GHCJS.DOM.EventTargetClosures (EventName, unsafeEventName) import GHCJS.DOM.JSFFI.Generated.Enums foreign import javascript unsafe "$1[\"name\"]" js_getName :: DocumentType -> IO JSString -- | getName :: (MonadIO m, FromJSString result) => DocumentType -> m result getName self = liftIO (fromJSString <$> (js_getName (self))) foreign import javascript unsafe "$1[\"entities\"]" js_getEntities :: DocumentType -> IO (Nullable NamedNodeMap) -- | getEntities :: (MonadIO m) => DocumentType -> m (Maybe NamedNodeMap) getEntities self = liftIO (nullableToMaybe <$> (js_getEntities (self))) -- | getEntitiesUnchecked :: (MonadIO m) => DocumentType -> m NamedNodeMap getEntitiesUnchecked self = liftIO (fromJust . nullableToMaybe <$> (js_getEntities (self))) foreign import javascript unsafe "$1[\"notations\"]" js_getNotations :: DocumentType -> IO (Nullable NamedNodeMap) -- | getNotations :: (MonadIO m) => DocumentType -> m (Maybe NamedNodeMap) getNotations self = liftIO (nullableToMaybe <$> (js_getNotations (self))) -- | getNotationsUnchecked :: (MonadIO m) => DocumentType -> m NamedNodeMap getNotationsUnchecked self = liftIO (fromJust . nullableToMaybe <$> (js_getNotations (self))) foreign import javascript unsafe "$1[\"publicId\"]" js_getPublicId :: DocumentType -> IO (Nullable JSString) -- | getPublicId :: (MonadIO m, FromJSString result) => DocumentType -> m (Maybe result) getPublicId self = liftIO (fromMaybeJSString <$> (js_getPublicId (self))) -- | getPublicIdUnchecked :: (MonadIO m, FromJSString result) => DocumentType -> m result getPublicIdUnchecked self = liftIO (fromJust . fromMaybeJSString <$> (js_getPublicId (self))) foreign import javascript unsafe "$1[\"systemId\"]" js_getSystemId :: DocumentType -> IO (Nullable JSString) -- | getSystemId :: (MonadIO m, FromJSString result) => DocumentType -> m (Maybe result) getSystemId self = liftIO (fromMaybeJSString <$> (js_getSystemId (self))) -- | getSystemIdUnchecked :: (MonadIO m, FromJSString result) => DocumentType -> m result getSystemIdUnchecked self = liftIO (fromJust . fromMaybeJSString <$> (js_getSystemId (self))) foreign import javascript unsafe "$1[\"internalSubset\"]" js_getInternalSubset :: DocumentType -> IO (Nullable JSString) -- | getInternalSubset :: (MonadIO m, FromJSString result) => DocumentType -> m (Maybe result) getInternalSubset self = liftIO (fromMaybeJSString <$> (js_getInternalSubset (self))) -- | getInternalSubsetUnchecked :: (MonadIO m, FromJSString result) => DocumentType -> m result getInternalSubsetUnchecked self = liftIO (fromJust . fromMaybeJSString <$> (js_getInternalSubset (self)))