{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- /No description available in the introspection data./

#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif

module GI.WebKit2WebExtension.Objects.DOMCSSStyleDeclaration
    ( 

-- * Exported types
    DOMCSSStyleDeclaration(..)              ,
    IsDOMCSSStyleDeclaration                ,
    toDOMCSSStyleDeclaration                ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [isPropertyImplicit]("GI.WebKit2WebExtension.Objects.DOMCSSStyleDeclaration#g:method:isPropertyImplicit"), [item]("GI.WebKit2WebExtension.Objects.DOMCSSStyleDeclaration#g:method:item"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [removeProperty]("GI.WebKit2WebExtension.Objects.DOMCSSStyleDeclaration#g:method:removeProperty"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getCssText]("GI.WebKit2WebExtension.Objects.DOMCSSStyleDeclaration#g:method:getCssText"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getLength]("GI.WebKit2WebExtension.Objects.DOMCSSStyleDeclaration#g:method:getLength"), [getParentRule]("GI.WebKit2WebExtension.Objects.DOMCSSStyleDeclaration#g:method:getParentRule"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getPropertyPriority]("GI.WebKit2WebExtension.Objects.DOMCSSStyleDeclaration#g:method:getPropertyPriority"), [getPropertyShorthand]("GI.WebKit2WebExtension.Objects.DOMCSSStyleDeclaration#g:method:getPropertyShorthand"), [getPropertyValue]("GI.WebKit2WebExtension.Objects.DOMCSSStyleDeclaration#g:method:getPropertyValue"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata").
-- 
-- ==== Setters
-- [setCssText]("GI.WebKit2WebExtension.Objects.DOMCSSStyleDeclaration#g:method:setCssText"), [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setProperty]("GI.WebKit2WebExtension.Objects.DOMCSSStyleDeclaration#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolveDOMCSSStyleDeclarationMethod     ,
#endif

-- ** getCssText #method:getCssText#

#if defined(ENABLE_OVERLOADING)
    DOMCSSStyleDeclarationGetCssTextMethodInfo,
#endif
    dOMCSSStyleDeclarationGetCssText        ,


-- ** getLength #method:getLength#

#if defined(ENABLE_OVERLOADING)
    DOMCSSStyleDeclarationGetLengthMethodInfo,
#endif
    dOMCSSStyleDeclarationGetLength         ,


-- ** getParentRule #method:getParentRule#

#if defined(ENABLE_OVERLOADING)
    DOMCSSStyleDeclarationGetParentRuleMethodInfo,
#endif
    dOMCSSStyleDeclarationGetParentRule     ,


-- ** getPropertyPriority #method:getPropertyPriority#

#if defined(ENABLE_OVERLOADING)
    DOMCSSStyleDeclarationGetPropertyPriorityMethodInfo,
#endif
    dOMCSSStyleDeclarationGetPropertyPriority,


-- ** getPropertyShorthand #method:getPropertyShorthand#

#if defined(ENABLE_OVERLOADING)
    DOMCSSStyleDeclarationGetPropertyShorthandMethodInfo,
#endif
    dOMCSSStyleDeclarationGetPropertyShorthand,


-- ** getPropertyValue #method:getPropertyValue#

#if defined(ENABLE_OVERLOADING)
    DOMCSSStyleDeclarationGetPropertyValueMethodInfo,
#endif
    dOMCSSStyleDeclarationGetPropertyValue  ,


-- ** isPropertyImplicit #method:isPropertyImplicit#

#if defined(ENABLE_OVERLOADING)
    DOMCSSStyleDeclarationIsPropertyImplicitMethodInfo,
#endif
    dOMCSSStyleDeclarationIsPropertyImplicit,


-- ** item #method:item#

#if defined(ENABLE_OVERLOADING)
    DOMCSSStyleDeclarationItemMethodInfo    ,
#endif
    dOMCSSStyleDeclarationItem              ,


-- ** removeProperty #method:removeProperty#

#if defined(ENABLE_OVERLOADING)
    DOMCSSStyleDeclarationRemovePropertyMethodInfo,
#endif
    dOMCSSStyleDeclarationRemoveProperty    ,


-- ** setCssText #method:setCssText#

#if defined(ENABLE_OVERLOADING)
    DOMCSSStyleDeclarationSetCssTextMethodInfo,
#endif
    dOMCSSStyleDeclarationSetCssText        ,


-- ** setProperty #method:setProperty#

#if defined(ENABLE_OVERLOADING)
    DOMCSSStyleDeclarationSetPropertyMethodInfo,
#endif
    dOMCSSStyleDeclarationSetProperty       ,




 -- * Properties


-- ** cssText #attr:cssText#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    DOMCSSStyleDeclarationCssTextPropertyInfo,
#endif
    clearDOMCSSStyleDeclarationCssText      ,
    constructDOMCSSStyleDeclarationCssText  ,
#if defined(ENABLE_OVERLOADING)
    dOMCSSStyleDeclarationCssText           ,
#endif
    getDOMCSSStyleDeclarationCssText        ,
    setDOMCSSStyleDeclarationCssText        ,


-- ** length #attr:length#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    DOMCSSStyleDeclarationLengthPropertyInfo,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMCSSStyleDeclarationLength            ,
#endif
    getDOMCSSStyleDeclarationLength         ,


-- ** parentRule #attr:parentRule#
-- | /No description available in the introspection data./

#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.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
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 Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.Kind as DK
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 GHC.Records as R

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

-- | Memory-managed wrapper type.
newtype DOMCSSStyleDeclaration = DOMCSSStyleDeclaration (SP.ManagedPtr DOMCSSStyleDeclaration)
    deriving (DOMCSSStyleDeclaration -> DOMCSSStyleDeclaration -> Bool
(DOMCSSStyleDeclaration -> DOMCSSStyleDeclaration -> Bool)
-> (DOMCSSStyleDeclaration -> DOMCSSStyleDeclaration -> Bool)
-> Eq DOMCSSStyleDeclaration
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DOMCSSStyleDeclaration -> DOMCSSStyleDeclaration -> Bool
== :: DOMCSSStyleDeclaration -> DOMCSSStyleDeclaration -> Bool
$c/= :: DOMCSSStyleDeclaration -> DOMCSSStyleDeclaration -> Bool
/= :: DOMCSSStyleDeclaration -> DOMCSSStyleDeclaration -> Bool
Eq)

instance SP.ManagedPtrNewtype DOMCSSStyleDeclaration where
    toManagedPtr :: DOMCSSStyleDeclaration -> ManagedPtr DOMCSSStyleDeclaration
toManagedPtr (DOMCSSStyleDeclaration ManagedPtr DOMCSSStyleDeclaration
p) = ManagedPtr DOMCSSStyleDeclaration
p

foreign import ccall "webkit_dom_css_style_declaration_get_type"
    c_webkit_dom_css_style_declaration_get_type :: IO B.Types.GType

instance B.Types.TypedObject DOMCSSStyleDeclaration where
    glibType :: IO GType
glibType = IO GType
c_webkit_dom_css_style_declaration_get_type

instance B.Types.GObject DOMCSSStyleDeclaration

-- | Type class for types which can be safely cast to `DOMCSSStyleDeclaration`, for instance with `toDOMCSSStyleDeclaration`.
class (SP.GObject o, O.IsDescendantOf DOMCSSStyleDeclaration o) => IsDOMCSSStyleDeclaration o
instance (SP.GObject o, O.IsDescendantOf DOMCSSStyleDeclaration o) => IsDOMCSSStyleDeclaration o

instance O.HasParentTypes DOMCSSStyleDeclaration
type instance O.ParentTypes DOMCSSStyleDeclaration = '[WebKit2WebExtension.DOMObject.DOMObject, GObject.Object.Object]

-- | Cast to `DOMCSSStyleDeclaration`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toDOMCSSStyleDeclaration :: (MIO.MonadIO m, IsDOMCSSStyleDeclaration o) => o -> m DOMCSSStyleDeclaration
toDOMCSSStyleDeclaration :: forall (m :: * -> *) o.
(MonadIO m, IsDOMCSSStyleDeclaration o) =>
o -> m DOMCSSStyleDeclaration
toDOMCSSStyleDeclaration = IO DOMCSSStyleDeclaration -> m DOMCSSStyleDeclaration
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr DOMCSSStyleDeclaration -> DOMCSSStyleDeclaration
DOMCSSStyleDeclaration

-- | Convert 'DOMCSSStyleDeclaration' to and from 'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue (Maybe DOMCSSStyleDeclaration) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_webkit_dom_css_style_declaration_get_type
    gvalueSet_ :: Ptr GValue -> Maybe DOMCSSStyleDeclaration -> IO ()
gvalueSet_ Ptr GValue
gv Maybe DOMCSSStyleDeclaration
P.Nothing = Ptr GValue -> Ptr DOMCSSStyleDeclaration -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr DOMCSSStyleDeclaration
forall a. Ptr a
FP.nullPtr :: FP.Ptr DOMCSSStyleDeclaration)
    gvalueSet_ Ptr GValue
gv (P.Just DOMCSSStyleDeclaration
obj) = DOMCSSStyleDeclaration
-> (Ptr DOMCSSStyleDeclaration -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr DOMCSSStyleDeclaration
obj (Ptr GValue -> Ptr DOMCSSStyleDeclaration -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe DOMCSSStyleDeclaration)
gvalueGet_ Ptr GValue
gv = do
        Ptr DOMCSSStyleDeclaration
ptr <- Ptr GValue -> IO (Ptr DOMCSSStyleDeclaration)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr DOMCSSStyleDeclaration)
        if Ptr DOMCSSStyleDeclaration
ptr Ptr DOMCSSStyleDeclaration -> Ptr DOMCSSStyleDeclaration -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr DOMCSSStyleDeclaration
forall a. Ptr a
FP.nullPtr
        then DOMCSSStyleDeclaration -> Maybe DOMCSSStyleDeclaration
forall a. a -> Maybe a
P.Just (DOMCSSStyleDeclaration -> Maybe DOMCSSStyleDeclaration)
-> IO DOMCSSStyleDeclaration -> IO (Maybe DOMCSSStyleDeclaration)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (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
        else Maybe DOMCSSStyleDeclaration -> IO (Maybe DOMCSSStyleDeclaration)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe DOMCSSStyleDeclaration
forall a. Maybe a
P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
type family ResolveDOMCSSStyleDeclarationMethod (t :: Symbol) (o :: DK.Type) :: DK.Type 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.OverloadedMethod 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

#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveDOMCSSStyleDeclarationMethod t DOMCSSStyleDeclaration, O.OverloadedMethod info DOMCSSStyleDeclaration p, R.HasField t DOMCSSStyleDeclaration p) => R.HasField t DOMCSSStyleDeclaration p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolveDOMCSSStyleDeclarationMethod t DOMCSSStyleDeclaration, O.OverloadedMethodInfo info DOMCSSStyleDeclaration) => OL.IsLabel t (O.MethodProxy info DOMCSSStyleDeclaration) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif

#endif

-- VVV Prop "css-text"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@css-text@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dOMCSSStyleDeclaration #cssText
-- @
getDOMCSSStyleDeclarationCssText :: (MonadIO m, IsDOMCSSStyleDeclaration o) => o -> m (Maybe T.Text)
getDOMCSSStyleDeclarationCssText :: forall (m :: * -> *) o.
(MonadIO m, IsDOMCSSStyleDeclaration o) =>
o -> m (Maybe Text)
getDOMCSSStyleDeclarationCssText o
obj = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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 String
"css-text"

-- | Set the value of the “@css-text@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' dOMCSSStyleDeclaration [ #cssText 'Data.GI.Base.Attributes.:=' value ]
-- @
setDOMCSSStyleDeclarationCssText :: (MonadIO m, IsDOMCSSStyleDeclaration o) => o -> T.Text -> m ()
setDOMCSSStyleDeclarationCssText :: forall (m :: * -> *) o.
(MonadIO m, IsDOMCSSStyleDeclaration o) =>
o -> Text -> m ()
setDOMCSSStyleDeclarationCssText o
obj Text
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"css-text" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Construct a `GValueConstruct` with valid value for the “@css-text@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructDOMCSSStyleDeclarationCssText :: (IsDOMCSSStyleDeclaration o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructDOMCSSStyleDeclarationCssText :: forall o (m :: * -> *).
(IsDOMCSSStyleDeclaration o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructDOMCSSStyleDeclarationCssText Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"css-text" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

-- | Set the value of the “@css-text@” property to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #cssText
-- @
clearDOMCSSStyleDeclarationCssText :: (MonadIO m, IsDOMCSSStyleDeclaration o) => o -> m ()
clearDOMCSSStyleDeclarationCssText :: forall (m :: * -> *) o.
(MonadIO m, IsDOMCSSStyleDeclaration o) =>
o -> m ()
clearDOMCSSStyleDeclarationCssText o
obj = IO () -> m ()
forall a. IO a -> m a
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 String
"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
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2WebExtension.Objects.DOMCSSStyleDeclaration.cssText"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.30/docs/GI-WebKit2WebExtension-Objects-DOMCSSStyleDeclaration.html#g:attr:cssText"
        })
#endif

-- VVV Prop "length"
   -- Type: TBasicType TULong
   -- Flags: [PropertyReadable]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@length@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dOMCSSStyleDeclaration #length
-- @
getDOMCSSStyleDeclarationLength :: (MonadIO m, IsDOMCSSStyleDeclaration o) => o -> m CULong
getDOMCSSStyleDeclarationLength :: forall (m :: * -> *) o.
(MonadIO m, IsDOMCSSStyleDeclaration o) =>
o -> m CULong
getDOMCSSStyleDeclarationLength o
obj = IO CULong -> m CULong
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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 String
"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
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2WebExtension.Objects.DOMCSSStyleDeclaration.length"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.30/docs/GI-WebKit2WebExtension-Objects-DOMCSSStyleDeclaration.html#g:attr:length"
        })
#endif

-- VVV Prop "parent-rule"
   -- Type: TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMCSSRule"})
   -- Flags: [PropertyReadable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@parent-rule@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dOMCSSStyleDeclaration #parentRule
-- @
getDOMCSSStyleDeclarationParentRule :: (MonadIO m, IsDOMCSSStyleDeclaration o) => o -> m (Maybe WebKit2WebExtension.DOMCSSRule.DOMCSSRule)
getDOMCSSStyleDeclarationParentRule :: forall (m :: * -> *) o.
(MonadIO m, IsDOMCSSStyleDeclaration o) =>
o -> m (Maybe DOMCSSRule)
getDOMCSSStyleDeclarationParentRule o
obj = IO (Maybe DOMCSSRule) -> m (Maybe DOMCSSRule)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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 String
"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
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2WebExtension.Objects.DOMCSSStyleDeclaration.parentRule"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.30/docs/GI-WebKit2WebExtension-Objects-DOMCSSStyleDeclaration.html#g:attr:parentRule"
        })
#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, DK.Type)])
#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, DK.Type)])

#endif

-- method DOMCSSStyleDeclaration::get_css_text
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name
--                   { namespace = "WebKit2WebExtension"
--                   , name = "DOMCSSStyleDeclaration"
--                   }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMCSSStyleDeclaration"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_css_style_declaration_get_css_text" webkit_dom_css_style_declaration_get_css_text :: 
    Ptr DOMCSSStyleDeclaration ->           -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMCSSStyleDeclaration"})
    IO CString

{-# DEPRECATED dOMCSSStyleDeclarationGetCssText ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMCSSStyleDeclarationGetCssText ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMCSSStyleDeclaration a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMCSSStyleDeclaration.DOMCSSStyleDeclaration'
    -> m T.Text
    -- ^ __Returns:__ A @/gchar/@
dOMCSSStyleDeclarationGetCssText :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDOMCSSStyleDeclaration a) =>
a -> m Text
dOMCSSStyleDeclarationGetCssText a
self = IO Text -> m Text
forall a. IO a -> m a
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 Text
"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 a. a -> IO a
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.OverloadedMethod DOMCSSStyleDeclarationGetCssTextMethodInfo a signature where
    overloadedMethod = dOMCSSStyleDeclarationGetCssText

instance O.OverloadedMethodInfo DOMCSSStyleDeclarationGetCssTextMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2WebExtension.Objects.DOMCSSStyleDeclaration.dOMCSSStyleDeclarationGetCssText",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.30/docs/GI-WebKit2WebExtension-Objects-DOMCSSStyleDeclaration.html#v:dOMCSSStyleDeclarationGetCssText"
        })


