{-# 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.DOMCSSRule
    ( 

-- * Exported types
    DOMCSSRule(..)                          ,
    IsDOMCSSRule                            ,
    toDOMCSSRule                            ,


 -- * 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"), [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"), [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.DOMCSSRule#g:method:getCssText"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getParentRule]("GI.WebKit2WebExtension.Objects.DOMCSSRule#g:method:getParentRule"), [getParentStyleSheet]("GI.WebKit2WebExtension.Objects.DOMCSSRule#g:method:getParentStyleSheet"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getRuleType]("GI.WebKit2WebExtension.Objects.DOMCSSRule#g:method:getRuleType").
-- 
-- ==== Setters
-- [setCssText]("GI.WebKit2WebExtension.Objects.DOMCSSRule#g:method:setCssText"), [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolveDOMCSSRuleMethod                 ,
#endif

-- ** getCssText #method:getCssText#

#if defined(ENABLE_OVERLOADING)
    DOMCSSRuleGetCssTextMethodInfo          ,
#endif
    dOMCSSRuleGetCssText                    ,


-- ** getParentRule #method:getParentRule#

#if defined(ENABLE_OVERLOADING)
    DOMCSSRuleGetParentRuleMethodInfo       ,
#endif
    dOMCSSRuleGetParentRule                 ,


-- ** getParentStyleSheet #method:getParentStyleSheet#

#if defined(ENABLE_OVERLOADING)
    DOMCSSRuleGetParentStyleSheetMethodInfo ,
#endif
    dOMCSSRuleGetParentStyleSheet           ,


-- ** getRuleType #method:getRuleType#

#if defined(ENABLE_OVERLOADING)
    DOMCSSRuleGetRuleTypeMethodInfo         ,
#endif
    dOMCSSRuleGetRuleType                   ,


-- ** setCssText #method:setCssText#

#if defined(ENABLE_OVERLOADING)
    DOMCSSRuleSetCssTextMethodInfo          ,
#endif
    dOMCSSRuleSetCssText                    ,




 -- * Properties


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

#if defined(ENABLE_OVERLOADING)
    DOMCSSRuleCssTextPropertyInfo           ,
#endif
    clearDOMCSSRuleCssText                  ,
    constructDOMCSSRuleCssText              ,
#if defined(ENABLE_OVERLOADING)
    dOMCSSRuleCssText                       ,
#endif
    getDOMCSSRuleCssText                    ,
    setDOMCSSRuleCssText                    ,


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

#if defined(ENABLE_OVERLOADING)
    DOMCSSRuleParentRulePropertyInfo        ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMCSSRuleParentRule                    ,
#endif
    getDOMCSSRuleParentRule                 ,


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

#if defined(ENABLE_OVERLOADING)
    DOMCSSRuleParentStyleSheetPropertyInfo  ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMCSSRuleParentStyleSheet              ,
#endif
    getDOMCSSRuleParentStyleSheet           ,


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

#if defined(ENABLE_OVERLOADING)
    DOMCSSRuleTypePropertyInfo              ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMCSSRuleType                          ,
#endif
    getDOMCSSRuleType                       ,




    ) 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.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.DOMCSSStyleSheet as WebKit2WebExtension.DOMCSSStyleSheet
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMObject as WebKit2WebExtension.DOMObject

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

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

foreign import ccall "webkit_dom_css_rule_get_type"
    c_webkit_dom_css_rule_get_type :: IO B.Types.GType

instance B.Types.TypedObject DOMCSSRule where
    glibType :: IO GType
glibType = IO GType
c_webkit_dom_css_rule_get_type

instance B.Types.GObject DOMCSSRule

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

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

-- | Cast to `DOMCSSRule`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toDOMCSSRule :: (MIO.MonadIO m, IsDOMCSSRule o) => o -> m DOMCSSRule
toDOMCSSRule :: forall (m :: * -> *) o.
(MonadIO m, IsDOMCSSRule o) =>
o -> m DOMCSSRule
toDOMCSSRule = IO DOMCSSRule -> m DOMCSSRule
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO DOMCSSRule -> m DOMCSSRule)
-> (o -> IO DOMCSSRule) -> o -> m DOMCSSRule
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr DOMCSSRule -> DOMCSSRule) -> o -> IO DOMCSSRule
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr DOMCSSRule -> DOMCSSRule
DOMCSSRule

