{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- 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.DOMHTMLOptionsCollection
    ( 

-- * Exported types
    DOMHTMLOptionsCollection(..)            ,
    IsDOMHTMLOptionsCollection              ,
    toDOMHTMLOptionsCollection              ,
    noDOMHTMLOptionsCollection              ,


 -- * Methods
-- ** Overloaded methods #method:Overloaded methods#

#if defined(ENABLE_OVERLOADING)
    ResolveDOMHTMLOptionsCollectionMethod   ,
#endif


-- ** getLength #method:getLength#

#if defined(ENABLE_OVERLOADING)
    DOMHTMLOptionsCollectionGetLengthMethodInfo,
#endif
    dOMHTMLOptionsCollectionGetLength       ,


-- ** getSelectedIndex #method:getSelectedIndex#

#if defined(ENABLE_OVERLOADING)
    DOMHTMLOptionsCollectionGetSelectedIndexMethodInfo,
#endif
    dOMHTMLOptionsCollectionGetSelectedIndex,


-- ** namedItem #method:namedItem#

#if defined(ENABLE_OVERLOADING)
    DOMHTMLOptionsCollectionNamedItemMethodInfo,
#endif
    dOMHTMLOptionsCollectionNamedItem       ,


-- ** setSelectedIndex #method:setSelectedIndex#

#if defined(ENABLE_OVERLOADING)
    DOMHTMLOptionsCollectionSetSelectedIndexMethodInfo,
#endif
    dOMHTMLOptionsCollectionSetSelectedIndex,




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

#if defined(ENABLE_OVERLOADING)
    DOMHTMLOptionsCollectionLengthPropertyInfo,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMHTMLOptionsCollectionLength          ,
#endif
    getDOMHTMLOptionsCollectionLength       ,


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

#if defined(ENABLE_OVERLOADING)
    DOMHTMLOptionsCollectionSelectedIndexPropertyInfo,
#endif
    constructDOMHTMLOptionsCollectionSelectedIndex,
#if defined(ENABLE_OVERLOADING)
    dOMHTMLOptionsCollectionSelectedIndex   ,
#endif
    getDOMHTMLOptionsCollectionSelectedIndex,
    setDOMHTMLOptionsCollectionSelectedIndex,




    ) where

import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL

import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMHTMLCollection as WebKit2WebExtension.DOMHTMLCollection
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 DOMHTMLOptionsCollection = DOMHTMLOptionsCollection (ManagedPtr DOMHTMLOptionsCollection)
    deriving (DOMHTMLOptionsCollection -> DOMHTMLOptionsCollection -> Bool
(DOMHTMLOptionsCollection -> DOMHTMLOptionsCollection -> Bool)
-> (DOMHTMLOptionsCollection -> DOMHTMLOptionsCollection -> Bool)
-> Eq DOMHTMLOptionsCollection
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DOMHTMLOptionsCollection -> DOMHTMLOptionsCollection -> Bool
$c/= :: DOMHTMLOptionsCollection -> DOMHTMLOptionsCollection -> Bool
== :: DOMHTMLOptionsCollection -> DOMHTMLOptionsCollection -> Bool
$c== :: DOMHTMLOptionsCollection -> DOMHTMLOptionsCollection -> Bool
Eq)
foreign import ccall "webkit_dom_html_options_collection_get_type"
    c_webkit_dom_html_options_collection_get_type :: IO GType

instance GObject DOMHTMLOptionsCollection where
    gobjectType :: IO GType
gobjectType = IO GType
c_webkit_dom_html_options_collection_get_type
    

-- | Convert 'DOMHTMLOptionsCollection' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue DOMHTMLOptionsCollection where
    toGValue :: DOMHTMLOptionsCollection -> IO GValue
toGValue o :: DOMHTMLOptionsCollection
o = do
        GType
gtype <- IO GType
c_webkit_dom_html_options_collection_get_type
        DOMHTMLOptionsCollection
-> (Ptr DOMHTMLOptionsCollection -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr DOMHTMLOptionsCollection
o (GType
-> (GValue -> Ptr DOMHTMLOptionsCollection -> IO ())
-> Ptr DOMHTMLOptionsCollection
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr DOMHTMLOptionsCollection -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
        
    fromGValue :: GValue -> IO DOMHTMLOptionsCollection
fromGValue gv :: GValue
gv = do
        Ptr DOMHTMLOptionsCollection
ptr <- GValue -> IO (Ptr DOMHTMLOptionsCollection)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr DOMHTMLOptionsCollection)
        (ManagedPtr DOMHTMLOptionsCollection -> DOMHTMLOptionsCollection)
-> Ptr DOMHTMLOptionsCollection -> IO DOMHTMLOptionsCollection
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr DOMHTMLOptionsCollection -> DOMHTMLOptionsCollection
DOMHTMLOptionsCollection Ptr DOMHTMLOptionsCollection
ptr
        
    

-- | Type class for types which can be safely cast to `DOMHTMLOptionsCollection`, for instance with `toDOMHTMLOptionsCollection`.
class (GObject o, O.IsDescendantOf DOMHTMLOptionsCollection o) => IsDOMHTMLOptionsCollection o
instance (GObject o, O.IsDescendantOf DOMHTMLOptionsCollection o) => IsDOMHTMLOptionsCollection o

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

-- | Cast to `DOMHTMLOptionsCollection`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toDOMHTMLOptionsCollection :: (MonadIO m, IsDOMHTMLOptionsCollection o) => o -> m DOMHTMLOptionsCollection
toDOMHTMLOptionsCollection :: o -> m DOMHTMLOptionsCollection
toDOMHTMLOptionsCollection = IO DOMHTMLOptionsCollection -> m DOMHTMLOptionsCollection
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DOMHTMLOptionsCollection -> m DOMHTMLOptionsCollection)
-> (o -> IO DOMHTMLOptionsCollection)
-> o
-> m DOMHTMLOptionsCollection
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr DOMHTMLOptionsCollection -> DOMHTMLOptionsCollection)
-> o -> IO DOMHTMLOptionsCollection
forall o o'.
(HasCallStack, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr DOMHTMLOptionsCollection -> DOMHTMLOptionsCollection
DOMHTMLOptionsCollection

-- | A convenience alias for `Nothing` :: `Maybe` `DOMHTMLOptionsCollection`.
noDOMHTMLOptionsCollection :: Maybe DOMHTMLOptionsCollection
noDOMHTMLOptionsCollection :: Maybe DOMHTMLOptionsCollection
noDOMHTMLOptionsCollection = Maybe DOMHTMLOptionsCollection
forall a. Maybe a
Nothing

#if defined(ENABLE_OVERLOADING)
type family ResolveDOMHTMLOptionsCollectionMethod (t :: Symbol) (o :: *) :: * where
    ResolveDOMHTMLOptionsCollectionMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveDOMHTMLOptionsCollectionMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveDOMHTMLOptionsCollectionMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveDOMHTMLOptionsCollectionMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveDOMHTMLOptionsCollectionMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveDOMHTMLOptionsCollectionMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveDOMHTMLOptionsCollectionMethod "item" o = WebKit2WebExtension.DOMHTMLCollection.DOMHTMLCollectionItemMethodInfo
    ResolveDOMHTMLOptionsCollectionMethod "namedItem" o = DOMHTMLOptionsCollectionNamedItemMethodInfo
    ResolveDOMHTMLOptionsCollectionMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveDOMHTMLOptionsCollectionMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveDOMHTMLOptionsCollectionMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveDOMHTMLOptionsCollectionMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveDOMHTMLOptionsCollectionMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveDOMHTMLOptionsCollectionMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveDOMHTMLOptionsCollectionMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveDOMHTMLOptionsCollectionMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveDOMHTMLOptionsCollectionMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveDOMHTMLOptionsCollectionMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveDOMHTMLOptionsCollectionMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveDOMHTMLOptionsCollectionMethod "getLength" o = DOMHTMLOptionsCollectionGetLengthMethodInfo
    ResolveDOMHTMLOptionsCollectionMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveDOMHTMLOptionsCollectionMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveDOMHTMLOptionsCollectionMethod "getSelectedIndex" o = DOMHTMLOptionsCollectionGetSelectedIndexMethodInfo
    ResolveDOMHTMLOptionsCollectionMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveDOMHTMLOptionsCollectionMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveDOMHTMLOptionsCollectionMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveDOMHTMLOptionsCollectionMethod "setSelectedIndex" o = DOMHTMLOptionsCollectionSetSelectedIndexMethodInfo
    ResolveDOMHTMLOptionsCollectionMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveDOMHTMLOptionsCollectionMethod t DOMHTMLOptionsCollection, O.MethodInfo info DOMHTMLOptionsCollection p) => OL.IsLabel t (DOMHTMLOptionsCollection -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#endif

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

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

#if defined(ENABLE_OVERLOADING)
data DOMHTMLOptionsCollectionLengthPropertyInfo
instance AttrInfo DOMHTMLOptionsCollectionLengthPropertyInfo where
    type AttrAllowedOps DOMHTMLOptionsCollectionLengthPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint DOMHTMLOptionsCollectionLengthPropertyInfo = IsDOMHTMLOptionsCollection
    type AttrSetTypeConstraint DOMHTMLOptionsCollectionLengthPropertyInfo = (~) ()
    type AttrTransferTypeConstraint DOMHTMLOptionsCollectionLengthPropertyInfo = (~) ()
    type AttrTransferType DOMHTMLOptionsCollectionLengthPropertyInfo = ()
    type AttrGetType DOMHTMLOptionsCollectionLengthPropertyInfo = CULong
    type AttrLabel DOMHTMLOptionsCollectionLengthPropertyInfo = "length"
    type AttrOrigin DOMHTMLOptionsCollectionLengthPropertyInfo = DOMHTMLOptionsCollection
    attrGet = getDOMHTMLOptionsCollectionLength
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

-- VVV Prop "selected-index"
   -- Type: TBasicType TLong
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@selected-index@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dOMHTMLOptionsCollection #selectedIndex
-- @
getDOMHTMLOptionsCollectionSelectedIndex :: (MonadIO m, IsDOMHTMLOptionsCollection o) => o -> m CLong
getDOMHTMLOptionsCollectionSelectedIndex :: o -> m CLong
getDOMHTMLOptionsCollectionSelectedIndex obj :: o
obj = IO CLong -> m CLong
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CLong -> m CLong) -> IO CLong -> m CLong
forall a b. (a -> b) -> a -> b
$ o -> String -> IO CLong
forall a. GObject a => a -> String -> IO CLong
B.Properties.getObjectPropertyLong o
obj "selected-index"