#endif

-- method DOMCSSStyleDeclaration::get_length
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name
--                   { namespace = "WebKit2WebExtension"
--                   , name = "DOMCSSStyleDeclaration"
--                   }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMCSSStyleDeclaration"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TULong)
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_css_style_declaration_get_length" webkit_dom_css_style_declaration_get_length :: 
    Ptr DOMCSSStyleDeclaration ->           -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMCSSStyleDeclaration"})
    IO CULong

{-# DEPRECATED dOMCSSStyleDeclarationGetLength ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMCSSStyleDeclarationGetLength ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMCSSStyleDeclaration a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMCSSStyleDeclaration.DOMCSSStyleDeclaration'
    -> m CULong
    -- ^ __Returns:__ A @/gulong/@
dOMCSSStyleDeclarationGetLength :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDOMCSSStyleDeclaration a) =>
a -> m CULong
dOMCSSStyleDeclarationGetLength a
self = IO CULong -> m CULong
forall a. IO a -> m a
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 a. a -> IO a
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.OverloadedMethod DOMCSSStyleDeclarationGetLengthMethodInfo a signature where
    overloadedMethod = dOMCSSStyleDeclarationGetLength

instance O.OverloadedMethodInfo DOMCSSStyleDeclarationGetLengthMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2WebExtension.Objects.DOMCSSStyleDeclaration.dOMCSSStyleDeclarationGetLength",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.30/docs/GI-WebKit2WebExtension-Objects-DOMCSSStyleDeclaration.html#v:dOMCSSStyleDeclarationGetLength"
        })


