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

-- * Exported types
    DOMStyleSheet(..)                       ,
    IsDOMStyleSheet                         ,
    toDOMStyleSheet                         ,


 -- * 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
-- [getContentType]("GI.WebKit2WebExtension.Objects.DOMStyleSheet#g:method:getContentType"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getDisabled]("GI.WebKit2WebExtension.Objects.DOMStyleSheet#g:method:getDisabled"), [getHref]("GI.WebKit2WebExtension.Objects.DOMStyleSheet#g:method:getHref"), [getMedia]("GI.WebKit2WebExtension.Objects.DOMStyleSheet#g:method:getMedia"), [getOwnerNode]("GI.WebKit2WebExtension.Objects.DOMStyleSheet#g:method:getOwnerNode"), [getParentStyleSheet]("GI.WebKit2WebExtension.Objects.DOMStyleSheet#g:method:getParentStyleSheet"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getTitle]("GI.WebKit2WebExtension.Objects.DOMStyleSheet#g:method:getTitle").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setDisabled]("GI.WebKit2WebExtension.Objects.DOMStyleSheet#g:method:setDisabled"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolveDOMStyleSheetMethod              ,
#endif

-- ** getContentType #method:getContentType#

#if defined(ENABLE_OVERLOADING)
    DOMStyleSheetGetContentTypeMethodInfo   ,
#endif
    dOMStyleSheetGetContentType             ,


-- ** getDisabled #method:getDisabled#

#if defined(ENABLE_OVERLOADING)
    DOMStyleSheetGetDisabledMethodInfo      ,
#endif
    dOMStyleSheetGetDisabled                ,


-- ** getHref #method:getHref#

#if defined(ENABLE_OVERLOADING)
    DOMStyleSheetGetHrefMethodInfo          ,
#endif
    dOMStyleSheetGetHref                    ,


-- ** getMedia #method:getMedia#

#if defined(ENABLE_OVERLOADING)
    DOMStyleSheetGetMediaMethodInfo         ,
#endif
    dOMStyleSheetGetMedia                   ,


-- ** getOwnerNode #method:getOwnerNode#

#if defined(ENABLE_OVERLOADING)
    DOMStyleSheetGetOwnerNodeMethodInfo     ,
#endif
    dOMStyleSheetGetOwnerNode               ,


-- ** getParentStyleSheet #method:getParentStyleSheet#

#if defined(ENABLE_OVERLOADING)
    DOMStyleSheetGetParentStyleSheetMethodInfo,
#endif
    dOMStyleSheetGetParentStyleSheet        ,


-- ** getTitle #method:getTitle#

#if defined(ENABLE_OVERLOADING)
    DOMStyleSheetGetTitleMethodInfo         ,
#endif
    dOMStyleSheetGetTitle                   ,


-- ** setDisabled #method:setDisabled#

#if defined(ENABLE_OVERLOADING)
    DOMStyleSheetSetDisabledMethodInfo      ,
#endif
    dOMStyleSheetSetDisabled                ,




 -- * Properties


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

#if defined(ENABLE_OVERLOADING)
    DOMStyleSheetDisabledPropertyInfo       ,
#endif
    constructDOMStyleSheetDisabled          ,
#if defined(ENABLE_OVERLOADING)
    dOMStyleSheetDisabled                   ,
#endif
    getDOMStyleSheetDisabled                ,
    setDOMStyleSheetDisabled                ,


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

#if defined(ENABLE_OVERLOADING)
    DOMStyleSheetHrefPropertyInfo           ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMStyleSheetHref                       ,
#endif
    getDOMStyleSheetHref                    ,


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

#if defined(ENABLE_OVERLOADING)
    DOMStyleSheetMediaPropertyInfo          ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMStyleSheetMedia                      ,
#endif
    getDOMStyleSheetMedia                   ,


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

#if defined(ENABLE_OVERLOADING)
    DOMStyleSheetOwnerNodePropertyInfo      ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMStyleSheetOwnerNode                  ,
#endif
    getDOMStyleSheetOwnerNode               ,


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

#if defined(ENABLE_OVERLOADING)
    DOMStyleSheetParentStyleSheetPropertyInfo,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMStyleSheetParentStyleSheet           ,
#endif
    getDOMStyleSheetParentStyleSheet        ,


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

#if defined(ENABLE_OVERLOADING)
    DOMStyleSheetTitlePropertyInfo          ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMStyleSheetTitle                      ,
#endif
    getDOMStyleSheetTitle                   ,


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

#if defined(ENABLE_OVERLOADING)
    DOMStyleSheetTypePropertyInfo           ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMStyleSheetType                       ,
#endif
    getDOMStyleSheetType                    ,




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

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

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

foreign import ccall "webkit_dom_style_sheet_get_type"
    c_webkit_dom_style_sheet_get_type :: IO B.Types.GType

instance B.Types.TypedObject DOMStyleSheet where
    glibType :: IO GType
glibType = IO GType
c_webkit_dom_style_sheet_get_type

instance B.Types.GObject DOMStyleSheet

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

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

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveDOMStyleSheetMethod (t :: Symbol) (o :: *) :: * where
    ResolveDOMStyleSheetMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveDOMStyleSheetMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveDOMStyleSheetMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveDOMStyleSheetMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveDOMStyleSheetMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveDOMStyleSheetMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveDOMStyleSheetMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveDOMStyleSheetMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveDOMStyleSheetMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveDOMStyleSheetMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveDOMStyleSheetMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveDOMStyleSheetMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveDOMStyleSheetMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveDOMStyleSheetMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveDOMStyleSheetMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveDOMStyleSheetMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveDOMStyleSheetMethod "getContentType" o = DOMStyleSheetGetContentTypeMethodInfo
    ResolveDOMStyleSheetMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveDOMStyleSheetMethod "getDisabled" o = DOMStyleSheetGetDisabledMethodInfo
    ResolveDOMStyleSheetMethod "getHref" o = DOMStyleSheetGetHrefMethodInfo
    ResolveDOMStyleSheetMethod "getMedia" o = DOMStyleSheetGetMediaMethodInfo
    ResolveDOMStyleSheetMethod "getOwnerNode" o = DOMStyleSheetGetOwnerNodeMethodInfo
    ResolveDOMStyleSheetMethod "getParentStyleSheet" o = DOMStyleSheetGetParentStyleSheetMethodInfo
    ResolveDOMStyleSheetMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveDOMStyleSheetMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveDOMStyleSheetMethod "getTitle" o = DOMStyleSheetGetTitleMethodInfo
    ResolveDOMStyleSheetMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveDOMStyleSheetMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveDOMStyleSheetMethod "setDisabled" o = DOMStyleSheetSetDisabledMethodInfo
    ResolveDOMStyleSheetMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveDOMStyleSheetMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

-- VVV Prop "disabled"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

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

-- | Set the value of the “@disabled@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' dOMStyleSheet [ #disabled 'Data.GI.Base.Attributes.:=' value ]
-- @
setDOMStyleSheetDisabled :: (MonadIO m, IsDOMStyleSheet o) => o -> Bool -> m ()
setDOMStyleSheetDisabled :: forall (m :: * -> *) o.
(MonadIO m, IsDOMStyleSheet o) =>
o -> Bool -> m ()
setDOMStyleSheetDisabled o
obj Bool
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 -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"disabled" Bool
val

-- | Construct a `GValueConstruct` with valid value for the “@disabled@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructDOMStyleSheetDisabled :: (IsDOMStyleSheet o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructDOMStyleSheetDisabled :: forall o (m :: * -> *).
(IsDOMStyleSheet o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructDOMStyleSheetDisabled Bool
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 -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"disabled" Bool
val

#if defined(ENABLE_OVERLOADING)
data DOMStyleSheetDisabledPropertyInfo
instance AttrInfo DOMStyleSheetDisabledPropertyInfo where
    type AttrAllowedOps DOMStyleSheetDisabledPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint DOMStyleSheetDisabledPropertyInfo = IsDOMStyleSheet
    type AttrSetTypeConstraint DOMStyleSheetDisabledPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint DOMStyleSheetDisabledPropertyInfo = (~) Bool
    type AttrTransferType DOMStyleSheetDisabledPropertyInfo = Bool
    type AttrGetType DOMStyleSheetDisabledPropertyInfo = Bool
    type AttrLabel DOMStyleSheetDisabledPropertyInfo = "disabled"
    type AttrOrigin DOMStyleSheetDisabledPropertyInfo = DOMStyleSheet
    attrGet = getDOMStyleSheetDisabled
    attrSet = setDOMStyleSheetDisabled
    attrTransfer _ v = do
        return v
    attrConstruct = constructDOMStyleSheetDisabled
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2WebExtension.Objects.DOMStyleSheet.disabled"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.28/docs/GI-WebKit2WebExtension-Objects-DOMStyleSheet.html#g:attr:disabled"
        })
#endif

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

-- | Get the value of the “@href@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dOMStyleSheet #href
-- @
getDOMStyleSheetHref :: (MonadIO m, IsDOMStyleSheet o) => o -> m (Maybe T.Text)
getDOMStyleSheetHref :: forall (m :: * -> *) o.
(MonadIO m, IsDOMStyleSheet o) =>
o -> m (Maybe Text)
getDOMStyleSheetHref 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
"href"

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

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

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

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

-- VVV Prop "owner-node"
   -- Type: TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMNode"})
   -- Flags: [PropertyReadable]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@owner-node@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dOMStyleSheet #ownerNode
-- @
getDOMStyleSheetOwnerNode :: (MonadIO m, IsDOMStyleSheet o) => o -> m WebKit2WebExtension.DOMNode.DOMNode
getDOMStyleSheetOwnerNode :: forall (m :: * -> *) o.
(MonadIO m, IsDOMStyleSheet o) =>
o -> m DOMNode
getDOMStyleSheetOwnerNode o
obj = IO DOMNode -> m DOMNode
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO DOMNode -> m DOMNode) -> IO DOMNode -> m DOMNode
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe DOMNode) -> IO DOMNode
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getDOMStyleSheetOwnerNode" (IO (Maybe DOMNode) -> IO DOMNode)
-> IO (Maybe DOMNode) -> IO DOMNode
forall a b. (a -> b) -> a -> b
$ o
-> String -> (ManagedPtr DOMNode -> DOMNode) -> IO (Maybe DOMNode)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"owner-node" ManagedPtr DOMNode -> DOMNode
WebKit2WebExtension.DOMNode.DOMNode

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

