{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.WebKit2WebExtension.Objects.DOMCSSStyleDeclaration
    ( 
    DOMCSSStyleDeclaration(..)              ,
    IsDOMCSSStyleDeclaration                ,
    toDOMCSSStyleDeclaration                ,
    noDOMCSSStyleDeclaration                ,
 
#if defined(ENABLE_OVERLOADING)
    ResolveDOMCSSStyleDeclarationMethod     ,
#endif
#if defined(ENABLE_OVERLOADING)
    DOMCSSStyleDeclarationGetCssTextMethodInfo,
#endif
    dOMCSSStyleDeclarationGetCssText        ,
#if defined(ENABLE_OVERLOADING)
    DOMCSSStyleDeclarationGetLengthMethodInfo,
#endif
    dOMCSSStyleDeclarationGetLength         ,
#if defined(ENABLE_OVERLOADING)
    DOMCSSStyleDeclarationGetParentRuleMethodInfo,
#endif
    dOMCSSStyleDeclarationGetParentRule     ,
#if defined(ENABLE_OVERLOADING)
    DOMCSSStyleDeclarationGetPropertyPriorityMethodInfo,
#endif
    dOMCSSStyleDeclarationGetPropertyPriority,
#if defined(ENABLE_OVERLOADING)
    DOMCSSStyleDeclarationGetPropertyShorthandMethodInfo,
#endif
    dOMCSSStyleDeclarationGetPropertyShorthand,
#if defined(ENABLE_OVERLOADING)
    DOMCSSStyleDeclarationGetPropertyValueMethodInfo,
#endif
    dOMCSSStyleDeclarationGetPropertyValue  ,
#if defined(ENABLE_OVERLOADING)
    DOMCSSStyleDeclarationIsPropertyImplicitMethodInfo,
#endif
    dOMCSSStyleDeclarationIsPropertyImplicit,
#if defined(ENABLE_OVERLOADING)
    DOMCSSStyleDeclarationItemMethodInfo    ,
#endif
    dOMCSSStyleDeclarationItem              ,
#if defined(ENABLE_OVERLOADING)
    DOMCSSStyleDeclarationRemovePropertyMethodInfo,
#endif
    dOMCSSStyleDeclarationRemoveProperty    ,
#if defined(ENABLE_OVERLOADING)
    DOMCSSStyleDeclarationSetCssTextMethodInfo,
#endif
    dOMCSSStyleDeclarationSetCssText        ,
#if defined(ENABLE_OVERLOADING)
    DOMCSSStyleDeclarationSetPropertyMethodInfo,
#endif
    dOMCSSStyleDeclarationSetProperty       ,
 
#if defined(ENABLE_OVERLOADING)
    DOMCSSStyleDeclarationCssTextPropertyInfo,
#endif
    clearDOMCSSStyleDeclarationCssText      ,
    constructDOMCSSStyleDeclarationCssText  ,
#if defined(ENABLE_OVERLOADING)
    dOMCSSStyleDeclarationCssText           ,
#endif
    getDOMCSSStyleDeclarationCssText        ,
    setDOMCSSStyleDeclarationCssText        ,
#if defined(ENABLE_OVERLOADING)
    DOMCSSStyleDeclarationLengthPropertyInfo,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMCSSStyleDeclarationLength            ,
#endif
    getDOMCSSStyleDeclarationLength         ,
#if defined(ENABLE_OVERLOADING)
    DOMCSSStyleDeclarationParentRulePropertyInfo,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMCSSStyleDeclarationParentRule        ,
#endif
    getDOMCSSStyleDeclarationParentRule     ,
    ) where
import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P
import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMCSSRule as WebKit2WebExtension.DOMCSSRule
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMObject as WebKit2WebExtension.DOMObject
newtype DOMCSSStyleDeclaration = DOMCSSStyleDeclaration (ManagedPtr DOMCSSStyleDeclaration)
    deriving (DOMCSSStyleDeclaration -> DOMCSSStyleDeclaration -> Bool
(DOMCSSStyleDeclaration -> DOMCSSStyleDeclaration -> Bool)
-> (DOMCSSStyleDeclaration -> DOMCSSStyleDeclaration -> Bool)
-> Eq DOMCSSStyleDeclaration
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DOMCSSStyleDeclaration -> DOMCSSStyleDeclaration -> Bool
$c/= :: DOMCSSStyleDeclaration -> DOMCSSStyleDeclaration -> Bool
== :: DOMCSSStyleDeclaration -> DOMCSSStyleDeclaration -> Bool
$c== :: DOMCSSStyleDeclaration -> DOMCSSStyleDeclaration -> Bool
Eq)
foreign import ccall "webkit_dom_css_style_declaration_get_type"
    c_webkit_dom_css_style_declaration_get_type :: IO GType
instance GObject DOMCSSStyleDeclaration where
    gobjectType :: IO GType
gobjectType = IO GType
c_webkit_dom_css_style_declaration_get_type
    
instance B.GValue.IsGValue DOMCSSStyleDeclaration where
    toGValue :: DOMCSSStyleDeclaration -> IO GValue
toGValue o :: DOMCSSStyleDeclaration
o = do
        GType
gtype <- IO GType
c_webkit_dom_css_style_declaration_get_type
        DOMCSSStyleDeclaration
-> (Ptr DOMCSSStyleDeclaration -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr DOMCSSStyleDeclaration
o (GType
-> (GValue -> Ptr DOMCSSStyleDeclaration -> IO ())
-> Ptr DOMCSSStyleDeclaration
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr DOMCSSStyleDeclaration -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
        
    fromGValue :: GValue -> IO DOMCSSStyleDeclaration
fromGValue gv :: GValue
gv = do
        Ptr DOMCSSStyleDeclaration
ptr <- GValue -> IO (Ptr DOMCSSStyleDeclaration)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr DOMCSSStyleDeclaration)
        (ManagedPtr DOMCSSStyleDeclaration -> DOMCSSStyleDeclaration)
-> Ptr DOMCSSStyleDeclaration -> IO DOMCSSStyleDeclaration
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr DOMCSSStyleDeclaration -> DOMCSSStyleDeclaration
DOMCSSStyleDeclaration Ptr DOMCSSStyleDeclaration
ptr
        
    
class (GObject o, O.IsDescendantOf DOMCSSStyleDeclaration o) => IsDOMCSSStyleDeclaration o
instance (GObject o, O.IsDescendantOf DOMCSSStyleDeclaration o) => IsDOMCSSStyleDeclaration o
instance O.HasParentTypes DOMCSSStyleDeclaration
type instance O.ParentTypes DOMCSSStyleDeclaration = '[WebKit2WebExtension.DOMObject.DOMObject, GObject.Object.Object]
toDOMCSSStyleDeclaration :: (MonadIO m, IsDOMCSSStyleDeclaration o) => o -> m DOMCSSStyleDeclaration
toDOMCSSStyleDeclaration :: o -> m DOMCSSStyleDeclaration
toDOMCSSStyleDeclaration = IO DOMCSSStyleDeclaration -> m DOMCSSStyleDeclaration
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DOMCSSStyleDeclaration -> m DOMCSSStyleDeclaration)
-> (o -> IO DOMCSSStyleDeclaration)
-> o
-> m DOMCSSStyleDeclaration
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr DOMCSSStyleDeclaration -> DOMCSSStyleDeclaration)
-> o -> IO DOMCSSStyleDeclaration
forall o o'.
(HasCallStack, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr DOMCSSStyleDeclaration -> DOMCSSStyleDeclaration
DOMCSSStyleDeclaration
noDOMCSSStyleDeclaration :: Maybe DOMCSSStyleDeclaration
noDOMCSSStyleDeclaration :: Maybe DOMCSSStyleDeclaration
noDOMCSSStyleDeclaration = Maybe DOMCSSStyleDeclaration
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolveDOMCSSStyleDeclarationMethod (t :: Symbol) (o :: *) :: * where
    ResolveDOMCSSStyleDeclarationMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveDOMCSSStyleDeclarationMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveDOMCSSStyleDeclarationMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveDOMCSSStyleDeclarationMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveDOMCSSStyleDeclarationMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveDOMCSSStyleDeclarationMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveDOMCSSStyleDeclarationMethod "isPropertyImplicit" o = DOMCSSStyleDeclarationIsPropertyImplicitMethodInfo
    ResolveDOMCSSStyleDeclarationMethod "item" o = DOMCSSStyleDeclarationItemMethodInfo
    ResolveDOMCSSStyleDeclarationMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveDOMCSSStyleDeclarationMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveDOMCSSStyleDeclarationMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveDOMCSSStyleDeclarationMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveDOMCSSStyleDeclarationMethod "removeProperty" o = DOMCSSStyleDeclarationRemovePropertyMethodInfo
    ResolveDOMCSSStyleDeclarationMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveDOMCSSStyleDeclarationMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveDOMCSSStyleDeclarationMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveDOMCSSStyleDeclarationMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveDOMCSSStyleDeclarationMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveDOMCSSStyleDeclarationMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveDOMCSSStyleDeclarationMethod "getCssText" o = DOMCSSStyleDeclarationGetCssTextMethodInfo
    ResolveDOMCSSStyleDeclarationMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveDOMCSSStyleDeclarationMethod "getLength" o = DOMCSSStyleDeclarationGetLengthMethodInfo
    ResolveDOMCSSStyleDeclarationMethod "getParentRule" o = DOMCSSStyleDeclarationGetParentRuleMethodInfo
    ResolveDOMCSSStyleDeclarationMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveDOMCSSStyleDeclarationMethod "getPropertyPriority" o = DOMCSSStyleDeclarationGetPropertyPriorityMethodInfo
    ResolveDOMCSSStyleDeclarationMethod "getPropertyShorthand" o = DOMCSSStyleDeclarationGetPropertyShorthandMethodInfo
    ResolveDOMCSSStyleDeclarationMethod "getPropertyValue" o = DOMCSSStyleDeclarationGetPropertyValueMethodInfo
    ResolveDOMCSSStyleDeclarationMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveDOMCSSStyleDeclarationMethod "setCssText" o = DOMCSSStyleDeclarationSetCssTextMethodInfo
    ResolveDOMCSSStyleDeclarationMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveDOMCSSStyleDeclarationMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveDOMCSSStyleDeclarationMethod "setProperty" o = DOMCSSStyleDeclarationSetPropertyMethodInfo
    ResolveDOMCSSStyleDeclarationMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveDOMCSSStyleDeclarationMethod t DOMCSSStyleDeclaration, O.MethodInfo info DOMCSSStyleDeclaration p) => OL.IsLabel t (DOMCSSStyleDeclaration -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif
#endif
   
   
   
getDOMCSSStyleDeclarationCssText :: (MonadIO m, IsDOMCSSStyleDeclaration o) => o -> m (Maybe T.Text)
getDOMCSSStyleDeclarationCssText :: o -> m (Maybe Text)
getDOMCSSStyleDeclarationCssText obj :: o
obj = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj "css-text"
setDOMCSSStyleDeclarationCssText :: (MonadIO m, IsDOMCSSStyleDeclaration o) => o -> T.Text -> m ()
setDOMCSSStyleDeclarationCssText :: o -> Text -> m ()
setDOMCSSStyleDeclarationCssText obj :: o
obj val :: Text
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj "css-text" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)
constructDOMCSSStyleDeclarationCssText :: (IsDOMCSSStyleDeclaration o) => T.Text -> IO (GValueConstruct o)
constructDOMCSSStyleDeclarationCssText :: Text -> IO (GValueConstruct o)
constructDOMCSSStyleDeclarationCssText val :: Text
val = String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString "css-text" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)
clearDOMCSSStyleDeclarationCssText :: (MonadIO m, IsDOMCSSStyleDeclaration o) => o -> m ()
clearDOMCSSStyleDeclarationCssText :: o -> m ()
clearDOMCSSStyleDeclarationCssText obj :: o
obj = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj "css-text" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)
#if defined(ENABLE_OVERLOADING)
data DOMCSSStyleDeclarationCssTextPropertyInfo
instance AttrInfo DOMCSSStyleDeclarationCssTextPropertyInfo where
    type AttrAllowedOps DOMCSSStyleDeclarationCssTextPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint DOMCSSStyleDeclarationCssTextPropertyInfo = IsDOMCSSStyleDeclaration
    type AttrSetTypeConstraint DOMCSSStyleDeclarationCssTextPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint DOMCSSStyleDeclarationCssTextPropertyInfo = (~) T.Text
    type AttrTransferType DOMCSSStyleDeclarationCssTextPropertyInfo = T.Text
    type AttrGetType DOMCSSStyleDeclarationCssTextPropertyInfo = (Maybe T.Text)
    type AttrLabel DOMCSSStyleDeclarationCssTextPropertyInfo = "css-text"
    type AttrOrigin DOMCSSStyleDeclarationCssTextPropertyInfo = DOMCSSStyleDeclaration
    attrGet = getDOMCSSStyleDeclarationCssText
    attrSet = setDOMCSSStyleDeclarationCssText
    attrTransfer _ v = do
        return v
    attrConstruct = constructDOMCSSStyleDeclarationCssText
    attrClear = clearDOMCSSStyleDeclarationCssText