-- | Set the value of the “@selected-index@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' dOMHTMLOptionsCollection [ #selectedIndex 'Data.GI.Base.Attributes.:=' value ]
-- @
setDOMHTMLOptionsCollectionSelectedIndex :: (MonadIO m, IsDOMHTMLOptionsCollection o) => o -> CLong -> m ()
setDOMHTMLOptionsCollectionSelectedIndex :: o -> CLong -> m ()
setDOMHTMLOptionsCollectionSelectedIndex obj :: o
obj val :: CLong
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 -> CLong -> IO ()
forall a. GObject a => a -> String -> CLong -> IO ()
B.Properties.setObjectPropertyLong o
obj "selected-index" CLong
val

-- | Construct a `GValueConstruct` with valid value for the “@selected-index@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructDOMHTMLOptionsCollectionSelectedIndex :: (IsDOMHTMLOptionsCollection o) => CLong -> IO (GValueConstruct o)
constructDOMHTMLOptionsCollectionSelectedIndex :: CLong -> IO (GValueConstruct o)
constructDOMHTMLOptionsCollectionSelectedIndex val :: CLong
val = String -> CLong -> IO (GValueConstruct o)
forall o. String -> CLong -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyLong "selected-index" CLong
val

#if defined(ENABLE_OVERLOADING)
data DOMHTMLOptionsCollectionSelectedIndexPropertyInfo
instance AttrInfo DOMHTMLOptionsCollectionSelectedIndexPropertyInfo where
    type AttrAllowedOps DOMHTMLOptionsCollectionSelectedIndexPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint DOMHTMLOptionsCollectionSelectedIndexPropertyInfo = IsDOMHTMLOptionsCollection
    type AttrSetTypeConstraint DOMHTMLOptionsCollectionSelectedIndexPropertyInfo = (~) CLong
    type AttrTransferTypeConstraint DOMHTMLOptionsCollectionSelectedIndexPropertyInfo = (~) CLong
    type AttrTransferType DOMHTMLOptionsCollectionSelectedIndexPropertyInfo = CLong
    type AttrGetType DOMHTMLOptionsCollectionSelectedIndexPropertyInfo = CLong
    type AttrLabel DOMHTMLOptionsCollectionSelectedIndexPropertyInfo = "selected-index"
    type AttrOrigin DOMHTMLOptionsCollectionSelectedIndexPropertyInfo = DOMHTMLOptionsCollection
    attrGet = getDOMHTMLOptionsCollectionSelectedIndex
    attrSet = setDOMHTMLOptionsCollectionSelectedIndex
    attrTransfer _ v = do
        return v
    attrConstruct = constructDOMHTMLOptionsCollectionSelectedIndex
    attrClear = undefined
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList DOMHTMLOptionsCollection
type instance O.AttributeList DOMHTMLOptionsCollection = DOMHTMLOptionsCollectionAttributeList
type DOMHTMLOptionsCollectionAttributeList = ('[ '("coreObject", WebKit2WebExtension.DOMObject.DOMObjectCoreObjectPropertyInfo), '("length", DOMHTMLOptionsCollectionLengthPropertyInfo), '("selectedIndex", DOMHTMLOptionsCollectionSelectedIndexPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
dOMHTMLOptionsCollectionLength :: AttrLabelProxy "length"
dOMHTMLOptionsCollectionLength = AttrLabelProxy

dOMHTMLOptionsCollectionSelectedIndex :: AttrLabelProxy "selectedIndex"
dOMHTMLOptionsCollectionSelectedIndex = AttrLabelProxy

#endif

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

#endif

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

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

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

#if defined(ENABLE_OVERLOADING)
data DOMHTMLOptionsCollectionGetLengthMethodInfo
instance (signature ~ (m CULong), MonadIO m, IsDOMHTMLOptionsCollection a) => O.MethodInfo DOMHTMLOptionsCollectionGetLengthMethodInfo a signature where
    overloadedMethod = dOMHTMLOptionsCollectionGetLength

#endif

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

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

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

#if defined(ENABLE_OVERLOADING)
data DOMHTMLOptionsCollectionGetSelectedIndexMethodInfo
instance (signature ~ (m CLong), MonadIO m, IsDOMHTMLOptionsCollection a) => O.MethodInfo DOMHTMLOptionsCollectionGetSelectedIndexMethodInfo a signature where
    overloadedMethod = dOMHTMLOptionsCollectionGetSelectedIndex

#endif

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

foreign import ccall "webkit_dom_html_options_collection_named_item" webkit_dom_html_options_collection_named_item :: 
    Ptr DOMHTMLOptionsCollection ->         -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMHTMLOptionsCollection"})
    CString ->                              -- name : TBasicType TUTF8
    IO (Ptr WebKit2WebExtension.DOMNode.DOMNode)

{-# DEPRECATED dOMHTMLOptionsCollectionNamedItem ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMHTMLOptionsCollectionNamedItem ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMHTMLOptionsCollection a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMHTMLOptionsCollection.DOMHTMLOptionsCollection'
    -> T.Text
    -- ^ /@name@/: A @/gchar/@
    -> m WebKit2WebExtension.DOMNode.DOMNode
    -- ^ __Returns:__ A t'GI.WebKit2WebExtension.Objects.DOMNode.DOMNode'
dOMHTMLOptionsCollectionNamedItem :: a -> Text -> m DOMNode
dOMHTMLOptionsCollectionNamedItem self :: a
self name :: Text
name = 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 DOMHTMLOptionsCollection
self' <- a -> IO (Ptr DOMHTMLOptionsCollection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
name' <- Text -> IO CString
textToCString Text
name
    Ptr DOMNode
result <- Ptr DOMHTMLOptionsCollection -> CString -> IO (Ptr DOMNode)
webkit_dom_html_options_collection_named_item Ptr DOMHTMLOptionsCollection
self' CString
name'
    Text -> Ptr DOMNode -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dOMHTMLOptionsCollectionNamedItem" 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
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
    DOMNode -> IO DOMNode
forall (m :: * -> *) a. Monad m => a -> m a
return DOMNode
result'

#if defined(ENABLE_OVERLOADING)
data DOMHTMLOptionsCollectionNamedItemMethodInfo
instance (signature ~ (T.Text -> m WebKit2WebExtension.DOMNode.DOMNode), MonadIO m, IsDOMHTMLOptionsCollection a) => O.MethodInfo DOMHTMLOptionsCollectionNamedItemMethodInfo a signature where
    overloadedMethod = dOMHTMLOptionsCollectionNamedItem

#endif

-- method DOMHTMLOptionsCollection::set_selected_index
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name
--                   { namespace = "WebKit2WebExtension"
--                   , name = "DOMHTMLOptionsCollection"
--                   }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMHTMLOptionsCollection"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TBasicType TLong
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #glong" , 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_html_options_collection_set_selected_index" webkit_dom_html_options_collection_set_selected_index :: 
    Ptr DOMHTMLOptionsCollection ->         -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMHTMLOptionsCollection"})
    CLong ->                                -- value : TBasicType TLong
    IO ()

{-# DEPRECATED dOMHTMLOptionsCollectionSetSelectedIndex ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMHTMLOptionsCollectionSetSelectedIndex ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMHTMLOptionsCollection a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMHTMLOptionsCollection.DOMHTMLOptionsCollection'
    -> CLong
    -- ^ /@value@/: A @/glong/@
    -> m ()
dOMHTMLOptionsCollectionSetSelectedIndex :: a -> CLong -> m ()
dOMHTMLOptionsCollectionSetSelectedIndex self :: a
self value :: CLong
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 DOMHTMLOptionsCollection
self' <- a -> IO (Ptr DOMHTMLOptionsCollection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr DOMHTMLOptionsCollection -> CLong -> IO ()
webkit_dom_html_options_collection_set_selected_index Ptr DOMHTMLOptionsCollection
self' CLong
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 DOMHTMLOptionsCollectionSetSelectedIndexMethodInfo
instance (signature ~ (CLong -> m ()), MonadIO m, IsDOMHTMLOptionsCollection a) => O.MethodInfo DOMHTMLOptionsCollectionSetSelectedIndexMethodInfo a signature where
    overloadedMethod = dOMHTMLOptionsCollectionSetSelectedIndex

#endif