-- VVV Prop "parent-style-sheet"
   -- Type: TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMStyleSheet"})
   -- 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' dOMStyleSheet #parentStyleSheet
-- @
getDOMStyleSheetParentStyleSheet :: (MonadIO m, IsDOMStyleSheet o) => o -> m (Maybe DOMStyleSheet)
getDOMStyleSheetParentStyleSheet :: forall (m :: * -> *) o.
(MonadIO m, IsDOMStyleSheet o) =>
o -> m (Maybe DOMStyleSheet)
getDOMStyleSheetParentStyleSheet o
obj = IO (Maybe DOMStyleSheet) -> m (Maybe DOMStyleSheet)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe DOMStyleSheet) -> m (Maybe DOMStyleSheet))
-> IO (Maybe DOMStyleSheet) -> m (Maybe DOMStyleSheet)
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr DOMStyleSheet -> DOMStyleSheet)
-> IO (Maybe DOMStyleSheet)
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 DOMStyleSheet -> DOMStyleSheet
DOMStyleSheet

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

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

-- | Get the value of the “@title@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dOMStyleSheet #title
-- @
getDOMStyleSheetTitle :: (MonadIO m, IsDOMStyleSheet o) => o -> m (Maybe T.Text)
getDOMStyleSheetTitle :: forall (m :: * -> *) o.
(MonadIO m, IsDOMStyleSheet o) =>
o -> m (Maybe Text)
getDOMStyleSheetTitle 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
"title"

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

