{-# LANGUAGE PatternSynonyms, ForeignFunctionInterface, JavaScriptFFI #-} module GHCJS.DOM.JSFFI.Generated.HTMLDocument (js_open, open, js_close, close, js_write, write, js_writeln, writeln, js_clear, clear, js_captureEvents, captureEvents, js_releaseEvents, releaseEvents, js_getEmbeds, getEmbeds, getEmbedsUnchecked, js_getPlugins, getPlugins, getPluginsUnchecked, js_getScripts, getScripts, getScriptsUnchecked, js_getAll, getAll, getAllUnchecked, js_getWidth, getWidth, js_getHeight, getHeight, js_setDir, setDir, js_getDir, getDir, getDirUnchecked, js_setDesignMode, setDesignMode, js_getDesignMode, getDesignMode, getDesignModeUnchecked, js_getCompatMode, getCompatMode, js_setBgColor, setBgColor, js_getBgColor, getBgColor, getBgColorUnchecked, js_setFgColor, setFgColor, js_getFgColor, getFgColor, getFgColorUnchecked, js_setAlinkColor, setAlinkColor, js_getAlinkColor, getAlinkColor, getAlinkColorUnchecked, js_setLinkColor, setLinkColor, js_getLinkColor, getLinkColor, getLinkColorUnchecked, js_setVlinkColor, setVlinkColor, js_getVlinkColor, getVlinkColor, getVlinkColorUnchecked, HTMLDocument, castToHTMLDocument, gTypeHTMLDocument) 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[\"open\"]()" js_open :: HTMLDocument -> IO () -- | open :: (MonadIO m) => HTMLDocument -> m () open self = liftIO (js_open (self)) foreign import javascript unsafe "$1[\"close\"]()" js_close :: HTMLDocument -> IO () -- | close :: (MonadIO m) => HTMLDocument -> m () close self = liftIO (js_close (self)) foreign import javascript unsafe "$1[\"write\"]($2)" js_write :: HTMLDocument -> JSString -> IO () -- | write :: (MonadIO m, ToJSString text) => HTMLDocument -> text -> m () write self text = liftIO (js_write (self) (toJSString text)) foreign import javascript unsafe "$1[\"writeln\"]($2)" js_writeln :: HTMLDocument -> JSString -> IO () -- | writeln :: (MonadIO m, ToJSString text) => HTMLDocument -> text -> m () writeln self text = liftIO (js_writeln (self) (toJSString text)) foreign import javascript unsafe "$1[\"clear\"]()" js_clear :: HTMLDocument -> IO () -- | clear :: (MonadIO m) => HTMLDocument -> m () clear self = liftIO (js_clear (self)) foreign import javascript unsafe "$1[\"captureEvents\"]()" js_captureEvents :: HTMLDocument -> IO () -- | captureEvents :: (MonadIO m) => HTMLDocument -> m () captureEvents self = liftIO (js_captureEvents (self)) foreign import javascript unsafe "$1[\"releaseEvents\"]()" js_releaseEvents :: HTMLDocument -> IO () -- | releaseEvents :: (MonadIO m) => HTMLDocument -> m () releaseEvents self = liftIO (js_releaseEvents (self)) foreign import javascript unsafe "$1[\"embeds\"]" js_getEmbeds :: HTMLDocument -> IO (Nullable HTMLCollection) -- | getEmbeds :: (MonadIO m) => HTMLDocument -> m (Maybe HTMLCollection) getEmbeds self = liftIO (nullableToMaybe <$> (js_getEmbeds (self))) -- | getEmbedsUnchecked :: (MonadIO m) => HTMLDocument -> m HTMLCollection getEmbedsUnchecked self = liftIO (fromJust . nullableToMaybe <$> (js_getEmbeds (self))) foreign import javascript unsafe "$1[\"plugins\"]" js_getPlugins :: HTMLDocument -> IO (Nullable HTMLCollection) -- | getPlugins :: (MonadIO m) => HTMLDocument -> m (Maybe HTMLCollection) getPlugins self = liftIO (nullableToMaybe <$> (js_getPlugins (self))) -- | getPluginsUnchecked :: (MonadIO m) => HTMLDocument -> m HTMLCollection getPluginsUnchecked self = liftIO (fromJust . nullableToMaybe <$> (js_getPlugins (self))) foreign import javascript unsafe "$1[\"scripts\"]" js_getScripts :: HTMLDocument -> IO (Nullable HTMLCollection) -- | getScripts :: (MonadIO m) => HTMLDocument -> m (Maybe HTMLCollection) getScripts self = liftIO (nullableToMaybe <$> (js_getScripts (self))) -- | getScriptsUnchecked :: (MonadIO m) => HTMLDocument -> m HTMLCollection getScriptsUnchecked self = liftIO (fromJust . nullableToMaybe <$> (js_getScripts (self))) foreign import javascript unsafe "$1[\"all\"]" js_getAll :: HTMLDocument -> IO (Nullable HTMLAllCollection) -- | getAll :: (MonadIO m) => HTMLDocument -> m (Maybe HTMLAllCollection) getAll self = liftIO (nullableToMaybe <$> (js_getAll (self))) -- | getAllUnchecked :: (MonadIO m) => HTMLDocument -> m HTMLAllCollection getAllUnchecked self = liftIO (fromJust . nullableToMaybe <$> (js_getAll (self))) foreign import javascript unsafe "$1[\"width\"]" js_getWidth :: HTMLDocument -> IO Int -- | getWidth :: (MonadIO m) => HTMLDocument -> m Int getWidth self = liftIO (js_getWidth (self)) foreign import javascript unsafe "$1[\"height\"]" js_getHeight :: HTMLDocument -> IO Int -- | getHeight :: (MonadIO m) => HTMLDocument -> m Int getHeight self = liftIO (js_getHeight (self)) foreign import javascript unsafe "$1[\"dir\"] = $2;" js_setDir :: HTMLDocument -> Nullable JSString -> IO () -- | setDir :: (MonadIO m, ToJSString val) => HTMLDocument -> Maybe val -> m () setDir self val = liftIO (js_setDir (self) (toMaybeJSString val)) foreign import javascript unsafe "$1[\"dir\"]" js_getDir :: HTMLDocument -> IO (Nullable JSString) -- | getDir :: (MonadIO m, FromJSString result) => HTMLDocument -> m (Maybe result) getDir self = liftIO (fromMaybeJSString <$> (js_getDir (self))) -- | getDirUnchecked :: (MonadIO m, FromJSString result) => HTMLDocument -> m result getDirUnchecked self = liftIO (fromJust . fromMaybeJSString <$> (js_getDir (self))) foreign import javascript unsafe "$1[\"designMode\"] = $2;" js_setDesignMode :: HTMLDocument -> Nullable JSString -> IO () -- | setDesignMode :: (MonadIO m, ToJSString val) => HTMLDocument -> Maybe val -> m () setDesignMode self val = liftIO (js_setDesignMode (self) (toMaybeJSString val)) foreign import javascript unsafe "$1[\"designMode\"]" js_getDesignMode :: HTMLDocument -> IO (Nullable JSString) -- | getDesignMode :: (MonadIO m, FromJSString result) => HTMLDocument -> m (Maybe result) getDesignMode self = liftIO (fromMaybeJSString <$> (js_getDesignMode (self))) -- | getDesignModeUnchecked :: (MonadIO m, FromJSString result) => HTMLDocument -> m result getDesignModeUnchecked self = liftIO (fromJust . fromMaybeJSString <$> (js_getDesignMode (self))) foreign import javascript unsafe "$1[\"compatMode\"]" js_getCompatMode :: HTMLDocument -> IO JSString -- | getCompatMode :: (MonadIO m, FromJSString result) => HTMLDocument -> m result getCompatMode self = liftIO (fromJSString <$> (js_getCompatMode (self))) foreign import javascript unsafe "$1[\"bgColor\"] = $2;" js_setBgColor :: HTMLDocument -> Nullable JSString -> IO () -- | setBgColor :: (MonadIO m, ToJSString val) => HTMLDocument -> Maybe val -> m () setBgColor self val = liftIO (js_setBgColor (self) (toMaybeJSString val)) foreign import javascript unsafe "$1[\"bgColor\"]" js_getBgColor :: HTMLDocument -> IO (Nullable JSString) -- | getBgColor :: (MonadIO m, FromJSString result) => HTMLDocument -> m (Maybe result) getBgColor self = liftIO (fromMaybeJSString <$> (js_getBgColor (self))) -- | getBgColorUnchecked :: (MonadIO m, FromJSString result) => HTMLDocument -> m result getBgColorUnchecked self = liftIO (fromJust . fromMaybeJSString <$> (js_getBgColor (self))) foreign import javascript unsafe "$1[\"fgColor\"] = $2;" js_setFgColor :: HTMLDocument -> Nullable JSString -> IO () -- | setFgColor :: (MonadIO m, ToJSString val) => HTMLDocument -> Maybe val -> m () setFgColor self val = liftIO (js_setFgColor (self) (toMaybeJSString val)) foreign import javascript unsafe "$1[\"fgColor\"]" js_getFgColor :: HTMLDocument -> IO (Nullable JSString) -- | getFgColor :: (MonadIO m, FromJSString result) => HTMLDocument -> m (Maybe result) getFgColor self = liftIO (fromMaybeJSString <$> (js_getFgColor (self))) -- | getFgColorUnchecked :: (MonadIO m, FromJSString result) => HTMLDocument -> m result getFgColorUnchecked self = liftIO (fromJust . fromMaybeJSString <$> (js_getFgColor (self))) foreign import javascript unsafe "$1[\"alinkColor\"] = $2;" js_setAlinkColor :: HTMLDocument -> Nullable JSString -> IO () -- | setAlinkColor :: (MonadIO m, ToJSString val) => HTMLDocument -> Maybe val -> m () setAlinkColor self val = liftIO (js_setAlinkColor (self) (toMaybeJSString val)) foreign import javascript unsafe "$1[\"alinkColor\"]" js_getAlinkColor :: HTMLDocument -> IO (Nullable JSString) -- | getAlinkColor :: (MonadIO m, FromJSString result) => HTMLDocument -> m (Maybe result) getAlinkColor self = liftIO (fromMaybeJSString <$> (js_getAlinkColor (self))) -- | getAlinkColorUnchecked :: (MonadIO m, FromJSString result) => HTMLDocument -> m result getAlinkColorUnchecked self = liftIO (fromJust . fromMaybeJSString <$> (js_getAlinkColor (self))) foreign import javascript unsafe "$1[\"linkColor\"] = $2;" js_setLinkColor :: HTMLDocument -> Nullable JSString -> IO () -- | setLinkColor :: (MonadIO m, ToJSString val) => HTMLDocument -> Maybe val -> m () setLinkColor self val = liftIO (js_setLinkColor (self) (toMaybeJSString val)) foreign import javascript unsafe "$1[\"linkColor\"]" js_getLinkColor :: HTMLDocument -> IO (Nullable JSString) -- | getLinkColor :: (MonadIO m, FromJSString result) => HTMLDocument -> m (Maybe result) getLinkColor self = liftIO (fromMaybeJSString <$> (js_getLinkColor (self))) -- | getLinkColorUnchecked :: (MonadIO m, FromJSString result) => HTMLDocument -> m result getLinkColorUnchecked self = liftIO (fromJust . fromMaybeJSString <$> (js_getLinkColor (self))) foreign import javascript unsafe "$1[\"vlinkColor\"] = $2;" js_setVlinkColor :: HTMLDocument -> Nullable JSString -> IO () -- | setVlinkColor :: (MonadIO m, ToJSString val) => HTMLDocument -> Maybe val -> m () setVlinkColor self val = liftIO (js_setVlinkColor (self) (toMaybeJSString val)) foreign import javascript unsafe "$1[\"vlinkColor\"]" js_getVlinkColor :: HTMLDocument -> IO (Nullable JSString) -- | getVlinkColor :: (MonadIO m, FromJSString result) => HTMLDocument -> m (Maybe result) getVlinkColor self = liftIO (fromMaybeJSString <$> (js_getVlinkColor (self))) -- | getVlinkColorUnchecked :: (MonadIO m, FromJSString result) => HTMLDocument -> m result getVlinkColorUnchecked self = liftIO (fromJust . fromMaybeJSString <$> (js_getVlinkColor (self)))