#endif
   
   
   
getDOMCSSStyleDeclarationLength :: (MonadIO m, IsDOMCSSStyleDeclaration o) => o -> m CULong
getDOMCSSStyleDeclarationLength :: o -> m CULong
getDOMCSSStyleDeclarationLength obj :: o
obj = IO CULong -> m CULong
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CULong -> m CULong) -> IO CULong -> m CULong
forall a b. (a -> b) -> a -> b
$ o -> String -> IO CULong
forall a. GObject a => a -> String -> IO CULong
B.Properties.getObjectPropertyULong o
obj "length"
#if defined(ENABLE_OVERLOADING)
data DOMCSSStyleDeclarationLengthPropertyInfo
instance AttrInfo DOMCSSStyleDeclarationLengthPropertyInfo where
    type AttrAllowedOps DOMCSSStyleDeclarationLengthPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint DOMCSSStyleDeclarationLengthPropertyInfo = IsDOMCSSStyleDeclaration
    type AttrSetTypeConstraint DOMCSSStyleDeclarationLengthPropertyInfo = (~) ()
    type AttrTransferTypeConstraint DOMCSSStyleDeclarationLengthPropertyInfo = (~) ()
    type AttrTransferType DOMCSSStyleDeclarationLengthPropertyInfo = ()
    type AttrGetType DOMCSSStyleDeclarationLengthPropertyInfo = CULong
    type AttrLabel DOMCSSStyleDeclarationLengthPropertyInfo = "length"
    type AttrOrigin DOMCSSStyleDeclarationLengthPropertyInfo = DOMCSSStyleDeclaration
    attrGet = getDOMCSSStyleDeclarationLength
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif
   
   
   
