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

-- * Exported types
    DOMXPathResult(..)                      ,
    IsDOMXPathResult                        ,
    toDOMXPathResult                        ,


 -- * 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"), [iterateNext]("GI.WebKit2WebExtension.Objects.DOMXPathResult#g:method:iterateNext"), [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"), [snapshotItem]("GI.WebKit2WebExtension.Objects.DOMXPathResult#g:method:snapshotItem"), [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
-- [getBooleanValue]("GI.WebKit2WebExtension.Objects.DOMXPathResult#g:method:getBooleanValue"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getInvalidIteratorState]("GI.WebKit2WebExtension.Objects.DOMXPathResult#g:method:getInvalidIteratorState"), [getNumberValue]("GI.WebKit2WebExtension.Objects.DOMXPathResult#g:method:getNumberValue"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getResultType]("GI.WebKit2WebExtension.Objects.DOMXPathResult#g:method:getResultType"), [getSingleNodeValue]("GI.WebKit2WebExtension.Objects.DOMXPathResult#g:method:getSingleNodeValue"), [getSnapshotLength]("GI.WebKit2WebExtension.Objects.DOMXPathResult#g:method:getSnapshotLength"), [getStringValue]("GI.WebKit2WebExtension.Objects.DOMXPathResult#g:method:getStringValue").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolveDOMXPathResultMethod             ,
#endif

-- ** getBooleanValue #method:getBooleanValue#

#if defined(ENABLE_OVERLOADING)
    DOMXPathResultGetBooleanValueMethodInfo ,
#endif
    dOMXPathResultGetBooleanValue           ,


-- ** getInvalidIteratorState #method:getInvalidIteratorState#

#if defined(ENABLE_OVERLOADING)
    DOMXPathResultGetInvalidIteratorStateMethodInfo,
#endif
    dOMXPathResultGetInvalidIteratorState   ,


-- ** getNumberValue #method:getNumberValue#

#if defined(ENABLE_OVERLOADING)
    DOMXPathResultGetNumberValueMethodInfo  ,
#endif
    dOMXPathResultGetNumberValue            ,


-- ** getResultType #method:getResultType#

#if defined(ENABLE_OVERLOADING)
    DOMXPathResultGetResultTypeMethodInfo   ,
#endif
    dOMXPathResultGetResultType             ,


-- ** getSingleNodeValue #method:getSingleNodeValue#

#if defined(ENABLE_OVERLOADING)
    DOMXPathResultGetSingleNodeValueMethodInfo,
#endif
    dOMXPathResultGetSingleNodeValue        ,


-- ** getSnapshotLength #method:getSnapshotLength#

#if defined(ENABLE_OVERLOADING)
    DOMXPathResultGetSnapshotLengthMethodInfo,
#endif
    dOMXPathResultGetSnapshotLength         ,


-- ** getStringValue #method:getStringValue#

#if defined(ENABLE_OVERLOADING)
    DOMXPathResultGetStringValueMethodInfo  ,
#endif
    dOMXPathResultGetStringValue            ,


-- ** iterateNext #method:iterateNext#

#if defined(ENABLE_OVERLOADING)
    DOMXPathResultIterateNextMethodInfo     ,
#endif
    dOMXPathResultIterateNext               ,


-- ** snapshotItem #method:snapshotItem#

#if defined(ENABLE_OVERLOADING)
    DOMXPathResultSnapshotItemMethodInfo    ,
#endif
    dOMXPathResultSnapshotItem              ,




 -- * Properties


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

#if defined(ENABLE_OVERLOADING)
    DOMXPathResultBooleanValuePropertyInfo  ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMXPathResultBooleanValue              ,
#endif
    getDOMXPathResultBooleanValue           ,


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

#if defined(ENABLE_OVERLOADING)
    DOMXPathResultInvalidIteratorStatePropertyInfo,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMXPathResultInvalidIteratorState      ,
#endif
    getDOMXPathResultInvalidIteratorState   ,


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

#if defined(ENABLE_OVERLOADING)
    DOMXPathResultNumberValuePropertyInfo   ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMXPathResultNumberValue               ,
#endif
    getDOMXPathResultNumberValue            ,


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

#if defined(ENABLE_OVERLOADING)
    DOMXPathResultResultTypePropertyInfo    ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMXPathResultResultType                ,
#endif
    getDOMXPathResultResultType             ,


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

