module Graphics.UI.Gtk.WebKit.DOM.HTMLQuoteElement
(htmlQuoteElementSetCite, htmlQuoteElementGetCite,
HTMLQuoteElement, HTMLQuoteElementClass, castToHTMLQuoteElement,
gTypeHTMLQuoteElement, toHTMLQuoteElement)
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
htmlQuoteElementSetCite ::
(HTMLQuoteElementClass self, GlibString string) =>
self -> string -> IO ()
htmlQuoteElementSetCite self val
= withUTFString val $
\ valPtr ->
(\(HTMLQuoteElement arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_quote_element_set_cite argPtr1 arg2)
(toHTMLQuoteElement self)
valPtr
htmlQuoteElementGetCite ::
(HTMLQuoteElementClass self, GlibString string) =>
self -> IO string
htmlQuoteElementGetCite self
= ((\(HTMLQuoteElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_quote_element_get_cite argPtr1)
(toHTMLQuoteElement self))
>>=
readUTFString
foreign import ccall safe "webkit_dom_html_quote_element_set_cite"
webkit_dom_html_quote_element_set_cite :: ((Ptr HTMLQuoteElement) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "webkit_dom_html_quote_element_get_cite"
webkit_dom_html_quote_element_get_cite :: ((Ptr HTMLQuoteElement) -> (IO (Ptr CChar)))