module Graphics.UI.Gtk.WebKit.DOM.CSSStyleDeclaration
(cssStyleDeclarationGetPropertyValue,
cssStyleDeclarationRemoveProperty,
cssStyleDeclarationGetPropertyPriority,
cssStyleDeclarationSetProperty, cssStyleDeclarationItem,
cssStyleDeclarationGetPropertyShorthand,
cssStyleDeclarationIsPropertyImplicit,
cssStyleDeclarationSetCssText, cssStyleDeclarationGetCssText,
cssStyleDeclarationGetLength, cssStyleDeclarationGetParentRule,
CSSStyleDeclaration, CSSStyleDeclarationClass,
castToCSSStyleDeclaration, gTypeCSSStyleDeclaration,
toCSSStyleDeclaration)
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
cssStyleDeclarationGetPropertyValue ::
(CSSStyleDeclarationClass self, GlibString string) =>
self -> string -> IO string
cssStyleDeclarationGetPropertyValue self propertyName
= (withUTFString propertyName $
\ propertyNamePtr ->
(\(CSSStyleDeclaration arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_css_style_declaration_get_property_value argPtr1 arg2)
(toCSSStyleDeclaration self)
propertyNamePtr)
>>=
readUTFString
cssStyleDeclarationRemoveProperty ::
(CSSStyleDeclarationClass self, GlibString string) =>
self -> string -> IO string
cssStyleDeclarationRemoveProperty self propertyName
= (propagateGError $
\ errorPtr_ ->
withUTFString propertyName $
\ propertyNamePtr ->
(\(CSSStyleDeclaration arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_css_style_declaration_remove_property argPtr1 arg2 arg3)
(toCSSStyleDeclaration self)
propertyNamePtr
errorPtr_)
>>=
readUTFString
cssStyleDeclarationGetPropertyPriority ::
(CSSStyleDeclarationClass self, GlibString string) =>
self -> string -> IO string
cssStyleDeclarationGetPropertyPriority self propertyName
= (withUTFString propertyName $
\ propertyNamePtr ->
(\(CSSStyleDeclaration arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_css_style_declaration_get_property_priority argPtr1 arg2)
(toCSSStyleDeclaration self)
propertyNamePtr)
>>=
readUTFString
cssStyleDeclarationSetProperty ::
(CSSStyleDeclarationClass self, GlibString string) =>
self -> string -> string -> string -> IO ()
cssStyleDeclarationSetProperty self propertyName value priority
= propagateGError $
\ errorPtr_ ->
withUTFString priority $
\ priorityPtr ->
withUTFString value $
\ valuePtr ->
withUTFString propertyName $
\ propertyNamePtr ->
(\(CSSStyleDeclaration arg1) arg2 arg3 arg4 arg5 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_css_style_declaration_set_property argPtr1 arg2 arg3 arg4 arg5)
(toCSSStyleDeclaration self)
propertyNamePtr
valuePtr
priorityPtr
errorPtr_
cssStyleDeclarationItem ::
(CSSStyleDeclarationClass self, GlibString string) =>
self -> Word -> IO string
cssStyleDeclarationItem self index
= ((\(CSSStyleDeclaration arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_css_style_declaration_item argPtr1 arg2)
(toCSSStyleDeclaration self)
(fromIntegral index))
>>=
readUTFString
cssStyleDeclarationGetPropertyShorthand ::
(CSSStyleDeclarationClass self, GlibString string) =>
self -> string -> IO string
cssStyleDeclarationGetPropertyShorthand self propertyName
= (withUTFString propertyName $
\ propertyNamePtr ->
(\(CSSStyleDeclaration arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_css_style_declaration_get_property_shorthand argPtr1 arg2)
(toCSSStyleDeclaration self)
propertyNamePtr)
>>=
readUTFString
cssStyleDeclarationIsPropertyImplicit ::
(CSSStyleDeclarationClass self, GlibString string) =>
self -> string -> IO Bool
cssStyleDeclarationIsPropertyImplicit self propertyName
= toBool <$>
(withUTFString propertyName $
\ propertyNamePtr ->
(\(CSSStyleDeclaration arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_css_style_declaration_is_property_implicit argPtr1 arg2)
(toCSSStyleDeclaration self)
propertyNamePtr)
cssStyleDeclarationSetCssText ::
(CSSStyleDeclarationClass self, GlibString string) =>
self -> string -> IO ()
cssStyleDeclarationSetCssText self val
= propagateGError $
\ errorPtr_ ->
withUTFString val $
\ valPtr ->
(\(CSSStyleDeclaration arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_css_style_declaration_set_css_text argPtr1 arg2 arg3)
(toCSSStyleDeclaration self)
valPtr
errorPtr_
cssStyleDeclarationGetCssText ::
(CSSStyleDeclarationClass self, GlibString string) =>
self -> IO string
cssStyleDeclarationGetCssText self
= ((\(CSSStyleDeclaration arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_css_style_declaration_get_css_text argPtr1)
(toCSSStyleDeclaration self))
>>=
readUTFString
cssStyleDeclarationGetLength ::
(CSSStyleDeclarationClass self) => self -> IO Word
cssStyleDeclarationGetLength self
= fromIntegral <$>
((\(CSSStyleDeclaration arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_css_style_declaration_get_length argPtr1)
(toCSSStyleDeclaration self))
cssStyleDeclarationGetParentRule ::
(CSSStyleDeclarationClass self) => self -> IO (Maybe CSSRule)
cssStyleDeclarationGetParentRule self
= maybeNull (makeNewGObject mkCSSRule)
((\(CSSStyleDeclaration arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_css_style_declaration_get_parent_rule argPtr1)
(toCSSStyleDeclaration self))
foreign import ccall safe "webkit_dom_css_style_declaration_get_property_value"
webkit_dom_css_style_declaration_get_property_value :: ((Ptr CSSStyleDeclaration) -> ((Ptr CChar) -> (IO (Ptr CChar))))
foreign import ccall safe "webkit_dom_css_style_declaration_remove_property"
webkit_dom_css_style_declaration_remove_property :: ((Ptr CSSStyleDeclaration) -> ((Ptr CChar) -> ((Ptr (Ptr ())) -> (IO (Ptr CChar)))))
foreign import ccall safe "webkit_dom_css_style_declaration_get_property_priority"
webkit_dom_css_style_declaration_get_property_priority :: ((Ptr CSSStyleDeclaration) -> ((Ptr CChar) -> (IO (Ptr CChar))))
foreign import ccall safe "webkit_dom_css_style_declaration_set_property"
webkit_dom_css_style_declaration_set_property :: ((Ptr CSSStyleDeclaration) -> ((Ptr CChar) -> ((Ptr CChar) -> ((Ptr CChar) -> ((Ptr (Ptr ())) -> (IO ()))))))
foreign import ccall safe "webkit_dom_css_style_declaration_item"
webkit_dom_css_style_declaration_item :: ((Ptr CSSStyleDeclaration) -> (CULong -> (IO (Ptr CChar))))
foreign import ccall safe "webkit_dom_css_style_declaration_get_property_shorthand"
webkit_dom_css_style_declaration_get_property_shorthand :: ((Ptr CSSStyleDeclaration) -> ((Ptr CChar) -> (IO (Ptr CChar))))
foreign import ccall safe "webkit_dom_css_style_declaration_is_property_implicit"
webkit_dom_css_style_declaration_is_property_implicit :: ((Ptr CSSStyleDeclaration) -> ((Ptr CChar) -> (IO CInt)))
foreign import ccall safe "webkit_dom_css_style_declaration_set_css_text"
webkit_dom_css_style_declaration_set_css_text :: ((Ptr CSSStyleDeclaration) -> ((Ptr CChar) -> ((Ptr (Ptr ())) -> (IO ()))))
foreign import ccall safe "webkit_dom_css_style_declaration_get_css_text"
webkit_dom_css_style_declaration_get_css_text :: ((Ptr CSSStyleDeclaration) -> (IO (Ptr CChar)))
foreign import ccall safe "webkit_dom_css_style_declaration_get_length"
webkit_dom_css_style_declaration_get_length :: ((Ptr CSSStyleDeclaration) -> (IO CULong))
foreign import ccall safe "webkit_dom_css_style_declaration_get_parent_rule"
webkit_dom_css_style_declaration_get_parent_rule :: ((Ptr CSSStyleDeclaration) -> (IO (Ptr CSSRule)))