module Graphics.UI.Gtk.WebKit.DOM.CSSStyleDeclaration(
getPropertyValue,
removeProperty,
getPropertyPriority,
setProperty,
item,
getPropertyShorthand,
isPropertyImplicit,
setCssText,
getCssText,
getLength,
getParentRule,
CSSStyleDeclaration,
castToCSSStyleDeclaration,
gTypeCSSStyleDeclaration,
CSSStyleDeclarationClass,
toCSSStyleDeclaration,
) where
import Prelude hiding (drop, error, print)
import Data.Typeable (Typeable)
import Foreign.Marshal (maybePeek, maybeWith)
import System.Glib.FFI (maybeNull, withForeignPtr, nullForeignPtr, Ptr, nullPtr, castPtr, Word, Int64, Word64, CChar(..), CInt(..), CUInt(..), CLong(..), CULong(..), CLLong(..), CULLong(..), CShort(..), CUShort(..), CFloat(..), CDouble(..), toBool, fromBool)
import System.Glib.UTFString (GlibString(..), readUTFString)
import Control.Applicative ((<$>))
import Control.Monad (void)
import Control.Monad.IO.Class (MonadIO(..))
import System.Glib.GError
import Graphics.UI.Gtk.WebKit.DOM.EventTargetClosures
import Graphics.UI.Gtk.WebKit.DOM.EventM
import Graphics.UI.Gtk.WebKit.Types
import Graphics.UI.Gtk.WebKit.DOM.Enums
getPropertyValue ::
(MonadIO m, CSSStyleDeclarationClass self, GlibString string) =>
self -> string -> m (Maybe string)
getPropertyValue self propertyName
= liftIO
((withUTFString propertyName $
\ propertyNamePtr ->
(\(CSSStyleDeclaration arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_css_style_declaration_get_property_value argPtr1 arg2)
(toCSSStyleDeclaration self)
propertyNamePtr)
>>=
maybePeek readUTFString)
removeProperty ::
(MonadIO m, CSSStyleDeclarationClass self, GlibString string) =>
self -> string -> m (Maybe string)
removeProperty self propertyName
= liftIO
((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_)
>>=
maybePeek readUTFString)
getPropertyPriority ::
(MonadIO m, CSSStyleDeclarationClass self, GlibString string) =>
self -> string -> m (Maybe string)
getPropertyPriority self propertyName
= liftIO
((withUTFString propertyName $
\ propertyNamePtr ->
(\(CSSStyleDeclaration arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_css_style_declaration_get_property_priority argPtr1 arg2)
(toCSSStyleDeclaration self)
propertyNamePtr)
>>=
maybePeek readUTFString)
setProperty ::
(MonadIO m, CSSStyleDeclarationClass self, GlibString string) =>
self -> string -> (Maybe string) -> string -> m ()
setProperty self propertyName value priority
= liftIO
(propagateGError $
\ errorPtr_ ->
withUTFString priority $
\ priorityPtr ->
maybeWith 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_)
item ::
(MonadIO m, CSSStyleDeclarationClass self, GlibString string) =>
self -> Word -> m string
item self index
= liftIO
(((\(CSSStyleDeclaration arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_css_style_declaration_item argPtr1 arg2)
(toCSSStyleDeclaration self)
(fromIntegral index))
>>=
readUTFString)
getPropertyShorthand ::
(MonadIO m, CSSStyleDeclarationClass self, GlibString string) =>
self -> string -> m (Maybe string)
getPropertyShorthand self propertyName
= liftIO
((withUTFString propertyName $
\ propertyNamePtr ->
(\(CSSStyleDeclaration arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_css_style_declaration_get_property_shorthand argPtr1 arg2)
(toCSSStyleDeclaration self)
propertyNamePtr)
>>=
maybePeek readUTFString)
isPropertyImplicit ::
(MonadIO m, CSSStyleDeclarationClass self, GlibString string) =>
self -> string -> m Bool
isPropertyImplicit self propertyName
= liftIO
(toBool <$>
(withUTFString propertyName $
\ propertyNamePtr ->
(\(CSSStyleDeclaration arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_css_style_declaration_is_property_implicit argPtr1 arg2)
(toCSSStyleDeclaration self)
propertyNamePtr))
setCssText ::
(MonadIO m, CSSStyleDeclarationClass self, GlibString string) =>
self -> (Maybe string) -> m ()
setCssText self val
= liftIO
(propagateGError $
\ errorPtr_ ->
maybeWith 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_)
getCssText ::
(MonadIO m, CSSStyleDeclarationClass self, GlibString string) =>
self -> m (Maybe string)
getCssText self
= liftIO
(((\(CSSStyleDeclaration arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_css_style_declaration_get_css_text argPtr1)
(toCSSStyleDeclaration self))
>>=
maybePeek readUTFString)
getLength ::
(MonadIO m, CSSStyleDeclarationClass self) => self -> m Word
getLength self
= liftIO
(fromIntegral <$>
((\(CSSStyleDeclaration arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_css_style_declaration_get_length argPtr1)
(toCSSStyleDeclaration self)))
getParentRule ::
(MonadIO m, CSSStyleDeclarationClass self) =>
self -> m (Maybe CSSRule)
getParentRule self
= liftIO
(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)))