#endif

-- method DOMCSSStyleDeclaration::get_parent_rule
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name
--                   { namespace = "WebKit2WebExtension"
--                   , name = "DOMCSSStyleDeclaration"
--                   }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMCSSStyleDeclaration"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "WebKit2WebExtension" , name = "DOMCSSRule" })
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_css_style_declaration_get_parent_rule" webkit_dom_css_style_declaration_get_parent_rule :: 
    Ptr DOMCSSStyleDeclaration ->           -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMCSSStyleDeclaration"})
    IO (Ptr WebKit2WebExtension.DOMCSSRule.DOMCSSRule)

{-# DEPRECATED dOMCSSStyleDeclarationGetParentRule ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMCSSStyleDeclarationGetParentRule ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMCSSStyleDeclaration a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMCSSStyleDeclaration.DOMCSSStyleDeclaration'
    -> m WebKit2WebExtension.DOMCSSRule.DOMCSSRule
    -- ^ __Returns:__ A t'GI.WebKit2WebExtension.Objects.DOMCSSRule.DOMCSSRule'
dOMCSSStyleDeclarationGetParentRule :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDOMCSSStyleDeclaration a) =>
a -> m DOMCSSRule
dOMCSSStyleDeclarationGetParentRule a
self = IO DOMCSSRule -> m DOMCSSRule
forall a. IO a -> m a
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 Text
"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 a. a -> IO a
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.OverloadedMethod DOMCSSStyleDeclarationGetParentRuleMethodInfo a signature where
    overloadedMethod = dOMCSSStyleDeclarationGetParentRule

