module Graphics.UI.Gtk.WebKit.DOM.DOMWindowCSS
(
domWindowCSSSupports, DOMWindowCSS, DOMWindowCSSClass,
castToDOMWindowCSS, gTypeDOMWindowCSS, toDOMWindowCSS
) 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
domWindowCSSSupports ::
(DOMWindowCSSClass self, GlibString string) =>
self -> string -> string -> IO Bool
domWindowCSSSupports self property value
= toBool <$>
(withUTFString value $
\ valuePtr ->
withUTFString property $
\ propertyPtr ->
(\(DOMWindowCSS arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_css_supports argPtr1 arg2 arg3) (toDOMWindowCSS self)
propertyPtr
valuePtr)
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/DOMWindowCSS.h webkit_dom_dom_window_css_supports"
webkit_dom_dom_window_css_supports :: ((Ptr DOMWindowCSS) -> ((Ptr CChar) -> ((Ptr CChar) -> (IO CInt))))