getDOMCSSStyleDeclarationParentRule :: (MonadIO m, IsDOMCSSStyleDeclaration o) => o -> m (Maybe WebKit2WebExtension.DOMCSSRule.DOMCSSRule)
getDOMCSSStyleDeclarationParentRule :: o -> m (Maybe DOMCSSRule)
getDOMCSSStyleDeclarationParentRule obj :: o
obj = IO (Maybe DOMCSSRule) -> m (Maybe DOMCSSRule)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe DOMCSSRule) -> m (Maybe DOMCSSRule))
-> IO (Maybe DOMCSSRule) -> m (Maybe DOMCSSRule)
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr DOMCSSRule -> DOMCSSRule)
-> IO (Maybe DOMCSSRule)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj "parent-rule" ManagedPtr DOMCSSRule -> DOMCSSRule
WebKit2WebExtension.DOMCSSRule.DOMCSSRule
#if defined(ENABLE_OVERLOADING)
data DOMCSSStyleDeclarationParentRulePropertyInfo
instance AttrInfo DOMCSSStyleDeclarationParentRulePropertyInfo where
    type AttrAllowedOps DOMCSSStyleDeclarationParentRulePropertyInfo = '[ 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint DOMCSSStyleDeclarationParentRulePropertyInfo = IsDOMCSSStyleDeclaration
    type AttrSetTypeConstraint DOMCSSStyleDeclarationParentRulePropertyInfo = (~) ()
    type AttrTransferTypeConstraint DOMCSSStyleDeclarationParentRulePropertyInfo = (~) ()
    type AttrTransferType DOMCSSStyleDeclarationParentRulePropertyInfo = ()
    type AttrGetType DOMCSSStyleDeclarationParentRulePropertyInfo = (Maybe WebKit2WebExtension.DOMCSSRule.DOMCSSRule)
    type AttrLabel DOMCSSStyleDeclarationParentRulePropertyInfo = "parent-rule"
    type AttrOrigin DOMCSSStyleDeclarationParentRulePropertyInfo = DOMCSSStyleDeclaration
    attrGet = getDOMCSSStyleDeclarationParentRule
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList DOMCSSStyleDeclaration
type instance O.AttributeList DOMCSSStyleDeclaration = DOMCSSStyleDeclarationAttributeList
type DOMCSSStyleDeclarationAttributeList = ('[ '("coreObject", WebKit2WebExtension.DOMObject.DOMObjectCoreObjectPropertyInfo), '("cssText", DOMCSSStyleDeclarationCssTextPropertyInfo), '("length", DOMCSSStyleDeclarationLengthPropertyInfo), '("parentRule", DOMCSSStyleDeclarationParentRulePropertyInfo)] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
dOMCSSStyleDeclarationCssText :: AttrLabelProxy "cssText"
dOMCSSStyleDeclarationCssText = AttrLabelProxy
dOMCSSStyleDeclarationLength :: AttrLabelProxy "length"
dOMCSSStyleDeclarationLength = AttrLabelProxy
dOMCSSStyleDeclarationParentRule :: AttrLabelProxy "parentRule"
dOMCSSStyleDeclarationParentRule = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList DOMCSSStyleDeclaration = DOMCSSStyleDeclarationSignalList
type DOMCSSStyleDeclarationSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "webkit_dom_css_style_declaration_get_css_text" webkit_dom_css_style_declaration_get_css_text :: 
    Ptr DOMCSSStyleDeclaration ->           
    IO CString
{-# DEPRECATED dOMCSSStyleDeclarationGetCssText ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
dOMCSSStyleDeclarationGetCssText ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMCSSStyleDeclaration a) =>
    a
    
    -> m T.Text
    
dOMCSSStyleDeclarationGetCssText :: a -> m Text
dOMCSSStyleDeclarationGetCssText self :: a
self = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMCSSStyleDeclaration
self' <- a -> IO (Ptr DOMCSSStyleDeclaration)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
result <- Ptr DOMCSSStyleDeclaration -> IO CString
webkit_dom_css_style_declaration_get_css_text Ptr DOMCSSStyleDeclaration
self'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dOMCSSStyleDeclarationGetCssText" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data DOMCSSStyleDeclarationGetCssTextMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsDOMCSSStyleDeclaration a) => O.MethodInfo DOMCSSStyleDeclarationGetCssTextMethodInfo a signature where
    overloadedMethod = dOMCSSStyleDeclarationGetCssText
#endif
foreign import ccall "webkit_dom_css_style_declaration_get_length" webkit_dom_css_style_declaration_get_length :: 
    Ptr DOMCSSStyleDeclaration ->           
    IO CULong
{-# DEPRECATED dOMCSSStyleDeclarationGetLength ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
dOMCSSStyleDeclarationGetLength ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMCSSStyleDeclaration a) =>
    a
    
    -> m CULong
    
dOMCSSStyleDeclarationGetLength :: a -> m CULong
dOMCSSStyleDeclarationGetLength self :: a
self = IO CULong -> m CULong
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CULong -> m CULong) -> IO CULong -> m CULong
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMCSSStyleDeclaration
self' <- a -> IO (Ptr DOMCSSStyleDeclaration)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CULong
result <- Ptr DOMCSSStyleDeclaration -> IO CULong
webkit_dom_css_style_declaration_get_length Ptr DOMCSSStyleDeclaration
self'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    CULong -> IO CULong
forall (m :: * -> *) a. Monad m => a -> m a
return CULong
result
#if defined(ENABLE_OVERLOADING)
data DOMCSSStyleDeclarationGetLengthMethodInfo
instance (signature ~ (m CULong), MonadIO m, IsDOMCSSStyleDeclaration a) => O.MethodInfo DOMCSSStyleDeclarationGetLengthMethodInfo a signature where
    overloadedMethod = dOMCSSStyleDeclarationGetLength