-- | Convert 'DOMCSSRule' 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 DOMCSSRule) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_webkit_dom_css_rule_get_type
    gvalueSet_ :: Ptr GValue -> Maybe DOMCSSRule -> IO ()
gvalueSet_ Ptr GValue
gv Maybe DOMCSSRule
P.Nothing = Ptr GValue -> Ptr DOMCSSRule -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr DOMCSSRule
forall a. Ptr a
FP.nullPtr :: FP.Ptr DOMCSSRule)
    gvalueSet_ Ptr GValue
gv (P.Just DOMCSSRule
obj) = DOMCSSRule -> (Ptr DOMCSSRule -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr DOMCSSRule
obj (Ptr GValue -> Ptr DOMCSSRule -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe DOMCSSRule)
gvalueGet_ Ptr GValue
gv = do
        Ptr DOMCSSRule
ptr <- Ptr GValue -> IO (Ptr DOMCSSRule)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr DOMCSSRule)
        if Ptr DOMCSSRule
ptr Ptr DOMCSSRule -> Ptr DOMCSSRule -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr DOMCSSRule
forall a. Ptr a
FP.nullPtr
        then DOMCSSRule -> Maybe DOMCSSRule
forall a. a -> Maybe a
P.Just (DOMCSSRule -> Maybe DOMCSSRule)
-> IO DOMCSSRule -> IO (Maybe DOMCSSRule)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr DOMCSSRule -> DOMCSSRule)
-> Ptr DOMCSSRule -> IO DOMCSSRule
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr DOMCSSRule -> DOMCSSRule
DOMCSSRule Ptr DOMCSSRule
ptr
        else Maybe DOMCSSRule -> IO (Maybe DOMCSSRule)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe DOMCSSRule
forall a. Maybe a
P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
type family ResolveDOMCSSRuleMethod (t :: Symbol) (o :: *) :: * where
    ResolveDOMCSSRuleMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveDOMCSSRuleMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveDOMCSSRuleMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveDOMCSSRuleMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveDOMCSSRuleMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveDOMCSSRuleMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveDOMCSSRuleMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveDOMCSSRuleMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveDOMCSSRuleMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveDOMCSSRuleMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveDOMCSSRuleMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveDOMCSSRuleMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveDOMCSSRuleMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveDOMCSSRuleMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveDOMCSSRuleMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveDOMCSSRuleMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveDOMCSSRuleMethod "getCssText" o = DOMCSSRuleGetCssTextMethodInfo
    ResolveDOMCSSRuleMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveDOMCSSRuleMethod "getParentRule" o = DOMCSSRuleGetParentRuleMethodInfo
    ResolveDOMCSSRuleMethod "getParentStyleSheet" o = DOMCSSRuleGetParentStyleSheetMethodInfo
    ResolveDOMCSSRuleMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveDOMCSSRuleMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveDOMCSSRuleMethod "getRuleType" o = DOMCSSRuleGetRuleTypeMethodInfo
    ResolveDOMCSSRuleMethod "setCssText" o = DOMCSSRuleSetCssTextMethodInfo
    ResolveDOMCSSRuleMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveDOMCSSRuleMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveDOMCSSRuleMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveDOMCSSRuleMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveDOMCSSRuleMethod t DOMCSSRule, O.OverloadedMethod info DOMCSSRule p) => OL.IsLabel t (DOMCSSRule -> 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 ~ ResolveDOMCSSRuleMethod t DOMCSSRule, O.OverloadedMethod info DOMCSSRule p, R.HasField t DOMCSSRule p) => R.HasField t DOMCSSRule p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolveDOMCSSRuleMethod t DOMCSSRule, O.OverloadedMethodInfo info DOMCSSRule) => OL.IsLabel t (O.MethodProxy info DOMCSSRule) 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' dOMCSSRule #cssText