-- VVV Prop "type"
   -- Type: TBasicType TUTF8
   -- 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' dOMStyleSheet #type
-- @
getDOMStyleSheetType :: (MonadIO m, IsDOMStyleSheet o) => o -> m (Maybe T.Text)
getDOMStyleSheetType :: forall (m :: * -> *) o.
(MonadIO m, IsDOMStyleSheet o) =>
o -> m (Maybe Text)
getDOMStyleSheetType 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
"type"

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

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList DOMStyleSheet
type instance O.AttributeList DOMStyleSheet = DOMStyleSheetAttributeList
type DOMStyleSheetAttributeList = ('[ '("coreObject", WebKit2WebExtension.DOMObject.DOMObjectCoreObjectPropertyInfo), '("disabled", DOMStyleSheetDisabledPropertyInfo), '("href", DOMStyleSheetHrefPropertyInfo), '("media", DOMStyleSheetMediaPropertyInfo), '("ownerNode", DOMStyleSheetOwnerNodePropertyInfo), '("parentStyleSheet", DOMStyleSheetParentStyleSheetPropertyInfo), '("title", DOMStyleSheetTitlePropertyInfo), '("type", DOMStyleSheetTypePropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
dOMStyleSheetDisabled :: AttrLabelProxy "disabled"
dOMStyleSheetDisabled = AttrLabelProxy

dOMStyleSheetHref :: AttrLabelProxy "href"
dOMStyleSheetHref = AttrLabelProxy

dOMStyleSheetMedia :: AttrLabelProxy "media"
dOMStyleSheetMedia = AttrLabelProxy

dOMStyleSheetOwnerNode :: AttrLabelProxy "ownerNode"
dOMStyleSheetOwnerNode = AttrLabelProxy

dOMStyleSheetParentStyleSheet :: AttrLabelProxy "parentStyleSheet"
dOMStyleSheetParentStyleSheet = AttrLabelProxy

dOMStyleSheetTitle :: AttrLabelProxy "title"
dOMStyleSheetTitle = AttrLabelProxy

dOMStyleSheetType :: AttrLabelProxy "type"
dOMStyleSheetType = AttrLabelProxy

#endif

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

#endif

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

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

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


#endif

-- method DOMStyleSheet::get_disabled
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit2WebExtension" , name = "DOMStyleSheet" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMStyleSheet"
--                 , 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_style_sheet_get_disabled" webkit_dom_style_sheet_get_disabled :: 
    Ptr DOMStyleSheet ->                    -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMStyleSheet"})
    IO CInt

{-# DEPRECATED dOMStyleSheetGetDisabled ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMStyleSheetGetDisabled ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMStyleSheet a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMStyleSheet.DOMStyleSheet'
    -> m Bool
    -- ^ __Returns:__ A t'P.Bool'
dOMStyleSheetGetDisabled :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDOMStyleSheet a) =>
a -> m Bool
dOMStyleSheetGetDisabled a
self = 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 DOMStyleSheet
self' <- a -> IO (Ptr DOMStyleSheet)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CInt
result <- Ptr DOMStyleSheet -> IO CInt
webkit_dom_style_sheet_get_disabled Ptr DOMStyleSheet
self'
    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
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data DOMStyleSheetGetDisabledMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsDOMStyleSheet a) => O.OverloadedMethod DOMStyleSheetGetDisabledMethodInfo a signature where
    overloadedMethod = dOMStyleSheetGetDisabled

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