#if defined(ENABLE_OVERLOADING)
    DOMXPathResultSingleNodeValuePropertyInfo,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMXPathResultSingleNodeValue           ,
#endif
    getDOMXPathResultSingleNodeValue        ,


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

#if defined(ENABLE_OVERLOADING)
    DOMXPathResultSnapshotLengthPropertyInfo,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMXPathResultSnapshotLength            ,
#endif
    getDOMXPathResultSnapshotLength         ,


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

#if defined(ENABLE_OVERLOADING)
    DOMXPathResultStringValuePropertyInfo   ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMXPathResultStringValue               ,
#endif
    getDOMXPathResultStringValue            ,




    ) 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.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 GHC.Records as R

import qualified GI.GObject.Objects.Object as GObject.Object
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 DOMXPathResult = DOMXPathResult (SP.ManagedPtr DOMXPathResult)
    deriving (DOMXPathResult -> DOMXPathResult -> Bool
(DOMXPathResult -> DOMXPathResult -> Bool)
-> (DOMXPathResult -> DOMXPathResult -> Bool) -> Eq DOMXPathResult
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DOMXPathResult -> DOMXPathResult -> Bool
$c/= :: DOMXPathResult -> DOMXPathResult -> Bool
== :: DOMXPathResult -> DOMXPathResult -> Bool
$c== :: DOMXPathResult -> DOMXPathResult -> Bool
Eq)

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

foreign import ccall "webkit_dom_xpath_result_get_type"
    c_webkit_dom_xpath_result_get_type :: IO B.Types.GType

instance B.Types.TypedObject DOMXPathResult where
    glibType :: IO GType
glibType = IO GType
c_webkit_dom_xpath_result_get_type

instance B.Types.GObject DOMXPathResult

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

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

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveDOMXPathResultMethod (t :: Symbol) (o :: *) :: * where
    ResolveDOMXPathResultMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveDOMXPathResultMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveDOMXPathResultMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveDOMXPathResultMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveDOMXPathResultMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveDOMXPathResultMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveDOMXPathResultMethod "iterateNext" o = DOMXPathResultIterateNextMethodInfo
    ResolveDOMXPathResultMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveDOMXPathResultMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveDOMXPathResultMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveDOMXPathResultMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveDOMXPathResultMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveDOMXPathResultMethod "snapshotItem" o = DOMXPathResultSnapshotItemMethodInfo
    ResolveDOMXPathResultMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveDOMXPathResultMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveDOMXPathResultMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveDOMXPathResultMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveDOMXPathResultMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveDOMXPathResultMethod "getBooleanValue" o = DOMXPathResultGetBooleanValueMethodInfo
    ResolveDOMXPathResultMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveDOMXPathResultMethod "getInvalidIteratorState" o = DOMXPathResultGetInvalidIteratorStateMethodInfo
    ResolveDOMXPathResultMethod "getNumberValue" o = DOMXPathResultGetNumberValueMethodInfo
    ResolveDOMXPathResultMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveDOMXPathResultMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveDOMXPathResultMethod "getResultType" o = DOMXPathResultGetResultTypeMethodInfo
    ResolveDOMXPathResultMethod "getSingleNodeValue" o = DOMXPathResultGetSingleNodeValueMethodInfo
    ResolveDOMXPathResultMethod "getSnapshotLength" o = DOMXPathResultGetSnapshotLengthMethodInfo
    ResolveDOMXPathResultMethod "getStringValue" o = DOMXPathResultGetStringValueMethodInfo
    ResolveDOMXPathResultMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveDOMXPathResultMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveDOMXPathResultMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveDOMXPathResultMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

-- VVV Prop "boolean-value"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@boolean-value@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dOMXPathResult #booleanValue
-- @
getDOMXPathResultBooleanValue :: (MonadIO m, IsDOMXPathResult o) => o -> m Bool
getDOMXPathResultBooleanValue :: forall (m :: * -> *) o.
(MonadIO m, IsDOMXPathResult o) =>
o -> m Bool
getDOMXPathResultBooleanValue o
obj = IO Bool -> m Bool
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
"boolean-value"

