module Graphics.UI.Gtk.WebKit.DOM.HTMLDocument
(htmlDocumentClose, htmlDocumentClear, htmlDocumentCaptureEvents,
htmlDocumentReleaseEvents, htmlDocumentHasFocus,
htmlDocumentGetEmbeds, htmlDocumentGetPlugins,
htmlDocumentGetScripts, htmlDocumentGetWidth,
htmlDocumentGetHeight, htmlDocumentSetDir, htmlDocumentGetDir,
htmlDocumentSetDesignMode, htmlDocumentGetDesignMode,
htmlDocumentGetCompatMode, htmlDocumentGetActiveElement,
htmlDocumentSetBgColor, htmlDocumentGetBgColor,
htmlDocumentSetFgColor, htmlDocumentGetFgColor,
htmlDocumentSetAlinkColor, htmlDocumentGetAlinkColor,
htmlDocumentSetLinkColor, htmlDocumentGetLinkColor,
htmlDocumentSetVlinkColor, htmlDocumentGetVlinkColor, HTMLDocument,
HTMLDocumentClass, castToHTMLDocument, gTypeHTMLDocument,
toHTMLDocument)
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
htmlDocumentClose :: (HTMLDocumentClass self) => self -> IO ()
htmlDocumentClose self
= (\(HTMLDocument arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_document_close argPtr1) (toHTMLDocument self)
htmlDocumentClear :: (HTMLDocumentClass self) => self -> IO ()
htmlDocumentClear self
= (\(HTMLDocument arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_document_clear argPtr1) (toHTMLDocument self)
htmlDocumentCaptureEvents ::
(HTMLDocumentClass self) => self -> IO ()
htmlDocumentCaptureEvents self
= (\(HTMLDocument arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_document_capture_events argPtr1)
(toHTMLDocument self)
htmlDocumentReleaseEvents ::
(HTMLDocumentClass self) => self -> IO ()
htmlDocumentReleaseEvents self
= (\(HTMLDocument arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_document_release_events argPtr1)
(toHTMLDocument self)
htmlDocumentHasFocus :: (HTMLDocumentClass self) => self -> IO Bool
htmlDocumentHasFocus self
= toBool <$>
((\(HTMLDocument arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_document_has_focus argPtr1)
(toHTMLDocument self))
htmlDocumentGetEmbeds ::
(HTMLDocumentClass self) => self -> IO (Maybe HTMLCollection)
htmlDocumentGetEmbeds self
= maybeNull (makeNewGObject mkHTMLCollection)
((\(HTMLDocument arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_document_get_embeds argPtr1)
(toHTMLDocument self))
htmlDocumentGetPlugins ::
(HTMLDocumentClass self) => self -> IO (Maybe HTMLCollection)
htmlDocumentGetPlugins self
= maybeNull (makeNewGObject mkHTMLCollection)
((\(HTMLDocument arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_document_get_plugins argPtr1)
(toHTMLDocument self))
htmlDocumentGetScripts ::
(HTMLDocumentClass self) => self -> IO (Maybe HTMLCollection)
htmlDocumentGetScripts self
= maybeNull (makeNewGObject mkHTMLCollection)
((\(HTMLDocument arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_document_get_scripts argPtr1)
(toHTMLDocument self))
htmlDocumentGetWidth :: (HTMLDocumentClass self) => self -> IO Int
htmlDocumentGetWidth self
= fromIntegral <$>
((\(HTMLDocument arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_document_get_width argPtr1)
(toHTMLDocument self))
htmlDocumentGetHeight :: (HTMLDocumentClass self) => self -> IO Int
htmlDocumentGetHeight self
= fromIntegral <$>
((\(HTMLDocument arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_document_get_height argPtr1)
(toHTMLDocument self))
htmlDocumentSetDir ::
(HTMLDocumentClass self, GlibString string) =>
self -> string -> IO ()
htmlDocumentSetDir self val
= withUTFString val $
\ valPtr ->
(\(HTMLDocument arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_document_set_dir argPtr1 arg2) (toHTMLDocument self)
valPtr
htmlDocumentGetDir ::
(HTMLDocumentClass self, GlibString string) => self -> IO string
htmlDocumentGetDir self
= ((\(HTMLDocument arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_document_get_dir argPtr1)
(toHTMLDocument self))
>>=
readUTFString
htmlDocumentSetDesignMode ::
(HTMLDocumentClass self, GlibString string) =>
self -> string -> IO ()
htmlDocumentSetDesignMode self val
= withUTFString val $
\ valPtr ->
(\(HTMLDocument arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_document_set_design_mode argPtr1 arg2)
(toHTMLDocument self)
valPtr
htmlDocumentGetDesignMode ::
(HTMLDocumentClass self, GlibString string) => self -> IO string
htmlDocumentGetDesignMode self
= ((\(HTMLDocument arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_document_get_design_mode argPtr1)
(toHTMLDocument self))
>>=
readUTFString
htmlDocumentGetCompatMode ::
(HTMLDocumentClass self, GlibString string) => self -> IO string
htmlDocumentGetCompatMode self
= ((\(HTMLDocument arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_document_get_compat_mode argPtr1)
(toHTMLDocument self))
>>=
readUTFString
htmlDocumentGetActiveElement ::
(HTMLDocumentClass self) => self -> IO (Maybe Element)
htmlDocumentGetActiveElement self
= maybeNull (makeNewGObject mkElement)
((\(HTMLDocument arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_document_get_active_element argPtr1)
(toHTMLDocument self))
htmlDocumentSetBgColor ::
(HTMLDocumentClass self, GlibString string) =>
self -> string -> IO ()
htmlDocumentSetBgColor self val
= withUTFString val $
\ valPtr ->
(\(HTMLDocument arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_document_set_bg_color argPtr1 arg2)
(toHTMLDocument self)
valPtr
htmlDocumentGetBgColor ::
(HTMLDocumentClass self, GlibString string) => self -> IO string
htmlDocumentGetBgColor self
= ((\(HTMLDocument arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_document_get_bg_color argPtr1)
(toHTMLDocument self))
>>=
readUTFString
htmlDocumentSetFgColor ::
(HTMLDocumentClass self, GlibString string) =>
self -> string -> IO ()
htmlDocumentSetFgColor self val
= withUTFString val $
\ valPtr ->
(\(HTMLDocument arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_document_set_fg_color argPtr1 arg2)
(toHTMLDocument self)
valPtr
htmlDocumentGetFgColor ::
(HTMLDocumentClass self, GlibString string) => self -> IO string
htmlDocumentGetFgColor self
= ((\(HTMLDocument arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_document_get_fg_color argPtr1)
(toHTMLDocument self))
>>=
readUTFString
htmlDocumentSetAlinkColor ::
(HTMLDocumentClass self, GlibString string) =>
self -> string -> IO ()
htmlDocumentSetAlinkColor self val
= withUTFString val $
\ valPtr ->
(\(HTMLDocument arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_document_set_alink_color argPtr1 arg2)
(toHTMLDocument self)
valPtr
htmlDocumentGetAlinkColor ::
(HTMLDocumentClass self, GlibString string) => self -> IO string
htmlDocumentGetAlinkColor self
= ((\(HTMLDocument arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_document_get_alink_color argPtr1)
(toHTMLDocument self))
>>=
readUTFString
htmlDocumentSetLinkColor ::
(HTMLDocumentClass self, GlibString string) =>
self -> string -> IO ()
htmlDocumentSetLinkColor self val
= withUTFString val $
\ valPtr ->
(\(HTMLDocument arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_document_set_link_color argPtr1 arg2)
(toHTMLDocument self)
valPtr
htmlDocumentGetLinkColor ::
(HTMLDocumentClass self, GlibString string) => self -> IO string
htmlDocumentGetLinkColor self
= ((\(HTMLDocument arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_document_get_link_color argPtr1)
(toHTMLDocument self))
>>=
readUTFString
htmlDocumentSetVlinkColor ::
(HTMLDocumentClass self, GlibString string) =>
self -> string -> IO ()
htmlDocumentSetVlinkColor self val
= withUTFString val $
\ valPtr ->
(\(HTMLDocument arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_document_set_vlink_color argPtr1 arg2)
(toHTMLDocument self)
valPtr
htmlDocumentGetVlinkColor ::
(HTMLDocumentClass self, GlibString string) => self -> IO string
htmlDocumentGetVlinkColor self
= ((\(HTMLDocument arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_document_get_vlink_color argPtr1)
(toHTMLDocument self))
>>=
readUTFString
foreign import ccall safe "webkit_dom_html_document_close"
webkit_dom_html_document_close :: ((Ptr HTMLDocument) -> (IO ()))
foreign import ccall safe "webkit_dom_html_document_clear"
webkit_dom_html_document_clear :: ((Ptr HTMLDocument) -> (IO ()))
foreign import ccall safe "webkit_dom_html_document_capture_events"
webkit_dom_html_document_capture_events :: ((Ptr HTMLDocument) -> (IO ()))
foreign import ccall safe "webkit_dom_html_document_release_events"
webkit_dom_html_document_release_events :: ((Ptr HTMLDocument) -> (IO ()))
foreign import ccall safe "webkit_dom_html_document_has_focus"
webkit_dom_html_document_has_focus :: ((Ptr HTMLDocument) -> (IO CInt))
foreign import ccall safe "webkit_dom_html_document_get_embeds"
webkit_dom_html_document_get_embeds :: ((Ptr HTMLDocument) -> (IO (Ptr HTMLCollection)))
foreign import ccall safe "webkit_dom_html_document_get_plugins"
webkit_dom_html_document_get_plugins :: ((Ptr HTMLDocument) -> (IO (Ptr HTMLCollection)))
foreign import ccall safe "webkit_dom_html_document_get_scripts"
webkit_dom_html_document_get_scripts :: ((Ptr HTMLDocument) -> (IO (Ptr HTMLCollection)))
foreign import ccall safe "webkit_dom_html_document_get_width"
webkit_dom_html_document_get_width :: ((Ptr HTMLDocument) -> (IO CLong))
foreign import ccall safe "webkit_dom_html_document_get_height"
webkit_dom_html_document_get_height :: ((Ptr HTMLDocument) -> (IO CLong))
foreign import ccall safe "webkit_dom_html_document_set_dir"
webkit_dom_html_document_set_dir :: ((Ptr HTMLDocument) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "webkit_dom_html_document_get_dir"
webkit_dom_html_document_get_dir :: ((Ptr HTMLDocument) -> (IO (Ptr CChar)))
foreign import ccall safe "webkit_dom_html_document_set_design_mode"
webkit_dom_html_document_set_design_mode :: ((Ptr HTMLDocument) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "webkit_dom_html_document_get_design_mode"
webkit_dom_html_document_get_design_mode :: ((Ptr HTMLDocument) -> (IO (Ptr CChar)))
foreign import ccall safe "webkit_dom_html_document_get_compat_mode"
webkit_dom_html_document_get_compat_mode :: ((Ptr HTMLDocument) -> (IO (Ptr CChar)))
foreign import ccall safe "webkit_dom_html_document_get_active_element"
webkit_dom_html_document_get_active_element :: ((Ptr HTMLDocument) -> (IO (Ptr Element)))
foreign import ccall safe "webkit_dom_html_document_set_bg_color"
webkit_dom_html_document_set_bg_color :: ((Ptr HTMLDocument) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "webkit_dom_html_document_get_bg_color"
webkit_dom_html_document_get_bg_color :: ((Ptr HTMLDocument) -> (IO (Ptr CChar)))
foreign import ccall safe "webkit_dom_html_document_set_fg_color"
webkit_dom_html_document_set_fg_color :: ((Ptr HTMLDocument) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "webkit_dom_html_document_get_fg_color"
webkit_dom_html_document_get_fg_color :: ((Ptr HTMLDocument) -> (IO (Ptr CChar)))
foreign import ccall safe "webkit_dom_html_document_set_alink_color"
webkit_dom_html_document_set_alink_color :: ((Ptr HTMLDocument) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "webkit_dom_html_document_get_alink_color"
webkit_dom_html_document_get_alink_color :: ((Ptr HTMLDocument) -> (IO (Ptr CChar)))
foreign import ccall safe "webkit_dom_html_document_set_link_color"
webkit_dom_html_document_set_link_color :: ((Ptr HTMLDocument) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "webkit_dom_html_document_get_link_color"
webkit_dom_html_document_get_link_color :: ((Ptr HTMLDocument) -> (IO (Ptr CChar)))
foreign import ccall safe "webkit_dom_html_document_set_vlink_color"
webkit_dom_html_document_set_vlink_color :: ((Ptr HTMLDocument) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "webkit_dom_html_document_get_vlink_color"
webkit_dom_html_document_get_vlink_color :: ((Ptr HTMLDocument) -> (IO (Ptr CChar)))