instance O.OverloadedMethodInfo DOMCSSStyleDeclarationGetParentRuleMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2WebExtension.Objects.DOMCSSStyleDeclaration.dOMCSSStyleDeclarationGetParentRule",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.30/docs/GI-WebKit2WebExtension-Objects-DOMCSSStyleDeclaration.html#v:dOMCSSStyleDeclarationGetParentRule"
        })


#endif

-- method DOMCSSStyleDeclaration::get_property_priority
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name
--                   { namespace = "WebKit2WebExtension"
--                   , name = "DOMCSSStyleDeclaration"
--                   }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMCSSStyleDeclaration"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "propertyName"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #gchar" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_css_style_declaration_get_property_priority" webkit_dom_css_style_declaration_get_property_priority :: 
    Ptr DOMCSSStyleDeclaration ->           -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMCSSStyleDeclaration"})
    CString ->                              -- propertyName : TBasicType TUTF8
    IO CString

{-# DEPRECATED dOMCSSStyleDeclarationGetPropertyPriority ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMCSSStyleDeclarationGetPropertyPriority ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMCSSStyleDeclaration a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMCSSStyleDeclaration.DOMCSSStyleDeclaration'
    -> T.Text
    -- ^ /@propertyName@/: A @/gchar/@
    -> m T.Text
    -- ^ __Returns:__ A @/gchar/@
dOMCSSStyleDeclarationGetPropertyPriority :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDOMCSSStyleDeclaration a) =>
a -> Text -> m Text
dOMCSSStyleDeclarationGetPropertyPriority a
self Text
propertyName = IO Text -> m Text
forall a. IO a -> m a
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 Text
"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 a. a -> IO a
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.OverloadedMethod DOMCSSStyleDeclarationGetPropertyPriorityMethodInfo a signature where
    overloadedMethod = dOMCSSStyleDeclarationGetPropertyPriority