#if defined(ENABLE_OVERLOADING)
data DOMXPathResultBooleanValuePropertyInfo
instance AttrInfo DOMXPathResultBooleanValuePropertyInfo where
    type AttrAllowedOps DOMXPathResultBooleanValuePropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint DOMXPathResultBooleanValuePropertyInfo = IsDOMXPathResult
    type AttrSetTypeConstraint DOMXPathResultBooleanValuePropertyInfo = (~) ()
    type AttrTransferTypeConstraint DOMXPathResultBooleanValuePropertyInfo = (~) ()
    type AttrTransferType DOMXPathResultBooleanValuePropertyInfo = ()
    type AttrGetType DOMXPathResultBooleanValuePropertyInfo = Bool
    type AttrLabel DOMXPathResultBooleanValuePropertyInfo = "boolean-value"
    type AttrOrigin DOMXPathResultBooleanValuePropertyInfo = DOMXPathResult
    attrGet = getDOMXPathResultBooleanValue
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

-- VVV Prop "invalid-iterator-state"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@invalid-iterator-state@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dOMXPathResult #invalidIteratorState
-- @
getDOMXPathResultInvalidIteratorState :: (MonadIO m, IsDOMXPathResult o) => o -> m Bool
getDOMXPathResultInvalidIteratorState :: forall (m :: * -> *) o.
(MonadIO m, IsDOMXPathResult o) =>
o -> m Bool
getDOMXPathResultInvalidIteratorState o
obj = IO Bool -> m Bool
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
"invalid-iterator-state"

#if defined(ENABLE_OVERLOADING)
data DOMXPathResultInvalidIteratorStatePropertyInfo
instance AttrInfo DOMXPathResultInvalidIteratorStatePropertyInfo where
    type AttrAllowedOps DOMXPathResultInvalidIteratorStatePropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint DOMXPathResultInvalidIteratorStatePropertyInfo = IsDOMXPathResult
    type AttrSetTypeConstraint DOMXPathResultInvalidIteratorStatePropertyInfo = (~) ()
    type AttrTransferTypeConstraint DOMXPathResultInvalidIteratorStatePropertyInfo = (~) ()
    type AttrTransferType DOMXPathResultInvalidIteratorStatePropertyInfo = ()
    type AttrGetType DOMXPathResultInvalidIteratorStatePropertyInfo = Bool
    type AttrLabel DOMXPathResultInvalidIteratorStatePropertyInfo = "invalid-iterator-state"
    type AttrOrigin DOMXPathResultInvalidIteratorStatePropertyInfo = DOMXPathResult
    attrGet = getDOMXPathResultInvalidIteratorState
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

-- VVV Prop "number-value"
   -- Type: TBasicType TDouble
   -- Flags: [PropertyReadable]
   -- Nullable: (Nothing,Nothing)

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

#if defined(ENABLE_OVERLOADING)
data DOMXPathResultNumberValuePropertyInfo
instance AttrInfo DOMXPathResultNumberValuePropertyInfo where
    type AttrAllowedOps DOMXPathResultNumberValuePropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint DOMXPathResultNumberValuePropertyInfo = IsDOMXPathResult
    type AttrSetTypeConstraint DOMXPathResultNumberValuePropertyInfo = (~) ()
    type AttrTransferTypeConstraint DOMXPathResultNumberValuePropertyInfo = (~) ()
    type AttrTransferType DOMXPathResultNumberValuePropertyInfo = ()
    type AttrGetType DOMXPathResultNumberValuePropertyInfo = Double
    type AttrLabel DOMXPathResultNumberValuePropertyInfo = "number-value"
    type AttrOrigin DOMXPathResultNumberValuePropertyInfo = DOMXPathResult
    attrGet = getDOMXPathResultNumberValue
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

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

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

#if defined(ENABLE_OVERLOADING)
data DOMXPathResultResultTypePropertyInfo
instance AttrInfo DOMXPathResultResultTypePropertyInfo where
    type AttrAllowedOps DOMXPathResultResultTypePropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint DOMXPathResultResultTypePropertyInfo = IsDOMXPathResult
    type AttrSetTypeConstraint DOMXPathResultResultTypePropertyInfo = (~) ()
    type AttrTransferTypeConstraint DOMXPathResultResultTypePropertyInfo = (~) ()
    type AttrTransferType DOMXPathResultResultTypePropertyInfo = ()
    type AttrGetType DOMXPathResultResultTypePropertyInfo = Word32
    type AttrLabel DOMXPathResultResultTypePropertyInfo = "result-type"
    type AttrOrigin DOMXPathResultResultTypePropertyInfo = DOMXPathResult
    attrGet = getDOMXPathResultResultType
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

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