-- @
getDOMCSSRuleCssText :: (MonadIO m, IsDOMCSSRule o) => o -> m (Maybe T.Text)
getDOMCSSRuleCssText :: forall (m :: * -> *) o.
(MonadIO m, IsDOMCSSRule o) =>
o -> m (Maybe Text)
getDOMCSSRuleCssText 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' dOMCSSRule [ #cssText 'Data.GI.Base.Attributes.:=' value ]
-- @
setDOMCSSRuleCssText :: (MonadIO m, IsDOMCSSRule o) => o -> T.Text -> m ()
setDOMCSSRuleCssText :: forall (m :: * -> *) o.
(MonadIO m, IsDOMCSSRule o) =>
o -> Text -> m ()
setDOMCSSRuleCssText 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`.
constructDOMCSSRuleCssText :: (IsDOMCSSRule o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructDOMCSSRuleCssText :: forall o (m :: * -> *).
(IsDOMCSSRule o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructDOMCSSRuleCssText 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
-- @
clearDOMCSSRuleCssText :: (MonadIO m, IsDOMCSSRule o) => o -> m ()
clearDOMCSSRuleCssText :: forall (m :: * -> *) o. (MonadIO m, IsDOMCSSRule o) => o -> m ()
clearDOMCSSRuleCssText 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 DOMCSSRuleCssTextPropertyInfo
instance AttrInfo DOMCSSRuleCssTextPropertyInfo where
    type AttrAllowedOps DOMCSSRuleCssTextPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint DOMCSSRuleCssTextPropertyInfo = IsDOMCSSRule
    type AttrSetTypeConstraint DOMCSSRuleCssTextPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint DOMCSSRuleCssTextPropertyInfo = (~) T.Text
    type AttrTransferType DOMCSSRuleCssTextPropertyInfo = T.Text
    type AttrGetType DOMCSSRuleCssTextPropertyInfo = (Maybe T.Text)
    type AttrLabel DOMCSSRuleCssTextPropertyInfo = "css-text"
    type AttrOrigin DOMCSSRuleCssTextPropertyInfo = DOMCSSRule
    attrGet = getDOMCSSRuleCssText
    attrSet = setDOMCSSRuleCssText
    attrTransfer _ v = do
        return v
    attrConstruct = constructDOMCSSRuleCssText
    attrClear = clearDOMCSSRuleCssText
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2WebExtension.Objects.DOMCSSRule.cssText"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.28/docs/GI-WebKit2WebExtension-Objects-DOMCSSRule.html#g:attr:cssText"
        })
#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' dOMCSSRule #parentRule
-- @
getDOMCSSRuleParentRule :: (MonadIO m, IsDOMCSSRule o) => o -> m (Maybe DOMCSSRule)
getDOMCSSRuleParentRule :: forall (m :: * -> *) o.
(MonadIO m, IsDOMCSSRule o) =>
o -> m (Maybe DOMCSSRule)
getDOMCSSRuleParentRule 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
DOMCSSRule

#if defined(ENABLE_OVERLOADING)
data DOMCSSRuleParentRulePropertyInfo
instance AttrInfo DOMCSSRuleParentRulePropertyInfo where
    type AttrAllowedOps DOMCSSRuleParentRulePropertyInfo = '[ 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint DOMCSSRuleParentRulePropertyInfo = IsDOMCSSRule
    type AttrSetTypeConstraint DOMCSSRuleParentRulePropertyInfo = (~) ()
    type AttrTransferTypeConstraint DOMCSSRuleParentRulePropertyInfo = (~) ()
    type AttrTransferType DOMCSSRuleParentRulePropertyInfo = ()
    type AttrGetType DOMCSSRuleParentRulePropertyInfo = (Maybe DOMCSSRule)
    type AttrLabel DOMCSSRuleParentRulePropertyInfo = "parent-rule"
    type AttrOrigin DOMCSSRuleParentRulePropertyInfo = DOMCSSRule
    attrGet = getDOMCSSRuleParentRule
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2WebExtension.Objects.DOMCSSRule.parentRule"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.28/docs/GI-WebKit2WebExtension-Objects-DOMCSSRule.html#g:attr:parentRule"
        })
#endif

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

-- | Get the value of the “@parent-style-sheet@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dOMCSSRule #parentStyleSheet
-- @
getDOMCSSRuleParentStyleSheet :: (MonadIO m, IsDOMCSSRule o) => o -> m (Maybe WebKit2WebExtension.DOMCSSStyleSheet.DOMCSSStyleSheet)
getDOMCSSRuleParentStyleSheet :: forall (m :: * -> *) o.
(MonadIO m, IsDOMCSSRule o) =>
o -> m (Maybe DOMCSSStyleSheet)
getDOMCSSRuleParentStyleSheet o
obj = IO (Maybe DOMCSSStyleSheet) -> m (Maybe DOMCSSStyleSheet)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe DOMCSSStyleSheet) -> m (Maybe DOMCSSStyleSheet))
-> IO (Maybe DOMCSSStyleSheet) -> m (Maybe DOMCSSStyleSheet)
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr DOMCSSStyleSheet -> DOMCSSStyleSheet)
-> IO (Maybe DOMCSSStyleSheet)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"parent-style-sheet" ManagedPtr DOMCSSStyleSheet -> DOMCSSStyleSheet
WebKit2WebExtension.DOMCSSStyleSheet.DOMCSSStyleSheet

#if defined(ENABLE_OVERLOADING)
data DOMCSSRuleParentStyleSheetPropertyInfo
instance AttrInfo DOMCSSRuleParentStyleSheetPropertyInfo where
    type AttrAllowedOps DOMCSSRuleParentStyleSheetPropertyInfo = '[ 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint DOMCSSRuleParentStyleSheetPropertyInfo = IsDOMCSSRule
    type AttrSetTypeConstraint DOMCSSRuleParentStyleSheetPropertyInfo = (~) ()
    type AttrTransferTypeConstraint DOMCSSRuleParentStyleSheetPropertyInfo = (~) ()
    type AttrTransferType DOMCSSRuleParentStyleSheetPropertyInfo = ()
    type AttrGetType DOMCSSRuleParentStyleSheetPropertyInfo = (Maybe WebKit2WebExtension.DOMCSSStyleSheet.DOMCSSStyleSheet)
    type AttrLabel DOMCSSRuleParentStyleSheetPropertyInfo = "parent-style-sheet"
    type AttrOrigin DOMCSSRuleParentStyleSheetPropertyInfo = DOMCSSRule
    attrGet = getDOMCSSRuleParentStyleSheet
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2WebExtension.Objects.DOMCSSRule.parentStyleSheet"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.28/docs/GI-WebKit2WebExtension-Objects-DOMCSSRule.html#g:attr:parentStyleSheet"
        })
#endif

-- VVV Prop "type"
   -- Type: TBasicType TUInt
   -- Flags: [PropertyReadable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@type@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dOMCSSRule #type
-- @
getDOMCSSRuleType :: (MonadIO m, IsDOMCSSRule o) => o -> m Word32
getDOMCSSRuleType :: forall (m :: * -> *) o.
(MonadIO m, IsDOMCSSRule o) =>
o -> m Word32
getDOMCSSRuleType o
obj = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Word32
forall a. GObject a => a -> String -> IO Word32
B.Properties.getObjectPropertyUInt32 o
obj String
"type"

#if defined(ENABLE_OVERLOADING)
data DOMCSSRuleTypePropertyInfo
instance AttrInfo DOMCSSRuleTypePropertyInfo where
    type AttrAllowedOps DOMCSSRuleTypePropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint DOMCSSRuleTypePropertyInfo = IsDOMCSSRule
    type AttrSetTypeConstraint DOMCSSRuleTypePropertyInfo = (~) ()
    type AttrTransferTypeConstraint DOMCSSRuleTypePropertyInfo = (~) ()
    type AttrTransferType DOMCSSRuleTypePropertyInfo = ()
    type AttrGetType DOMCSSRuleTypePropertyInfo = Word32
    type AttrLabel DOMCSSRuleTypePropertyInfo = "type"
    type AttrOrigin DOMCSSRuleTypePropertyInfo = DOMCSSRule
    attrGet = getDOMCSSRuleType
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2WebExtension.Objects.DOMCSSRule.type"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.28/docs/GI-WebKit2WebExtension-Objects-DOMCSSRule.html#g:attr:type"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList DOMCSSRule
type instance O.AttributeList DOMCSSRule = DOMCSSRuleAttributeList
type DOMCSSRuleAttributeList = ('[ '("coreObject", WebKit2WebExtension.DOMObject.DOMObjectCoreObjectPropertyInfo), '("cssText", DOMCSSRuleCssTextPropertyInfo), '("parentRule", DOMCSSRuleParentRulePropertyInfo), '("parentStyleSheet", DOMCSSRuleParentStyleSheetPropertyInfo), '("type", DOMCSSRuleTypePropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
dOMCSSRuleCssText :: AttrLabelProxy "cssText"
dOMCSSRuleCssText = AttrLabelProxy

dOMCSSRuleParentRule :: AttrLabelProxy "parentRule"
dOMCSSRuleParentRule = AttrLabelProxy

dOMCSSRuleParentStyleSheet :: AttrLabelProxy "parentStyleSheet"
dOMCSSRuleParentStyleSheet = AttrLabelProxy

dOMCSSRuleType :: AttrLabelProxy "type"
dOMCSSRuleType = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList DOMCSSRule = DOMCSSRuleSignalList
type DOMCSSRuleSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif

-- method DOMCSSRule::get_css_text
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit2WebExtension" , name = "DOMCSSRule" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMCSSRule"
--                 , 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_rule_get_css_text" webkit_dom_css_rule_get_css_text :: 
    Ptr DOMCSSRule ->                       -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMCSSRule"})
    IO CString

{-# DEPRECATED dOMCSSRuleGetCssText ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMCSSRuleGetCssText ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMCSSRule a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMCSSRule.DOMCSSRule'
    -> m T.Text
    -- ^ __Returns:__ A @/gchar/@
dOMCSSRuleGetCssText :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDOMCSSRule a) =>
a -> m Text
dOMCSSRuleGetCssText 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 DOMCSSRule
self' <- a -> IO (Ptr DOMCSSRule)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
result <- Ptr DOMCSSRule -> IO CString
webkit_dom_css_rule_get_css_text Ptr DOMCSSRule
self'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"dOMCSSRuleGetCssText" 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 DOMCSSRuleGetCssTextMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsDOMCSSRule a) => O.OverloadedMethod DOMCSSRuleGetCssTextMethodInfo a signature where
    overloadedMethod = dOMCSSRuleGetCssText

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


#endif

-- method DOMCSSRule::get_parent_rule
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit2WebExtension" , name = "DOMCSSRule" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMCSSRule"
--                 , 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_rule_get_parent_rule" webkit_dom_css_rule_get_parent_rule :: 
    Ptr DOMCSSRule ->                       -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMCSSRule"})
    IO (Ptr DOMCSSRule)

{-# DEPRECATED dOMCSSRuleGetParentRule ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMCSSRuleGetParentRule ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMCSSRule a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMCSSRule.DOMCSSRule'
    -> m DOMCSSRule
    -- ^ __Returns:__ A t'GI.WebKit2WebExtension.Objects.DOMCSSRule.DOMCSSRule'
dOMCSSRuleGetParentRule :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDOMCSSRule a) =>
a -> m DOMCSSRule
dOMCSSRuleGetParentRule 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 DOMCSSRule
self' <- a -> IO (Ptr DOMCSSRule)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr DOMCSSRule
result <- Ptr DOMCSSRule -> IO (Ptr DOMCSSRule)
webkit_dom_css_rule_get_parent_rule Ptr DOMCSSRule
self'
    Text -> Ptr DOMCSSRule -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"dOMCSSRuleGetParentRule" 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
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 DOMCSSRuleGetParentRuleMethodInfo
instance (signature ~ (m DOMCSSRule), MonadIO m, IsDOMCSSRule a) => O.OverloadedMethod DOMCSSRuleGetParentRuleMethodInfo a signature where
    overloadedMethod = dOMCSSRuleGetParentRule

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


#endif

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

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

{-# DEPRECATED dOMCSSRuleGetParentStyleSheet ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMCSSRuleGetParentStyleSheet ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMCSSRule a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMCSSRule.DOMCSSRule'
    -> m WebKit2WebExtension.DOMCSSStyleSheet.DOMCSSStyleSheet
    -- ^ __Returns:__ A t'GI.WebKit2WebExtension.Objects.DOMCSSStyleSheet.DOMCSSStyleSheet'
dOMCSSRuleGetParentStyleSheet :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDOMCSSRule a) =>
a -> m DOMCSSStyleSheet
dOMCSSRuleGetParentStyleSheet a
self = IO DOMCSSStyleSheet -> m DOMCSSStyleSheet
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DOMCSSStyleSheet -> m DOMCSSStyleSheet)
-> IO DOMCSSStyleSheet -> m DOMCSSStyleSheet
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMCSSRule
self' <- a -> IO (Ptr DOMCSSRule)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr DOMCSSStyleSheet
result <- Ptr DOMCSSRule -> IO (Ptr DOMCSSStyleSheet)
webkit_dom_css_rule_get_parent_style_sheet Ptr DOMCSSRule
self'
    Text -> Ptr DOMCSSStyleSheet -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"dOMCSSRuleGetParentStyleSheet" Ptr DOMCSSStyleSheet
result
    DOMCSSStyleSheet
result' <- ((ManagedPtr DOMCSSStyleSheet -> DOMCSSStyleSheet)
-> Ptr DOMCSSStyleSheet -> IO DOMCSSStyleSheet
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr DOMCSSStyleSheet -> DOMCSSStyleSheet
WebKit2WebExtension.DOMCSSStyleSheet.DOMCSSStyleSheet) Ptr DOMCSSStyleSheet
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    DOMCSSStyleSheet -> IO DOMCSSStyleSheet
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return DOMCSSStyleSheet
result'

#if defined(ENABLE_OVERLOADING)
data DOMCSSRuleGetParentStyleSheetMethodInfo
instance (signature ~ (m WebKit2WebExtension.DOMCSSStyleSheet.DOMCSSStyleSheet), MonadIO m, IsDOMCSSRule a) => O.OverloadedMethod DOMCSSRuleGetParentStyleSheetMethodInfo a signature where
    overloadedMethod = dOMCSSRuleGetParentStyleSheet

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


#endif

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

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

{-# DEPRECATED dOMCSSRuleGetRuleType ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMCSSRuleGetRuleType ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMCSSRule a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMCSSRule.DOMCSSRule'
    -> m Word16
    -- ^ __Returns:__ A @/gushort/@
dOMCSSRuleGetRuleType :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDOMCSSRule a) =>
a -> m Word16
dOMCSSRuleGetRuleType a
self = IO Word16 -> m Word16
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word16 -> m Word16) -> IO Word16 -> m Word16
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMCSSRule
self' <- a -> IO (Ptr DOMCSSRule)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Word16
result <- Ptr DOMCSSRule -> IO Word16
webkit_dom_css_rule_get_rule_type Ptr DOMCSSRule
self'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Word16 -> IO Word16
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word16
result

#if defined(ENABLE_OVERLOADING)
data DOMCSSRuleGetRuleTypeMethodInfo
instance (signature ~ (m Word16), MonadIO m, IsDOMCSSRule a) => O.OverloadedMethod DOMCSSRuleGetRuleTypeMethodInfo a signature where
    overloadedMethod = dOMCSSRuleGetRuleType

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


#endif

-- method DOMCSSRule::set_css_text
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit2WebExtension" , name = "DOMCSSRule" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMCSSRule"
--                 , 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_rule_set_css_text" webkit_dom_css_rule_set_css_text :: 
    Ptr DOMCSSRule ->                       -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMCSSRule"})
    CString ->                              -- value : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO ()

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

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


#endif