instance O.OverloadedMethodInfo DOMCSSStyleDeclarationGetPropertyPriorityMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2WebExtension.Objects.DOMCSSStyleDeclaration.dOMCSSStyleDeclarationGetPropertyPriority",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.30/docs/GI-WebKit2WebExtension-Objects-DOMCSSStyleDeclaration.html#v:dOMCSSStyleDeclarationGetPropertyPriority"
        })


#endif

-- method DOMCSSStyleDeclaration::get_property_shorthand
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name
--                   { namespace = "WebKit2WebExtension"
--                   , name = "DOMCSSStyleDeclaration"
--                   }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMCSSStyleDeclaration"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "propertyName"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #gchar" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_css_style_declaration_get_property_shorthand" webkit_dom_css_style_declaration_get_property_shorthand :: 
    Ptr DOMCSSStyleDeclaration ->           -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMCSSStyleDeclaration"})
    CString ->                              -- propertyName : TBasicType TUTF8
    IO CString

{-# DEPRECATED dOMCSSStyleDeclarationGetPropertyShorthand ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMCSSStyleDeclarationGetPropertyShorthand ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMCSSStyleDeclaration a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMCSSStyleDeclaration.DOMCSSStyleDeclaration'
    -> T.Text
    -- ^ /@propertyName@/: A @/gchar/@
    -> m T.Text
    -- ^ __Returns:__ A @/gchar/@
dOMCSSStyleDeclarationGetPropertyShorthand :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDOMCSSStyleDeclaration a) =>
a -> Text -> m Text
dOMCSSStyleDeclarationGetPropertyShorthand a
self Text
propertyName = IO Text -> m Text
forall a. IO a -> m a
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 Text
"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 a. a -> IO a
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.OverloadedMethod DOMCSSStyleDeclarationGetPropertyShorthandMethodInfo a signature where
    overloadedMethod = dOMCSSStyleDeclarationGetPropertyShorthand