-- | Get the value of the “@single-node-value@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dOMXPathResult #singleNodeValue
-- @
getDOMXPathResultSingleNodeValue :: (MonadIO m, IsDOMXPathResult o) => o -> m (Maybe WebKit2WebExtension.DOMNode.DOMNode)
getDOMXPathResultSingleNodeValue :: forall (m :: * -> *) o.
(MonadIO m, IsDOMXPathResult o) =>
o -> m (Maybe DOMNode)
getDOMXPathResultSingleNodeValue o
obj = IO (Maybe DOMNode) -> m (Maybe DOMNode)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe DOMNode) -> m (Maybe DOMNode))
-> IO (Maybe DOMNode) -> m (Maybe 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
"single-node-value" ManagedPtr DOMNode -> DOMNode
WebKit2WebExtension.DOMNode.DOMNode

#if defined(ENABLE_OVERLOADING)
data DOMXPathResultSingleNodeValuePropertyInfo
instance AttrInfo DOMXPathResultSingleNodeValuePropertyInfo where
    type AttrAllowedOps DOMXPathResultSingleNodeValuePropertyInfo = '[ 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint DOMXPathResultSingleNodeValuePropertyInfo = IsDOMXPathResult
    type AttrSetTypeConstraint DOMXPathResultSingleNodeValuePropertyInfo = (~) ()
    type AttrTransferTypeConstraint DOMXPathResultSingleNodeValuePropertyInfo = (~) ()
    type AttrTransferType DOMXPathResultSingleNodeValuePropertyInfo = ()
    type AttrGetType DOMXPathResultSingleNodeValuePropertyInfo = (Maybe WebKit2WebExtension.DOMNode.DOMNode)
    type AttrLabel DOMXPathResultSingleNodeValuePropertyInfo = "single-node-value"
    type AttrOrigin DOMXPathResultSingleNodeValuePropertyInfo = DOMXPathResult
    attrGet = getDOMXPathResultSingleNodeValue
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

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

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

#if defined(ENABLE_OVERLOADING)
data DOMXPathResultSnapshotLengthPropertyInfo
instance AttrInfo DOMXPathResultSnapshotLengthPropertyInfo where
    type AttrAllowedOps DOMXPathResultSnapshotLengthPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint DOMXPathResultSnapshotLengthPropertyInfo = IsDOMXPathResult
    type AttrSetTypeConstraint DOMXPathResultSnapshotLengthPropertyInfo = (~) ()
    type AttrTransferTypeConstraint DOMXPathResultSnapshotLengthPropertyInfo = (~) ()
    type AttrTransferType DOMXPathResultSnapshotLengthPropertyInfo = ()
    type AttrGetType DOMXPathResultSnapshotLengthPropertyInfo = CULong
    type AttrLabel DOMXPathResultSnapshotLengthPropertyInfo = "snapshot-length"
    type AttrOrigin DOMXPathResultSnapshotLengthPropertyInfo = DOMXPathResult
    attrGet = getDOMXPathResultSnapshotLength
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

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

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

#if defined(ENABLE_OVERLOADING)
data DOMXPathResultStringValuePropertyInfo
instance AttrInfo DOMXPathResultStringValuePropertyInfo where
    type AttrAllowedOps DOMXPathResultStringValuePropertyInfo = '[ 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint DOMXPathResultStringValuePropertyInfo = IsDOMXPathResult
    type AttrSetTypeConstraint DOMXPathResultStringValuePropertyInfo = (~) ()
    type AttrTransferTypeConstraint DOMXPathResultStringValuePropertyInfo = (~) ()
    type AttrTransferType DOMXPathResultStringValuePropertyInfo = ()
    type AttrGetType DOMXPathResultStringValuePropertyInfo = (Maybe T.Text)
    type AttrLabel DOMXPathResultStringValuePropertyInfo = "string-value"
    type AttrOrigin DOMXPathResultStringValuePropertyInfo = DOMXPathResult
    attrGet = getDOMXPathResultStringValue
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList DOMXPathResult
type instance O.AttributeList DOMXPathResult = DOMXPathResultAttributeList
type DOMXPathResultAttributeList = ('[ '("booleanValue", DOMXPathResultBooleanValuePropertyInfo), '("coreObject", WebKit2WebExtension.DOMObject.DOMObjectCoreObjectPropertyInfo), '("invalidIteratorState", DOMXPathResultInvalidIteratorStatePropertyInfo), '("numberValue", DOMXPathResultNumberValuePropertyInfo), '("resultType", DOMXPathResultResultTypePropertyInfo), '("singleNodeValue", DOMXPathResultSingleNodeValuePropertyInfo), '("snapshotLength", DOMXPathResultSnapshotLengthPropertyInfo), '("stringValue", DOMXPathResultStringValuePropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
dOMXPathResultBooleanValue :: AttrLabelProxy "booleanValue"
dOMXPathResultBooleanValue = AttrLabelProxy

dOMXPathResultInvalidIteratorState :: AttrLabelProxy "invalidIteratorState"
dOMXPathResultInvalidIteratorState = AttrLabelProxy

dOMXPathResultNumberValue :: AttrLabelProxy "numberValue"
dOMXPathResultNumberValue = AttrLabelProxy

dOMXPathResultResultType :: AttrLabelProxy "resultType"
dOMXPathResultResultType = AttrLabelProxy

dOMXPathResultSingleNodeValue :: AttrLabelProxy "singleNodeValue"
dOMXPathResultSingleNodeValue = AttrLabelProxy

dOMXPathResultSnapshotLength :: AttrLabelProxy "snapshotLength"
dOMXPathResultSnapshotLength = AttrLabelProxy

dOMXPathResultStringValue :: AttrLabelProxy "stringValue"
dOMXPathResultStringValue = AttrLabelProxy

#endif

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

#endif

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

foreign import ccall "webkit_dom_xpath_result_get_boolean_value" webkit_dom_xpath_result_get_boolean_value :: 
    Ptr DOMXPathResult ->                   -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMXPathResult"})
    Ptr (Ptr GError) ->                     -- error
    IO CInt

{-# DEPRECATED dOMXPathResultGetBooleanValue ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMXPathResultGetBooleanValue ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMXPathResult a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMXPathResult.DOMXPathResult'
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
dOMXPathResultGetBooleanValue :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDOMXPathResult a) =>
a -> m ()
dOMXPathResultGetBooleanValue a
self = 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 DOMXPathResult
self' <- a -> IO (Ptr DOMXPathResult)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr DOMXPathResult -> Ptr (Ptr GError) -> IO CInt
webkit_dom_xpath_result_get_boolean_value Ptr DOMXPathResult
self'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data DOMXPathResultGetBooleanValueMethodInfo
instance (signature ~ (m ()), MonadIO m, IsDOMXPathResult a) => O.OverloadedMethod DOMXPathResultGetBooleanValueMethodInfo a signature where
    overloadedMethod = dOMXPathResultGetBooleanValue

instance O.OverloadedMethodInfo DOMXPathResultGetBooleanValueMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.WebKit2WebExtension.Objects.DOMXPathResult.dOMXPathResultGetBooleanValue",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.26/docs/GI-WebKit2WebExtension-Objects-DOMXPathResult.html#v:dOMXPathResultGetBooleanValue"
        }


#endif

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

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

instance O.OverloadedMethodInfo DOMXPathResultGetInvalidIteratorStateMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.WebKit2WebExtension.Objects.DOMXPathResult.dOMXPathResultGetInvalidIteratorState",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.26/docs/GI-WebKit2WebExtension-Objects-DOMXPathResult.html#v:dOMXPathResultGetInvalidIteratorState"
        }