#endif
foreign import ccall "webkit_dom_css_style_declaration_get_parent_rule" webkit_dom_css_style_declaration_get_parent_rule :: 
    Ptr DOMCSSStyleDeclaration ->           
    IO (Ptr WebKit2WebExtension.DOMCSSRule.DOMCSSRule)
{-# DEPRECATED dOMCSSStyleDeclarationGetParentRule ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
dOMCSSStyleDeclarationGetParentRule ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMCSSStyleDeclaration a) =>
    a
    
    -> m WebKit2WebExtension.DOMCSSRule.DOMCSSRule
    
dOMCSSStyleDeclarationGetParentRule :: a -> m DOMCSSRule
dOMCSSStyleDeclarationGetParentRule self :: a
self = IO DOMCSSRule -> m DOMCSSRule
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DOMCSSRule -> m DOMCSSRule) -> IO DOMCSSRule -> m DOMCSSRule
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMCSSStyleDeclaration
self' <- a -> IO (Ptr DOMCSSStyleDeclaration)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr DOMCSSRule
result <- Ptr DOMCSSStyleDeclaration -> IO (Ptr DOMCSSRule)
webkit_dom_css_style_declaration_get_parent_rule Ptr DOMCSSStyleDeclaration
self'
    Text -> Ptr DOMCSSRule -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dOMCSSStyleDeclarationGetParentRule" Ptr DOMCSSRule