instance O.OverloadedMethodInfo DOMCSSStyleDeclarationGetPropertyShorthandMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2WebExtension.Objects.DOMCSSStyleDeclaration.dOMCSSStyleDeclarationGetPropertyShorthand",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.30/docs/GI-WebKit2WebExtension-Objects-DOMCSSStyleDeclaration.html#v:dOMCSSStyleDeclarationGetPropertyShorthand"
        })


#endif

-- method DOMCSSStyleDeclaration::get_property_value
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name
--                   { namespace = "WebKit2WebExtension"
--                   , name = "DOMCSSStyleDeclaration"
--                   }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMCSSStyleDeclaration"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "propertyName"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #gchar" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_css_style_declaration_get_property_value" webkit_dom_css_style_declaration_get_property_value :: 
    Ptr DOMCSSStyleDeclaration ->           -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMCSSStyleDeclaration"})
    CString ->                              -- propertyName : TBasicType TUTF8
    IO CString

{-# DEPRECATED dOMCSSStyleDeclarationGetPropertyValue ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMCSSStyleDeclarationGetPropertyValue ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMCSSStyleDeclaration a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMCSSStyleDeclaration.DOMCSSStyleDeclaration'
    -> T.Text
    -- ^ /@propertyName@/: A @/gchar/@
    -> m T.Text
    -- ^ __Returns:__ A @/gchar/@
dOMCSSStyleDeclarationGetPropertyValue :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDOMCSSStyleDeclaration a) =>
a -> Text -> m Text
dOMCSSStyleDeclarationGetPropertyValue a
self Text
propertyName = IO Text -> m Text
forall a. IO a -> m a
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 Text
"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 a. a -> IO a
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.OverloadedMethod DOMCSSStyleDeclarationGetPropertyValueMethodInfo a signature where
    overloadedMethod = dOMCSSStyleDeclarationGetPropertyValue

instance O.OverloadedMethodInfo DOMCSSStyleDeclarationGetPropertyValueMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2WebExtension.Objects.DOMCSSStyleDeclaration.dOMCSSStyleDeclarationGetPropertyValue",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.30/docs/GI-WebKit2WebExtension-Objects-DOMCSSStyleDeclaration.html#v:dOMCSSStyleDeclarationGetPropertyValue"
        })


#endif

-- method DOMCSSStyleDeclaration::is_property_implicit
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name
--                   { namespace = "WebKit2WebExtension"
--                   , name = "DOMCSSStyleDeclaration"
--                   }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMCSSStyleDeclaration"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "propertyName"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #gchar" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_css_style_declaration_is_property_implicit" webkit_dom_css_style_declaration_is_property_implicit :: 
    Ptr DOMCSSStyleDeclaration ->           -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMCSSStyleDeclaration"})
    CString ->                              -- propertyName : TBasicType TUTF8
    IO CInt

