{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.WebKit2WebExtension.Objects.DOMStyleSheet
(
DOMStyleSheet(..) ,
IsDOMStyleSheet ,
toDOMStyleSheet ,
#if defined(ENABLE_OVERLOADING)
ResolveDOMStyleSheetMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
DOMStyleSheetGetContentTypeMethodInfo ,
#endif
dOMStyleSheetGetContentType ,
#if defined(ENABLE_OVERLOADING)
DOMStyleSheetGetDisabledMethodInfo ,
#endif
dOMStyleSheetGetDisabled ,
#if defined(ENABLE_OVERLOADING)
DOMStyleSheetGetHrefMethodInfo ,
#endif
dOMStyleSheetGetHref ,
#if defined(ENABLE_OVERLOADING)
DOMStyleSheetGetMediaMethodInfo ,
#endif
dOMStyleSheetGetMedia ,
#if defined(ENABLE_OVERLOADING)
DOMStyleSheetGetOwnerNodeMethodInfo ,
#endif
dOMStyleSheetGetOwnerNode ,
#if defined(ENABLE_OVERLOADING)
DOMStyleSheetGetParentStyleSheetMethodInfo,
#endif
dOMStyleSheetGetParentStyleSheet ,
#if defined(ENABLE_OVERLOADING)
DOMStyleSheetGetTitleMethodInfo ,
#endif
dOMStyleSheetGetTitle ,
#if defined(ENABLE_OVERLOADING)
DOMStyleSheetSetDisabledMethodInfo ,
#endif
dOMStyleSheetSetDisabled ,
#if defined(ENABLE_OVERLOADING)
DOMStyleSheetDisabledPropertyInfo ,
#endif
constructDOMStyleSheetDisabled ,
#if defined(ENABLE_OVERLOADING)
dOMStyleSheetDisabled ,
#endif
getDOMStyleSheetDisabled ,
setDOMStyleSheetDisabled ,
#if defined(ENABLE_OVERLOADING)
DOMStyleSheetHrefPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
dOMStyleSheetHref ,
#endif
getDOMStyleSheetHref ,
#if defined(ENABLE_OVERLOADING)
DOMStyleSheetMediaPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
dOMStyleSheetMedia ,
#endif
getDOMStyleSheetMedia ,
#if defined(ENABLE_OVERLOADING)
DOMStyleSheetOwnerNodePropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
dOMStyleSheetOwnerNode ,
#endif
getDOMStyleSheetOwnerNode ,
#if defined(ENABLE_OVERLOADING)
DOMStyleSheetParentStyleSheetPropertyInfo,
#endif
#if defined(ENABLE_OVERLOADING)
dOMStyleSheetParentStyleSheet ,
#endif
getDOMStyleSheetParentStyleSheet ,
#if defined(ENABLE_OVERLOADING)
DOMStyleSheetTitlePropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
dOMStyleSheetTitle ,
#endif
getDOMStyleSheetTitle ,
#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.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMMediaList as WebKit2WebExtension.DOMMediaList
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMNode as WebKit2WebExtension.DOMNode
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMObject as WebKit2WebExtension.DOMObject
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
/= :: DOMStyleSheet -> DOMStyleSheet -> Bool
$c/= :: DOMStyleSheet -> DOMStyleSheet -> Bool
== :: DOMStyleSheet -> DOMStyleSheet -> Bool
$c== :: 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
instance B.GValue.IsGValue DOMStyleSheet where
toGValue :: DOMStyleSheet -> IO GValue
toGValue DOMStyleSheet
o = do
GType
gtype <- IO GType
c_webkit_dom_style_sheet_get_type
DOMStyleSheet -> (Ptr DOMStyleSheet -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr DOMStyleSheet
o (GType
-> (GValue -> Ptr DOMStyleSheet -> IO ())
-> Ptr DOMStyleSheet
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr DOMStyleSheet -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
fromGValue :: GValue -> IO DOMStyleSheet
fromGValue GValue
gv = do
Ptr DOMStyleSheet
ptr <- GValue -> IO (Ptr DOMStyleSheet)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr DOMStyleSheet)
(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
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]
toDOMStyleSheet :: (MonadIO m, IsDOMStyleSheet o) => o -> m DOMStyleSheet
toDOMStyleSheet :: o -> m DOMStyleSheet
toDOMStyleSheet = IO DOMStyleSheet -> m DOMStyleSheet
forall (m :: * -> *) a. MonadIO m => IO a -> m a
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'
unsafeCastTo ManagedPtr DOMStyleSheet -> DOMStyleSheet
DOMStyleSheet
#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.MethodInfo 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
#endif
getDOMStyleSheetDisabled :: (MonadIO m, IsDOMStyleSheet o) => o -> m Bool
getDOMStyleSheetDisabled :: o -> m Bool
getDOMStyleSheetDisabled o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"disabled"
setDOMStyleSheetDisabled :: (MonadIO m, IsDOMStyleSheet o) => o -> Bool -> m ()
setDOMStyleSheetDisabled :: o -> Bool -> m ()
setDOMStyleSheetDisabled o
obj Bool
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"disabled" Bool
val
constructDOMStyleSheetDisabled :: (IsDOMStyleSheet o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructDOMStyleSheetDisabled :: Bool -> m (GValueConstruct o)
constructDOMStyleSheetDisabled Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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
$ 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
#endif
getDOMStyleSheetHref :: (MonadIO m, IsDOMStyleSheet o) => o -> m (Maybe T.Text)
getDOMStyleSheetHref :: o -> m (Maybe Text)
getDOMStyleSheetHref o
obj = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj 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
#endif
getDOMStyleSheetMedia :: (MonadIO m, IsDOMStyleSheet o) => o -> m (Maybe WebKit2WebExtension.DOMMediaList.DOMMediaList)
getDOMStyleSheetMedia :: o -> m (Maybe DOMMediaList)
getDOMStyleSheetMedia o
obj = IO (Maybe DOMMediaList) -> m (Maybe DOMMediaList)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
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
#endif
getDOMStyleSheetOwnerNode :: (MonadIO m, IsDOMStyleSheet o) => o -> m WebKit2WebExtension.DOMNode.DOMNode
getDOMStyleSheetOwnerNode :: o -> m DOMNode
getDOMStyleSheetOwnerNode o
obj = IO DOMNode -> m DOMNode
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
$ 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
#endif
getDOMStyleSheetParentStyleSheet :: (MonadIO m, IsDOMStyleSheet o) => o -> m (Maybe DOMStyleSheet)
getDOMStyleSheetParentStyleSheet :: o -> m (Maybe DOMStyleSheet)
getDOMStyleSheetParentStyleSheet o
obj = IO (Maybe DOMStyleSheet) -> m (Maybe DOMStyleSheet)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
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
#endif
getDOMStyleSheetTitle :: (MonadIO m, IsDOMStyleSheet o) => o -> m (Maybe T.Text)
getDOMStyleSheetTitle :: o -> m (Maybe Text)
getDOMStyleSheetTitle o
obj = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj 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
#endif
getDOMStyleSheetType :: (MonadIO m, IsDOMStyleSheet o) => o -> m (Maybe T.Text)
getDOMStyleSheetType :: o -> m (Maybe Text)
getDOMStyleSheetType o
obj = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj 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
#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
foreign import ccall "webkit_dom_style_sheet_get_content_type" webkit_dom_style_sheet_get_content_type ::
Ptr DOMStyleSheet ->
IO CString
{-# DEPRECATED dOMStyleSheetGetContentType ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
dOMStyleSheetGetContentType ::
(B.CallStack.HasCallStack, MonadIO m, IsDOMStyleSheet a) =>
a
-> m T.Text
dOMStyleSheetGetContentType :: a -> m Text
dOMStyleSheetGetContentType a
self = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
Ptr 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 (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.MethodInfo DOMStyleSheetGetContentTypeMethodInfo a signature where
overloadedMethod = dOMStyleSheetGetContentType
#endif
foreign import ccall "webkit_dom_style_sheet_get_disabled" webkit_dom_style_sheet_get_disabled ::
Ptr DOMStyleSheet ->
IO CInt
{-# DEPRECATED dOMStyleSheetGetDisabled ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
dOMStyleSheetGetDisabled ::
(B.CallStack.HasCallStack, MonadIO m, IsDOMStyleSheet a) =>
a
-> m Bool
dOMStyleSheetGetDisabled :: a -> m Bool
dOMStyleSheetGetDisabled a
self = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
Ptr 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 (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.MethodInfo DOMStyleSheetGetDisabledMethodInfo a signature where
overloadedMethod = dOMStyleSheetGetDisabled
#endif
foreign import ccall "webkit_dom_style_sheet_get_href" webkit_dom_style_sheet_get_href ::
Ptr DOMStyleSheet ->
IO CString
{-# DEPRECATED dOMStyleSheetGetHref ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
dOMStyleSheetGetHref ::
(B.CallStack.HasCallStack, MonadIO m, IsDOMStyleSheet a) =>
a
-> m T.Text
dOMStyleSheetGetHref :: a -> m Text
dOMStyleSheetGetHref a
self = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
Ptr 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 (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.MethodInfo DOMStyleSheetGetHrefMethodInfo a signature where
overloadedMethod = dOMStyleSheetGetHref
#endif
foreign import ccall "webkit_dom_style_sheet_get_media" webkit_dom_style_sheet_get_media ::
Ptr DOMStyleSheet ->
IO (Ptr WebKit2WebExtension.DOMMediaList.DOMMediaList)
{-# DEPRECATED dOMStyleSheetGetMedia ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
dOMStyleSheetGetMedia ::
(B.CallStack.HasCallStack, MonadIO m, IsDOMStyleSheet a) =>
a
-> m WebKit2WebExtension.DOMMediaList.DOMMediaList
dOMStyleSheetGetMedia :: a -> m DOMMediaList
dOMStyleSheetGetMedia a
self = IO DOMMediaList -> m DOMMediaList
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 (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.MethodInfo DOMStyleSheetGetMediaMethodInfo a signature where
overloadedMethod = dOMStyleSheetGetMedia
#endif
foreign import ccall "webkit_dom_style_sheet_get_owner_node" webkit_dom_style_sheet_get_owner_node ::
Ptr DOMStyleSheet ->
IO (Ptr WebKit2WebExtension.DOMNode.DOMNode)
{-# DEPRECATED dOMStyleSheetGetOwnerNode ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
dOMStyleSheetGetOwnerNode ::
(B.CallStack.HasCallStack, MonadIO m, IsDOMStyleSheet a) =>
a
-> m WebKit2WebExtension.DOMNode.DOMNode
dOMStyleSheetGetOwnerNode :: a -> m DOMNode
dOMStyleSheetGetOwnerNode a
self = IO DOMNode -> m DOMNode
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 (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.MethodInfo DOMStyleSheetGetOwnerNodeMethodInfo a signature where
overloadedMethod = dOMStyleSheetGetOwnerNode
#endif
foreign import ccall "webkit_dom_style_sheet_get_parent_style_sheet" webkit_dom_style_sheet_get_parent_style_sheet ::
Ptr DOMStyleSheet ->
IO (Ptr DOMStyleSheet)
{-# DEPRECATED dOMStyleSheetGetParentStyleSheet ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
dOMStyleSheetGetParentStyleSheet ::
(B.CallStack.HasCallStack, MonadIO m, IsDOMStyleSheet a) =>
a
-> m DOMStyleSheet
dOMStyleSheetGetParentStyleSheet :: a -> m DOMStyleSheet
dOMStyleSheetGetParentStyleSheet a
self = IO DOMStyleSheet -> m DOMStyleSheet
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 (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.MethodInfo DOMStyleSheetGetParentStyleSheetMethodInfo a signature where
overloadedMethod = dOMStyleSheetGetParentStyleSheet
#endif
foreign import ccall "webkit_dom_style_sheet_get_title" webkit_dom_style_sheet_get_title ::
Ptr DOMStyleSheet ->
IO CString
{-# DEPRECATED dOMStyleSheetGetTitle ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
dOMStyleSheetGetTitle ::
(B.CallStack.HasCallStack, MonadIO m, IsDOMStyleSheet a) =>
a
-> m T.Text
dOMStyleSheetGetTitle :: a -> m Text
dOMStyleSheetGetTitle a
self = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
Ptr 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 (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.MethodInfo DOMStyleSheetGetTitleMethodInfo a signature where
overloadedMethod = dOMStyleSheetGetTitle
#endif
foreign import ccall "webkit_dom_style_sheet_set_disabled" webkit_dom_style_sheet_set_disabled ::
Ptr DOMStyleSheet ->
CInt ->
IO ()
{-# DEPRECATED dOMStyleSheetSetDisabled ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
dOMStyleSheetSetDisabled ::
(B.CallStack.HasCallStack, MonadIO m, IsDOMStyleSheet a) =>
a
-> Bool
-> m ()
dOMStyleSheetSetDisabled :: a -> Bool -> m ()
dOMStyleSheetSetDisabled a
self Bool
value = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr 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 (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data DOMStyleSheetSetDisabledMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsDOMStyleSheet a) => O.MethodInfo DOMStyleSheetSetDisabledMethodInfo a signature where
overloadedMethod = dOMStyleSheetSetDisabled
#endif