result
    DOMCSSRule
result' <- ((ManagedPtr DOMCSSRule -> DOMCSSRule)
-> Ptr DOMCSSRule -> IO DOMCSSRule
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr DOMCSSRule -> DOMCSSRule
WebKit2WebExtension.DOMCSSRule.DOMCSSRule) Ptr DOMCSSRule
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    DOMCSSRule -> IO DOMCSSRule
forall (m :: * -> *) a. Monad m => a -> m a
return DOMCSSRule
result'
#if defined(ENABLE_OVERLOADING)
data DOMCSSStyleDeclarationGetParentRuleMethodInfo
instance (signature ~ (m WebKit2WebExtension.DOMCSSRule.DOMCSSRule), MonadIO m, IsDOMCSSStyleDeclaration a) => O.MethodInfo DOMCSSStyleDeclarationGetParentRuleMethodInfo a signature where
    overloadedMethod = dOMCSSStyleDeclarationGetParentRule
#endif
foreign import ccall "webkit_dom_css_style_declaration_get_property_priority" webkit_dom_css_style_declaration_get_property_priority :: 
    Ptr DOMCSSStyleDeclaration ->           
    CString ->                              
    IO CString
{-# DEPRECATED dOMCSSStyleDeclarationGetPropertyPriority ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
dOMCSSStyleDeclarationGetPropertyPriority ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMCSSStyleDeclaration a) =>
    a
    
    -> T.Text
    
    -> m T.Text
    