{-# DEPRECATED dOMCSSStyleDeclarationIsPropertyImplicit ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMCSSStyleDeclarationIsPropertyImplicit ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMCSSStyleDeclaration a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMCSSStyleDeclaration.DOMCSSStyleDeclaration'
    -> T.Text
    -- ^ /@propertyName@/: A @/gchar/@
    -> m Bool
    -- ^ __Returns:__ A t'P.Bool'
dOMCSSStyleDeclarationIsPropertyImplicit :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDOMCSSStyleDeclaration a) =>
a -> Text -> m Bool
dOMCSSStyleDeclarationIsPropertyImplicit a
self Text
propertyName = IO Bool -> m Bool
forall a. IO a -> m a
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
/= CInt
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 a. a -> IO a
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.OverloadedMethod DOMCSSStyleDeclarationIsPropertyImplicitMethodInfo a signature where
    overloadedMethod = dOMCSSStyleDeclarationIsPropertyImplicit

instance O.OverloadedMethodInfo DOMCSSStyleDeclarationIsPropertyImplicitMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2WebExtension.Objects.DOMCSSStyleDeclaration.dOMCSSStyleDeclarationIsPropertyImplicit",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.30/docs/GI-WebKit2WebExtension-Objects-DOMCSSStyleDeclaration.html#v:dOMCSSStyleDeclarationIsPropertyImplicit"
        })


#endif

-- method DOMCSSStyleDeclaration::item
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name
--                   { namespace = "WebKit2WebExtension"
--                   , name = "DOMCSSStyleDeclaration"
--                   }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMCSSStyleDeclaration"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "index"
--           , argType = TBasicType TULong
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #gulong" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_css_style_declaration_item" webkit_dom_css_style_declaration_item :: 
    Ptr DOMCSSStyleDeclaration ->           -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMCSSStyleDeclaration"})
    CULong ->                               -- index : TBasicType TULong
    IO CString

{-# DEPRECATED dOMCSSStyleDeclarationItem ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMCSSStyleDeclarationItem ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMCSSStyleDeclaration a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMCSSStyleDeclaration.DOMCSSStyleDeclaration'
    -> CULong
    -- ^ /@index@/: A @/gulong/@
    -> m T.Text
    -- ^ __Returns:__ A @/gchar/@
dOMCSSStyleDeclarationItem :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDOMCSSStyleDeclaration a) =>
a -> CULong -> m Text
dOMCSSStyleDeclarationItem a
self CULong
index = IO Text -> m Text
forall a. IO a -> m a
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 Text
"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 a. a -> IO a
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.OverloadedMethod DOMCSSStyleDeclarationItemMethodInfo a signature where
    overloadedMethod = dOMCSSStyleDeclarationItem

instance O.OverloadedMethodInfo DOMCSSStyleDeclarationItemMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2WebExtension.Objects.DOMCSSStyleDeclaration.dOMCSSStyleDeclarationItem",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.30/docs/GI-WebKit2WebExtension-Objects-DOMCSSStyleDeclaration.html#v:dOMCSSStyleDeclarationItem"
        })


#endif

-- method DOMCSSStyleDeclaration::remove_property
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name
--                   { namespace = "WebKit2WebExtension"
--                   , name = "DOMCSSStyleDeclaration"
--                   }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMCSSStyleDeclaration"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "propertyName"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #gchar" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : True
-- Skip return : False

foreign import ccall "webkit_dom_css_style_declaration_remove_property" webkit_dom_css_style_declaration_remove_property :: 
    Ptr DOMCSSStyleDeclaration ->           -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMCSSStyleDeclaration"})
    CString ->                              -- propertyName : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO CString

{-# DEPRECATED dOMCSSStyleDeclarationRemoveProperty ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMCSSStyleDeclarationRemoveProperty ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMCSSStyleDeclaration a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMCSSStyleDeclaration.DOMCSSStyleDeclaration'
    -> T.Text
    -- ^ /@propertyName@/: A @/gchar/@
    -> m T.Text
    -- ^ __Returns:__ A @/gchar/@ /(Can throw 'Data.GI.Base.GError.GError')/
dOMCSSStyleDeclarationRemoveProperty :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDOMCSSStyleDeclaration a) =>
a -> Text -> m Text
dOMCSSStyleDeclarationRemoveProperty a
self Text
propertyName = IO Text -> m Text
forall a. IO a -> m a
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 Text
"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 a. a -> IO a
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.OverloadedMethod DOMCSSStyleDeclarationRemovePropertyMethodInfo a signature where
    overloadedMethod = dOMCSSStyleDeclarationRemoveProperty