#endif

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

foreign import ccall "webkit_dom_xpath_result_get_number_value" webkit_dom_xpath_result_get_number_value :: 
    Ptr DOMXPathResult ->                   -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMXPathResult"})
    Ptr (Ptr GError) ->                     -- error
    IO CDouble

{-# DEPRECATED dOMXPathResultGetNumberValue ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMXPathResultGetNumberValue ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMXPathResult a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMXPathResult.DOMXPathResult'
    -> m Double
    -- ^ __Returns:__ A @/gdouble/@ /(Can throw 'Data.GI.Base.GError.GError')/
dOMXPathResultGetNumberValue :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDOMXPathResult a) =>
a -> m Double
dOMXPathResultGetNumberValue a
self = IO Double -> m Double
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMXPathResult
self' <- a -> IO (Ptr DOMXPathResult)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    IO Double -> IO () -> IO Double
forall a b. IO a -> IO b -> IO a
onException (do
        CDouble
result <- (Ptr (Ptr GError) -> IO CDouble) -> IO CDouble
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CDouble) -> IO CDouble)
-> (Ptr (Ptr GError) -> IO CDouble) -> IO CDouble
forall a b. (a -> b) -> a -> b
$ Ptr DOMXPathResult -> Ptr (Ptr GError) -> IO CDouble
webkit_dom_xpath_result_get_number_value Ptr DOMXPathResult
self'
        let result' :: Double
result' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
result
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
        Double -> IO Double
forall (m :: * -> *) a. Monad m => a -> m a
return Double
result'
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data DOMXPathResultGetNumberValueMethodInfo
instance (signature ~ (m Double), MonadIO m, IsDOMXPathResult a) => O.OverloadedMethod DOMXPathResultGetNumberValueMethodInfo a signature where
    overloadedMethod = dOMXPathResultGetNumberValue

instance O.OverloadedMethodInfo DOMXPathResultGetNumberValueMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.WebKit2WebExtension.Objects.DOMXPathResult.dOMXPathResultGetNumberValue",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.26/docs/GI-WebKit2WebExtension-Objects-DOMXPathResult.html#v:dOMXPathResultGetNumberValue"
        }


#endif

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

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

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

#if defined(ENABLE_OVERLOADING)
data DOMXPathResultGetResultTypeMethodInfo
instance (signature ~ (m Word16), MonadIO m, IsDOMXPathResult a) => O.OverloadedMethod DOMXPathResultGetResultTypeMethodInfo a signature where
    overloadedMethod = dOMXPathResultGetResultType

instance O.OverloadedMethodInfo DOMXPathResultGetResultTypeMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.WebKit2WebExtension.Objects.DOMXPathResult.dOMXPathResultGetResultType",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.26/docs/GI-WebKit2WebExtension-Objects-DOMXPathResult.html#v:dOMXPathResultGetResultType"
        }


#endif

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

foreign import ccall "webkit_dom_xpath_result_get_single_node_value" webkit_dom_xpath_result_get_single_node_value :: 
    Ptr DOMXPathResult ->                   -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMXPathResult"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr WebKit2WebExtension.DOMNode.DOMNode)

{-# DEPRECATED dOMXPathResultGetSingleNodeValue ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMXPathResultGetSingleNodeValue ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMXPathResult a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMXPathResult.DOMXPathResult'
    -> m WebKit2WebExtension.DOMNode.DOMNode
    -- ^ __Returns:__ A t'GI.WebKit2WebExtension.Objects.DOMNode.DOMNode' /(Can throw 'Data.GI.Base.GError.GError')/
dOMXPathResultGetSingleNodeValue :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDOMXPathResult a) =>
a -> m DOMNode
dOMXPathResultGetSingleNodeValue 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 DOMXPathResult
self' <- a -> IO (Ptr DOMXPathResult)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    IO DOMNode -> IO () -> IO DOMNode
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr DOMNode
result <- (Ptr (Ptr GError) -> IO (Ptr DOMNode)) -> IO (Ptr DOMNode)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr DOMNode)) -> IO (Ptr DOMNode))
-> (Ptr (Ptr GError) -> IO (Ptr DOMNode)) -> IO (Ptr DOMNode)
forall a b. (a -> b) -> a -> b
$ Ptr DOMXPathResult -> Ptr (Ptr GError) -> IO (Ptr DOMNode)
webkit_dom_xpath_result_get_single_node_value Ptr DOMXPathResult
self'
        Text -> Ptr DOMNode -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"dOMXPathResultGetSingleNodeValue" 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'
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data DOMXPathResultGetSingleNodeValueMethodInfo
instance (signature ~ (m WebKit2WebExtension.DOMNode.DOMNode), MonadIO m, IsDOMXPathResult a) => O.OverloadedMethod DOMXPathResultGetSingleNodeValueMethodInfo a signature where
    overloadedMethod = dOMXPathResultGetSingleNodeValue

instance O.OverloadedMethodInfo DOMXPathResultGetSingleNodeValueMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.WebKit2WebExtension.Objects.DOMXPathResult.dOMXPathResultGetSingleNodeValue",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.26/docs/GI-WebKit2WebExtension-Objects-DOMXPathResult.html#v:dOMXPathResultGetSingleNodeValue"
        }


#endif

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