dOMCSSStyleDeclarationGetPropertyPriority :: a -> Text -> m Text
dOMCSSStyleDeclarationGetPropertyPriority self :: a
self propertyName :: Text
propertyName = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMCSSStyleDeclaration
self' <- a -> IO (Ptr DOMCSSStyleDeclaration)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
propertyName' <- Text -> IO CString
textToCString Text
propertyName
    CString
result <- Ptr DOMCSSStyleDeclaration -> CString -> IO CString
webkit_dom_css_style_declaration_get_property_priority Ptr DOMCSSStyleDeclaration
self' CString
propertyName'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dOMCSSStyleDeclarationGetPropertyPriority" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
propertyName'
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data DOMCSSStyleDeclarationGetPropertyPriorityMethodInfo
instance (signature ~ (T.Text -> m T.Text), MonadIO m, IsDOMCSSStyleDeclaration a) => O.MethodInfo DOMCSSStyleDeclarationGetPropertyPriorityMethodInfo a signature where
    overloadedMethod = dOMCSSStyleDeclarationGetPropertyPriority
#endif
foreign import ccall "webkit_dom_css_style_declaration_get_property_shorthand" webkit_dom_css_style_declaration_get_property_shorthand :: 
    Ptr DOMCSSStyleDeclaration ->           
    CString ->                              
    IO CString
{-# DEPRECATED dOMCSSStyleDeclarationGetPropertyShorthand ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
dOMCSSStyleDeclarationGetPropertyShorthand ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMCSSStyleDeclaration a) =>
    a
    
    -> T.Text
    
    -> m T.Text
    
dOMCSSStyleDeclarationGetPropertyShorthand :: a -> Text -> m Text
dOMCSSStyleDeclarationGetPropertyShorthand self :: a
self propertyName :: Text
propertyName = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMCSSStyleDeclaration
self' <- a -> IO (Ptr DOMCSSStyleDeclaration)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
propertyName' <- Text -> IO CString
textToCString Text
propertyName
    CString
result <- Ptr DOMCSSStyleDeclaration -> CString -> IO CString
webkit_dom_css_style_declaration_get_property_shorthand Ptr DOMCSSStyleDeclaration
self' CString
propertyName'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dOMCSSStyleDeclarationGetPropertyShorthand" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
propertyName'
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data DOMCSSStyleDeclarationGetPropertyShorthandMethodInfo
instance (signature ~ (T.Text -> m T.Text), MonadIO m, IsDOMCSSStyleDeclaration a) => O.MethodInfo DOMCSSStyleDeclarationGetPropertyShorthandMethodInfo a signature where
    overloadedMethod = dOMCSSStyleDeclarationGetPropertyShorthand
#endif
foreign import ccall "webkit_dom_css_style_declaration_get_property_value" webkit_dom_css_style_declaration_get_property_value :: 
    Ptr DOMCSSStyleDeclaration ->           
    CString ->                              
    IO CString
{-# DEPRECATED dOMCSSStyleDeclarationGetPropertyValue ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
dOMCSSStyleDeclarationGetPropertyValue ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMCSSStyleDeclaration a) =>
    a
    
    -> T.Text
    
    -> m T.Text
    
dOMCSSStyleDeclarationGetPropertyValue :: a -> Text -> m Text
dOMCSSStyleDeclarationGetPropertyValue self :: a
self propertyName :: Text
propertyName = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMCSSStyleDeclaration
self' <- a -> IO (Ptr DOMCSSStyleDeclaration)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
propertyName' <- Text -> IO CString
textToCString Text
propertyName
    CString