instance O.OverloadedMethodInfo DOMCSSStyleDeclarationRemovePropertyMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2WebExtension.Objects.DOMCSSStyleDeclaration.dOMCSSStyleDeclarationRemoveProperty",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.30/docs/GI-WebKit2WebExtension-Objects-DOMCSSStyleDeclaration.html#v:dOMCSSStyleDeclarationRemoveProperty"
        })


#endif

-- method DOMCSSStyleDeclaration::set_css_text
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name
--                   { namespace = "WebKit2WebExtension"
--                   , name = "DOMCSSStyleDeclaration"
--                   }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMCSSStyleDeclaration"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #gchar" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : True
-- Skip return : False

foreign import ccall "webkit_dom_css_style_declaration_set_css_text" webkit_dom_css_style_declaration_set_css_text :: 
    Ptr DOMCSSStyleDeclaration ->           -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMCSSStyleDeclaration"})
    CString ->                              -- value : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO ()

{-# DEPRECATED dOMCSSStyleDeclarationSetCssText ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMCSSStyleDeclarationSetCssText ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMCSSStyleDeclaration a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMCSSStyleDeclaration.DOMCSSStyleDeclaration'
    -> T.Text
    -- ^ /@value@/: A @/gchar/@
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
dOMCSSStyleDeclarationSetCssText :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDOMCSSStyleDeclaration a) =>
a -> Text -> m ()
dOMCSSStyleDeclarationSetCssText a
self Text
value = IO () -> m ()
forall a. IO a -> m a
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 a. a -> IO a
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.OverloadedMethod DOMCSSStyleDeclarationSetCssTextMethodInfo a signature where
    overloadedMethod = dOMCSSStyleDeclarationSetCssText

instance O.OverloadedMethodInfo DOMCSSStyleDeclarationSetCssTextMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2WebExtension.Objects.DOMCSSStyleDeclaration.dOMCSSStyleDeclarationSetCssText",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.30/docs/GI-WebKit2WebExtension-Objects-DOMCSSStyleDeclaration.html#v:dOMCSSStyleDeclarationSetCssText"
        })


#endif

-- method DOMCSSStyleDeclaration::set_property
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name
--                   { namespace = "WebKit2WebExtension"
--                   , name = "DOMCSSStyleDeclaration"
--                   }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMCSSStyleDeclaration"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "propertyName"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #gchar" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #gchar" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "priority"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #gchar" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : True
-- Skip return : False

foreign import ccall "webkit_dom_css_style_declaration_set_property" webkit_dom_css_style_declaration_set_property :: 
    Ptr DOMCSSStyleDeclaration ->           -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMCSSStyleDeclaration"})
    CString ->                              -- propertyName : TBasicType TUTF8
    CString ->                              -- value : TBasicType TUTF8
    CString ->                              -- priority : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO ()

{-# DEPRECATED dOMCSSStyleDeclarationSetProperty ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMCSSStyleDeclarationSetProperty ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMCSSStyleDeclaration a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMCSSStyleDeclaration.DOMCSSStyleDeclaration'
    -> T.Text
    -- ^ /@propertyName@/: A @/gchar/@
    -> T.Text
    -- ^ /@value@/: A @/gchar/@
    -> T.Text
    -- ^ /@priority@/: A @/gchar/@
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
dOMCSSStyleDeclarationSetProperty :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDOMCSSStyleDeclaration a) =>
a -> Text -> Text -> Text -> m ()
dOMCSSStyleDeclarationSetProperty a
self Text
propertyName Text
value Text
priority = IO () -> m ()
forall a. IO a -> m a
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 a. a -> IO a
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.OverloadedMethod DOMCSSStyleDeclarationSetPropertyMethodInfo a signature where
    overloadedMethod = dOMCSSStyleDeclarationSetProperty

instance O.OverloadedMethodInfo DOMCSSStyleDeclarationSetPropertyMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2WebExtension.Objects.DOMCSSStyleDeclaration.dOMCSSStyleDeclarationSetProperty",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.30/docs/GI-WebKit2WebExtension-Objects-DOMCSSStyleDeclaration.html#v:dOMCSSStyleDeclarationSetProperty"
        })


#endif