foreign import ccall "webkit_dom_xpath_result_get_snapshot_length" webkit_dom_xpath_result_get_snapshot_length :: 
    Ptr DOMXPathResult ->                   -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMXPathResult"})
    Ptr (Ptr GError) ->                     -- error
    IO CULong

{-# DEPRECATED dOMXPathResultGetSnapshotLength ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMXPathResultGetSnapshotLength ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMXPathResult a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMXPathResult.DOMXPathResult'
    -> m CULong
    -- ^ __Returns:__ A @/gulong/@ /(Can throw 'Data.GI.Base.GError.GError')/
dOMXPathResultGetSnapshotLength :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDOMXPathResult a) =>
a -> m CULong
dOMXPathResultGetSnapshotLength 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 DOMXPathResult
self' <- a -> IO (Ptr DOMXPathResult)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    IO CULong -> IO () -> IO CULong
forall a b. IO a -> IO b -> IO a
onException (do
        CULong
result <- (Ptr (Ptr GError) -> IO CULong) -> IO CULong
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CULong) -> IO CULong)
-> (Ptr (Ptr GError) -> IO CULong) -> IO CULong
forall a b. (a -> b) -> a -> b
$ Ptr DOMXPathResult -> Ptr (Ptr GError) -> IO CULong
webkit_dom_xpath_result_get_snapshot_length Ptr DOMXPathResult
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
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data DOMXPathResultGetSnapshotLengthMethodInfo
instance (signature ~ (m CULong), MonadIO m, IsDOMXPathResult a) => O.OverloadedMethod DOMXPathResultGetSnapshotLengthMethodInfo a signature where
    overloadedMethod = dOMXPathResultGetSnapshotLength

instance O.OverloadedMethodInfo DOMXPathResultGetSnapshotLengthMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.WebKit2WebExtension.Objects.DOMXPathResult.dOMXPathResultGetSnapshotLength",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.26/docs/GI-WebKit2WebExtension-Objects-DOMXPathResult.html#v:dOMXPathResultGetSnapshotLength"
        }


#endif

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

foreign import ccall "webkit_dom_xpath_result_get_string_value" webkit_dom_xpath_result_get_string_value :: 
    Ptr DOMXPathResult ->                   -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMXPathResult"})
    Ptr (Ptr GError) ->                     -- error
    IO CString

{-# DEPRECATED dOMXPathResultGetStringValue ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMXPathResultGetStringValue ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMXPathResult a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMXPathResult.DOMXPathResult'
    -> m T.Text
    -- ^ __Returns:__ A @/gchar/@ /(Can throw 'Data.GI.Base.GError.GError')/
dOMXPathResultGetStringValue :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDOMXPathResult a) =>
a -> m Text
dOMXPathResultGetStringValue 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 DOMXPathResult
self' <- a -> IO (Ptr DOMXPathResult)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    IO Text -> IO () -> IO Text
forall a b. IO a -> IO b -> IO a
onException (do
        CString
result <- (Ptr (Ptr GError) -> IO CString) -> IO CString
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CString) -> IO CString)
-> (Ptr (Ptr GError) -> IO CString) -> IO CString
forall a b. (a -> b) -> a -> b
$ Ptr DOMXPathResult -> Ptr (Ptr GError) -> IO CString
webkit_dom_xpath_result_get_string_value Ptr DOMXPathResult
self'
        Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"dOMXPathResultGetStringValue" 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'
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data DOMXPathResultGetStringValueMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsDOMXPathResult a) => O.OverloadedMethod DOMXPathResultGetStringValueMethodInfo a signature where
    overloadedMethod = dOMXPathResultGetStringValue

instance O.OverloadedMethodInfo DOMXPathResultGetStringValueMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.WebKit2WebExtension.Objects.DOMXPathResult.dOMXPathResultGetStringValue",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.26/docs/GI-WebKit2WebExtension-Objects-DOMXPathResult.html#v:dOMXPathResultGetStringValue"
        }


#endif

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

foreign import ccall "webkit_dom_xpath_result_iterate_next" webkit_dom_xpath_result_iterate_next :: 
    Ptr DOMXPathResult ->                   -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMXPathResult"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr WebKit2WebExtension.DOMNode.DOMNode)