result <- Ptr DOMCSSStyleDeclaration -> CString -> IO CString
webkit_dom_css_style_declaration_get_property_value Ptr DOMCSSStyleDeclaration
self' CString
propertyName'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dOMCSSStyleDeclarationGetPropertyValue" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
propertyName'
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data DOMCSSStyleDeclarationGetPropertyValueMethodInfo
instance (signature ~ (T.Text -> m T.Text), MonadIO m, IsDOMCSSStyleDeclaration a) => O.MethodInfo DOMCSSStyleDeclarationGetPropertyValueMethodInfo a signature where
    overloadedMethod = dOMCSSStyleDeclarationGetPropertyValue
#endif
foreign import ccall "webkit_dom_css_style_declaration_is_property_implicit" webkit_dom_css_style_declaration_is_property_implicit :: 
    Ptr DOMCSSStyleDeclaration ->           
    CString ->                              
    IO CInt
{-# DEPRECATED dOMCSSStyleDeclarationIsPropertyImplicit ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
dOMCSSStyleDeclarationIsPropertyImplicit ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMCSSStyleDeclaration a) =>
    a
    
    -> T.Text
    
    -> m Bool
    
dOMCSSStyleDeclarationIsPropertyImplicit :: a -> Text -> m Bool
dOMCSSStyleDeclarationIsPropertyImplicit self :: a
self propertyName :: Text
propertyName = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMCSSStyleDeclaration
self' <- a -> IO (Ptr DOMCSSStyleDeclaration)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
propertyName' <- Text -> IO CString
textToCString Text
propertyName
    CInt
result <- Ptr DOMCSSStyleDeclaration -> CString -> IO CInt
webkit_dom_css_style_declaration_is_property_implicit Ptr DOMCSSStyleDeclaration
self' CString
propertyName'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
propertyName'
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data DOMCSSStyleDeclarationIsPropertyImplicitMethodInfo
instance (signature ~ (T.Text -> m Bool), MonadIO m, IsDOMCSSStyleDeclaration a) => O.MethodInfo DOMCSSStyleDeclarationIsPropertyImplicitMethodInfo a signature where
    overloadedMethod = dOMCSSStyleDeclarationIsPropertyImplicit
#endif
foreign import ccall "webkit_dom_css_style_declaration_item" webkit_dom_css_style_declaration_item :: 
    Ptr DOMCSSStyleDeclaration ->           
    CULong ->                               
    IO CString
{-# DEPRECATED dOMCSSStyleDeclarationItem ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
dOMCSSStyleDeclarationItem ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMCSSStyleDeclaration a) =>
    a
    
    -> CULong
    
    -> m T.Text
    
dOMCSSStyleDeclarationItem :: a -> CULong -> m Text
dOMCSSStyleDeclarationItem self :: a
self index :: CULong
index = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMCSSStyleDeclaration
self' <- a -> IO (Ptr DOMCSSStyleDeclaration)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
result <- Ptr DOMCSSStyleDeclaration -> CULong -> IO CString
webkit_dom_css_style_declaration_item Ptr DOMCSSStyleDeclaration
self' CULong
index
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dOMCSSStyleDeclarationItem" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data DOMCSSStyleDeclarationItemMethodInfo
instance (signature ~ (CULong -> m T.Text), MonadIO m, IsDOMCSSStyleDeclaration a) => O.MethodInfo DOMCSSStyleDeclarationItemMethodInfo a signature where
    overloadedMethod = dOMCSSStyleDeclarationItem
#endif
foreign import ccall "webkit_dom_css_style_declaration_remove_property" webkit_dom_css_style_declaration_remove_property :: 
    Ptr DOMCSSStyleDeclaration ->           
    CString ->                              
    Ptr (Ptr GError) ->                     
    IO CString
{-# DEPRECATED dOMCSSStyleDeclarationRemoveProperty ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
dOMCSSStyleDeclarationRemoveProperty ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMCSSStyleDeclaration a) =>
    a
    
    -> T.Text
    
    -> m T.Text
    
dOMCSSStyleDeclarationRemoveProperty :: a -> Text -> m Text
dOMCSSStyleDeclarationRemoveProperty self :: a
self propertyName :: Text
propertyName = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMCSSStyleDeclaration
self' <- a -> IO (Ptr DOMCSSStyleDeclaration)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
propertyName' <- Text -> IO CString
textToCString Text
propertyName
    IO Text -> IO () -> IO Text