#endif

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

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

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


#endif

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

foreign import ccall "webkit_dom_style_sheet_get_media" webkit_dom_style_sheet_get_media :: 
    Ptr DOMStyleSheet ->                    -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMStyleSheet"})
    IO (Ptr WebKit2WebExtension.DOMMediaList.DOMMediaList)

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

#if defined(ENABLE_OVERLOADING)
data DOMStyleSheetGetMediaMethodInfo
instance (signature ~ (m WebKit2WebExtension.DOMMediaList.DOMMediaList), MonadIO m, IsDOMStyleSheet a) => O.OverloadedMethod DOMStyleSheetGetMediaMethodInfo a signature where
    overloadedMethod = dOMStyleSheetGetMedia

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


#endif

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

foreign import ccall "webkit_dom_style_sheet_get_owner_node" webkit_dom_style_sheet_get_owner_node :: 
    Ptr DOMStyleSheet ->                    -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMStyleSheet"})
    IO (Ptr WebKit2WebExtension.DOMNode.DOMNode)

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

#if defined(ENABLE_OVERLOADING)
data DOMStyleSheetGetOwnerNodeMethodInfo
instance (signature ~ (m WebKit2WebExtension.DOMNode.DOMNode), MonadIO m, IsDOMStyleSheet a) => O.OverloadedMethod DOMStyleSheetGetOwnerNodeMethodInfo a signature where
    overloadedMethod = dOMStyleSheetGetOwnerNode

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


#endif

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

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

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

#if defined(ENABLE_OVERLOADING)
data DOMStyleSheetGetParentStyleSheetMethodInfo
instance (signature ~ (m DOMStyleSheet), MonadIO m, IsDOMStyleSheet a) => O.OverloadedMethod DOMStyleSheetGetParentStyleSheetMethodInfo a signature where
    overloadedMethod = dOMStyleSheetGetParentStyleSheet

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


#endif

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

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

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


#endif

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

foreign import ccall "webkit_dom_style_sheet_set_disabled" webkit_dom_style_sheet_set_disabled :: 
    Ptr DOMStyleSheet ->                    -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMStyleSheet"})
    CInt ->                                 -- value : TBasicType TBoolean
    IO ()

{-# DEPRECATED dOMStyleSheetSetDisabled ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMStyleSheetSetDisabled ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMStyleSheet a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMStyleSheet.DOMStyleSheet'
    -> Bool
    -- ^ /@value@/: A t'P.Bool'
    -> m ()
dOMStyleSheetSetDisabled :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDOMStyleSheet a) =>
a -> Bool -> m ()
dOMStyleSheetSetDisabled a
self Bool
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 DOMStyleSheet
self' <- a -> IO (Ptr DOMStyleSheet)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    let value' :: CInt
value' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
value
    Ptr DOMStyleSheet -> CInt -> IO ()
webkit_dom_style_sheet_set_disabled Ptr DOMStyleSheet
self' CInt
value'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DOMStyleSheetSetDisabledMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsDOMStyleSheet a) => O.OverloadedMethod DOMStyleSheetSetDisabledMethodInfo a signature where
    overloadedMethod = dOMStyleSheetSetDisabled

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


#endif