{-# DEPRECATED dOMXPathResultIterateNext ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMXPathResultIterateNext ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMXPathResult a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMXPathResult.DOMXPathResult'
    -> m WebKit2WebExtension.DOMNode.DOMNode
    -- ^ __Returns:__ A t'GI.WebKit2WebExtension.Objects.DOMNode.DOMNode' /(Can throw 'Data.GI.Base.GError.GError')/
dOMXPathResultIterateNext :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDOMXPathResult a) =>
a -> m DOMNode
dOMXPathResultIterateNext 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 DOMXPathResult
self' <- a -> IO (Ptr DOMXPathResult)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    IO DOMNode -> IO () -> IO DOMNode
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr DOMNode
result <- (Ptr (Ptr GError) -> IO (Ptr DOMNode)) -> IO (Ptr DOMNode)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr DOMNode)) -> IO (Ptr DOMNode))
-> (Ptr (Ptr GError) -> IO (Ptr DOMNode)) -> IO (Ptr DOMNode)
forall a b. (a -> b) -> a -> b
$ Ptr DOMXPathResult -> Ptr (Ptr GError) -> IO (Ptr DOMNode)
webkit_dom_xpath_result_iterate_next Ptr DOMXPathResult
self'
        Text -> Ptr DOMNode -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"dOMXPathResultIterateNext" 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'
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data DOMXPathResultIterateNextMethodInfo
instance (signature ~ (m WebKit2WebExtension.DOMNode.DOMNode), MonadIO m, IsDOMXPathResult a) => O.OverloadedMethod DOMXPathResultIterateNextMethodInfo a signature where
    overloadedMethod = dOMXPathResultIterateNext

instance O.OverloadedMethodInfo DOMXPathResultIterateNextMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.WebKit2WebExtension.Objects.DOMXPathResult.dOMXPathResultIterateNext",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.26/docs/GI-WebKit2WebExtension-Objects-DOMXPathResult.html#v:dOMXPathResultIterateNext"
        }


#endif

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

foreign import ccall "webkit_dom_xpath_result_snapshot_item" webkit_dom_xpath_result_snapshot_item :: 
    Ptr DOMXPathResult ->                   -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMXPathResult"})
    CULong ->                               -- index : TBasicType TULong
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr WebKit2WebExtension.DOMNode.DOMNode)

{-# DEPRECATED dOMXPathResultSnapshotItem ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMXPathResultSnapshotItem ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMXPathResult a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMXPathResult.DOMXPathResult'
    -> CULong
    -- ^ /@index@/: A @/gulong/@
    -> m WebKit2WebExtension.DOMNode.DOMNode
    -- ^ __Returns:__ A t'GI.WebKit2WebExtension.Objects.DOMNode.DOMNode' /(Can throw 'Data.GI.Base.GError.GError')/
dOMXPathResultSnapshotItem :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDOMXPathResult a) =>
a -> CULong -> m DOMNode
dOMXPathResultSnapshotItem a
self CULong
index = 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 DOMXPathResult
self' <- a -> IO (Ptr DOMXPathResult)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    IO DOMNode -> IO () -> IO DOMNode
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr DOMNode
result <- (Ptr (Ptr GError) -> IO (Ptr DOMNode)) -> IO (Ptr DOMNode)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr DOMNode)) -> IO (Ptr DOMNode))
-> (Ptr (Ptr GError) -> IO (Ptr DOMNode)) -> IO (Ptr DOMNode)
forall a b. (a -> b) -> a -> b
$ Ptr DOMXPathResult
-> CULong -> Ptr (Ptr GError) -> IO (Ptr DOMNode)
webkit_dom_xpath_result_snapshot_item Ptr DOMXPathResult
self' CULong
index
        Text -> Ptr DOMNode -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"dOMXPathResultSnapshotItem" 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'
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data DOMXPathResultSnapshotItemMethodInfo
instance (signature ~ (CULong -> m WebKit2WebExtension.DOMNode.DOMNode), MonadIO m, IsDOMXPathResult a) => O.OverloadedMethod DOMXPathResultSnapshotItemMethodInfo a signature where
    overloadedMethod = dOMXPathResultSnapshotItem

instance O.OverloadedMethodInfo DOMXPathResultSnapshotItemMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.WebKit2WebExtension.Objects.DOMXPathResult.dOMXPathResultSnapshotItem",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.26/docs/GI-WebKit2WebExtension-Objects-DOMXPathResult.html#v:dOMXPathResultSnapshotItem"
        }


#endif