forall a b. IO a -> IO b -> IO a
onException (do
        CString
result <- (Ptr (Ptr GError) -> IO CString) -> IO CString
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CString) -> IO CString)
-> (Ptr (Ptr GError) -> IO CString) -> IO CString
forall a b. (a -> b) -> a -> b
$ Ptr DOMCSSStyleDeclaration
-> CString -> Ptr (Ptr GError) -> IO CString
webkit_dom_css_style_declaration_remove_property Ptr DOMCSSStyleDeclaration
self' CString
propertyName'
        Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dOMCSSStyleDeclarationRemoveProperty" CString
result
        Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
propertyName'
        Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
propertyName'
     )
#if defined(ENABLE_OVERLOADING)
data DOMCSSStyleDeclarationRemovePropertyMethodInfo
instance (signature ~ (T.Text -> m T.Text), MonadIO m, IsDOMCSSStyleDeclaration a) => O.MethodInfo DOMCSSStyleDeclarationRemovePropertyMethodInfo a signature where
    overloadedMethod = dOMCSSStyleDeclarationRemoveProperty
#endif
foreign import ccall "webkit_dom_css_style_declaration_set_css_text" webkit_dom_css_style_declaration_set_css_text :: 
    Ptr DOMCSSStyleDeclaration ->           
    CString ->                              
    Ptr (Ptr GError) ->                     
    IO ()
{-# DEPRECATED dOMCSSStyleDeclarationSetCssText ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
dOMCSSStyleDeclarationSetCssText ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMCSSStyleDeclaration a) =>
    a
    
    -> T.Text
    
    -> m ()
    
dOMCSSStyleDeclarationSetCssText :: a -> Text -> m ()
dOMCSSStyleDeclarationSetCssText self :: a
self value :: Text
value = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMCSSStyleDeclaration
self' <- a -> IO (Ptr DOMCSSStyleDeclaration)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
value' <- Text -> IO CString
textToCString Text
value
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        (Ptr (Ptr GError) -> IO ()) -> IO ()
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO ()) -> IO ())
-> (Ptr (Ptr GError) -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ Ptr DOMCSSStyleDeclaration -> CString -> Ptr (Ptr GError) -> IO ()
webkit_dom_css_style_declaration_set_css_text Ptr DOMCSSStyleDeclaration
self' CString
value'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
value'
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
value'
     )
#if defined(ENABLE_OVERLOADING)
data DOMCSSStyleDeclarationSetCssTextMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsDOMCSSStyleDeclaration a) => O.MethodInfo DOMCSSStyleDeclarationSetCssTextMethodInfo a signature where
    overloadedMethod = dOMCSSStyleDeclarationSetCssText
#endif
foreign import ccall "webkit_dom_css_style_declaration_set_property" webkit_dom_css_style_declaration_set_property :: 
    Ptr DOMCSSStyleDeclaration ->           
    CString ->                              
    CString ->                              
    CString ->                              
    Ptr (Ptr GError) ->                     
    IO ()
{-# DEPRECATED dOMCSSStyleDeclarationSetProperty ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
dOMCSSStyleDeclarationSetProperty ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMCSSStyleDeclaration a) =>
    a
    
    -> T.Text
    
    -> T.Text
    
    -> T.Text
    
    -> m ()
    
dOMCSSStyleDeclarationSetProperty :: a -> Text -> Text -> Text -> m ()
dOMCSSStyleDeclarationSetProperty self :: a
self propertyName :: Text
propertyName value :: Text
value priority :: Text
priority = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMCSSStyleDeclaration
self' <- a -> IO (Ptr DOMCSSStyleDeclaration)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
propertyName' <- Text -> IO CString
textToCString Text
propertyName
    CString
value' <- Text -> IO CString
textToCString Text
value
    CString
priority' <- Text -> IO CString
textToCString Text
priority
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        (Ptr (Ptr GError) -> IO ()) -> IO ()
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO ()) -> IO ())
-> (Ptr (Ptr GError) -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ Ptr DOMCSSStyleDeclaration
-> CString -> CString -> CString -> Ptr (Ptr GError) -> IO ()
webkit_dom_css_style_declaration_set_property Ptr DOMCSSStyleDeclaration
self' CString
propertyName' CString
value' CString
priority'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
propertyName'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
value'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
priority'
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
propertyName'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
value'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
priority'
     )
#if defined(ENABLE_OVERLOADING)
data DOMCSSStyleDeclarationSetPropertyMethodInfo
instance (signature ~ (T.Text -> T.Text -> T.Text -> m ()), MonadIO m, IsDOMCSSStyleDeclaration a) => O.MethodInfo DOMCSSStyleDeclarationSetPropertyMethodInfo a signature where
    overloadedMethod = dOMCSSStyleDeclarationSetProperty
#endif