{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- /No description available in the introspection data./

#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif

module GI.WebKit2WebExtension.Objects.DOMDOMSelection
    ( 

-- * Exported types
    DOMDOMSelection(..)                     ,
    IsDOMDOMSelection                       ,
    toDOMDOMSelection                       ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [addRange]("GI.WebKit2WebExtension.Objects.DOMDOMSelection#g:method:addRange"), [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [collapse]("GI.WebKit2WebExtension.Objects.DOMDOMSelection#g:method:collapse"), [collapseToEnd]("GI.WebKit2WebExtension.Objects.DOMDOMSelection#g:method:collapseToEnd"), [collapseToStart]("GI.WebKit2WebExtension.Objects.DOMDOMSelection#g:method:collapseToStart"), [containsNode]("GI.WebKit2WebExtension.Objects.DOMDOMSelection#g:method:containsNode"), [deleteFromDocument]("GI.WebKit2WebExtension.Objects.DOMDOMSelection#g:method:deleteFromDocument"), [empty]("GI.WebKit2WebExtension.Objects.DOMDOMSelection#g:method:empty"), [extend]("GI.WebKit2WebExtension.Objects.DOMDOMSelection#g:method:extend"), [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"), [modify]("GI.WebKit2WebExtension.Objects.DOMDOMSelection#g:method:modify"), [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"), [removeAllRanges]("GI.WebKit2WebExtension.Objects.DOMDOMSelection#g:method:removeAllRanges"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [selectAllChildren]("GI.WebKit2WebExtension.Objects.DOMDOMSelection#g:method:selectAllChildren"), [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
-- [getAnchorNode]("GI.WebKit2WebExtension.Objects.DOMDOMSelection#g:method:getAnchorNode"), [getAnchorOffset]("GI.WebKit2WebExtension.Objects.DOMDOMSelection#g:method:getAnchorOffset"), [getBaseNode]("GI.WebKit2WebExtension.Objects.DOMDOMSelection#g:method:getBaseNode"), [getBaseOffset]("GI.WebKit2WebExtension.Objects.DOMDOMSelection#g:method:getBaseOffset"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getExtentNode]("GI.WebKit2WebExtension.Objects.DOMDOMSelection#g:method:getExtentNode"), [getExtentOffset]("GI.WebKit2WebExtension.Objects.DOMDOMSelection#g:method:getExtentOffset"), [getFocusNode]("GI.WebKit2WebExtension.Objects.DOMDOMSelection#g:method:getFocusNode"), [getFocusOffset]("GI.WebKit2WebExtension.Objects.DOMDOMSelection#g:method:getFocusOffset"), [getIsCollapsed]("GI.WebKit2WebExtension.Objects.DOMDOMSelection#g:method:getIsCollapsed"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getRangeAt]("GI.WebKit2WebExtension.Objects.DOMDOMSelection#g:method:getRangeAt"), [getRangeCount]("GI.WebKit2WebExtension.Objects.DOMDOMSelection#g:method:getRangeCount"), [getSelectionType]("GI.WebKit2WebExtension.Objects.DOMDOMSelection#g:method:getSelectionType").
-- 
-- ==== Setters
-- [setBaseAndExtent]("GI.WebKit2WebExtension.Objects.DOMDOMSelection#g:method:setBaseAndExtent"), [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setPosition]("GI.WebKit2WebExtension.Objects.DOMDOMSelection#g:method:setPosition"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolveDOMDOMSelectionMethod            ,
#endif

-- ** addRange #method:addRange#

#if defined(ENABLE_OVERLOADING)
    DOMDOMSelectionAddRangeMethodInfo       ,
#endif
    dOMDOMSelectionAddRange                 ,


-- ** collapse #method:collapse#

#if defined(ENABLE_OVERLOADING)
    DOMDOMSelectionCollapseMethodInfo       ,
#endif
    dOMDOMSelectionCollapse                 ,


-- ** collapseToEnd #method:collapseToEnd#

#if defined(ENABLE_OVERLOADING)
    DOMDOMSelectionCollapseToEndMethodInfo  ,
#endif
    dOMDOMSelectionCollapseToEnd            ,


-- ** collapseToStart #method:collapseToStart#

#if defined(ENABLE_OVERLOADING)
    DOMDOMSelectionCollapseToStartMethodInfo,
#endif
    dOMDOMSelectionCollapseToStart          ,


-- ** containsNode #method:containsNode#

#if defined(ENABLE_OVERLOADING)
    DOMDOMSelectionContainsNodeMethodInfo   ,
#endif
    dOMDOMSelectionContainsNode             ,


-- ** deleteFromDocument #method:deleteFromDocument#

#if defined(ENABLE_OVERLOADING)
    DOMDOMSelectionDeleteFromDocumentMethodInfo,
#endif
    dOMDOMSelectionDeleteFromDocument       ,


-- ** empty #method:empty#

#if defined(ENABLE_OVERLOADING)
    DOMDOMSelectionEmptyMethodInfo          ,
#endif
    dOMDOMSelectionEmpty                    ,


-- ** extend #method:extend#

#if defined(ENABLE_OVERLOADING)
    DOMDOMSelectionExtendMethodInfo         ,
#endif
    dOMDOMSelectionExtend                   ,


-- ** getAnchorNode #method:getAnchorNode#

#if defined(ENABLE_OVERLOADING)
    DOMDOMSelectionGetAnchorNodeMethodInfo  ,
#endif
    dOMDOMSelectionGetAnchorNode            ,


-- ** getAnchorOffset #method:getAnchorOffset#

#if defined(ENABLE_OVERLOADING)
    DOMDOMSelectionGetAnchorOffsetMethodInfo,
#endif
    dOMDOMSelectionGetAnchorOffset          ,


-- ** getBaseNode #method:getBaseNode#

#if defined(ENABLE_OVERLOADING)
    DOMDOMSelectionGetBaseNodeMethodInfo    ,
#endif
    dOMDOMSelectionGetBaseNode              ,


-- ** getBaseOffset #method:getBaseOffset#

#if defined(ENABLE_OVERLOADING)
    DOMDOMSelectionGetBaseOffsetMethodInfo  ,
#endif
    dOMDOMSelectionGetBaseOffset            ,


-- ** getExtentNode #method:getExtentNode#

#if defined(ENABLE_OVERLOADING)
    DOMDOMSelectionGetExtentNodeMethodInfo  ,
#endif
    dOMDOMSelectionGetExtentNode            ,


-- ** getExtentOffset #method:getExtentOffset#

#if defined(ENABLE_OVERLOADING)
    DOMDOMSelectionGetExtentOffsetMethodInfo,
#endif
    dOMDOMSelectionGetExtentOffset          ,


-- ** getFocusNode #method:getFocusNode#

#if defined(ENABLE_OVERLOADING)
    DOMDOMSelectionGetFocusNodeMethodInfo   ,
#endif
    dOMDOMSelectionGetFocusNode             ,


-- ** getFocusOffset #method:getFocusOffset#

#if defined(ENABLE_OVERLOADING)
    DOMDOMSelectionGetFocusOffsetMethodInfo ,
#endif
    dOMDOMSelectionGetFocusOffset           ,


-- ** getIsCollapsed #method:getIsCollapsed#

#if defined(ENABLE_OVERLOADING)
    DOMDOMSelectionGetIsCollapsedMethodInfo ,
#endif
    dOMDOMSelectionGetIsCollapsed           ,


-- ** getRangeAt #method:getRangeAt#

#if defined(ENABLE_OVERLOADING)
    DOMDOMSelectionGetRangeAtMethodInfo     ,
#endif
    dOMDOMSelectionGetRangeAt               ,


-- ** getRangeCount #method:getRangeCount#

#if defined(ENABLE_OVERLOADING)
    DOMDOMSelectionGetRangeCountMethodInfo  ,
#endif
    dOMDOMSelectionGetRangeCount            ,


-- ** getSelectionType #method:getSelectionType#

#if defined(ENABLE_OVERLOADING)
    DOMDOMSelectionGetSelectionTypeMethodInfo,
#endif
    dOMDOMSelectionGetSelectionType         ,


-- ** modify #method:modify#

#if defined(ENABLE_OVERLOADING)
    DOMDOMSelectionModifyMethodInfo         ,
#endif
    dOMDOMSelectionModify                   ,


-- ** removeAllRanges #method:removeAllRanges#

#if defined(ENABLE_OVERLOADING)
    DOMDOMSelectionRemoveAllRangesMethodInfo,
#endif
    dOMDOMSelectionRemoveAllRanges          ,


-- ** selectAllChildren #method:selectAllChildren#

#if defined(ENABLE_OVERLOADING)
    DOMDOMSelectionSelectAllChildrenMethodInfo,
#endif
    dOMDOMSelectionSelectAllChildren        ,


-- ** setBaseAndExtent #method:setBaseAndExtent#

#if defined(ENABLE_OVERLOADING)
    DOMDOMSelectionSetBaseAndExtentMethodInfo,
#endif
    dOMDOMSelectionSetBaseAndExtent         ,


-- ** setPosition #method:setPosition#

#if defined(ENABLE_OVERLOADING)
    DOMDOMSelectionSetPositionMethodInfo    ,
#endif
    dOMDOMSelectionSetPosition              ,




 -- * Properties


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

#if defined(ENABLE_OVERLOADING)
    DOMDOMSelectionAnchorNodePropertyInfo   ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMDOMSelectionAnchorNode               ,
#endif
    getDOMDOMSelectionAnchorNode            ,


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

#if defined(ENABLE_OVERLOADING)
    DOMDOMSelectionAnchorOffsetPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMDOMSelectionAnchorOffset             ,
#endif
    getDOMDOMSelectionAnchorOffset          ,


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

#if defined(ENABLE_OVERLOADING)
    DOMDOMSelectionBaseNodePropertyInfo     ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMDOMSelectionBaseNode                 ,
#endif
    getDOMDOMSelectionBaseNode              ,


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

#if defined(ENABLE_OVERLOADING)
    DOMDOMSelectionBaseOffsetPropertyInfo   ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMDOMSelectionBaseOffset               ,
#endif
    getDOMDOMSelectionBaseOffset            ,


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

#if defined(ENABLE_OVERLOADING)
    DOMDOMSelectionExtentNodePropertyInfo   ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMDOMSelectionExtentNode               ,
#endif
    getDOMDOMSelectionExtentNode            ,


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

#if defined(ENABLE_OVERLOADING)
    DOMDOMSelectionExtentOffsetPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMDOMSelectionExtentOffset             ,
#endif
    getDOMDOMSelectionExtentOffset          ,


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

#if defined(ENABLE_OVERLOADING)
    DOMDOMSelectionFocusNodePropertyInfo    ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMDOMSelectionFocusNode                ,
#endif
    getDOMDOMSelectionFocusNode             ,


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

#if defined(ENABLE_OVERLOADING)
    DOMDOMSelectionFocusOffsetPropertyInfo  ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMDOMSelectionFocusOffset              ,
#endif
    getDOMDOMSelectionFocusOffset           ,


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

#if defined(ENABLE_OVERLOADING)
    DOMDOMSelectionIsCollapsedPropertyInfo  ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMDOMSelectionIsCollapsed              ,
#endif
    getDOMDOMSelectionIsCollapsed           ,


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

#if defined(ENABLE_OVERLOADING)
    DOMDOMSelectionRangeCountPropertyInfo   ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMDOMSelectionRangeCount               ,
#endif
    getDOMDOMSelectionRangeCount            ,


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

#if defined(ENABLE_OVERLOADING)
    DOMDOMSelectionTypePropertyInfo         ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMDOMSelectionType                     ,
#endif
    getDOMDOMSelectionType                  ,




    ) where

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

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.Kind as DK
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
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMRange as WebKit2WebExtension.DOMRange

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

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

foreign import ccall "webkit_dom_dom_selection_get_type"
    c_webkit_dom_dom_selection_get_type :: IO B.Types.GType

instance B.Types.TypedObject DOMDOMSelection where
    glibType :: IO GType
glibType = IO GType
c_webkit_dom_dom_selection_get_type

instance B.Types.GObject DOMDOMSelection

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

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

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveDOMDOMSelectionMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveDOMDOMSelectionMethod "addRange" o = DOMDOMSelectionAddRangeMethodInfo
    ResolveDOMDOMSelectionMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveDOMDOMSelectionMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveDOMDOMSelectionMethod "collapse" o = DOMDOMSelectionCollapseMethodInfo
    ResolveDOMDOMSelectionMethod "collapseToEnd" o = DOMDOMSelectionCollapseToEndMethodInfo
    ResolveDOMDOMSelectionMethod "collapseToStart" o = DOMDOMSelectionCollapseToStartMethodInfo
    ResolveDOMDOMSelectionMethod "containsNode" o = DOMDOMSelectionContainsNodeMethodInfo
    ResolveDOMDOMSelectionMethod "deleteFromDocument" o = DOMDOMSelectionDeleteFromDocumentMethodInfo
    ResolveDOMDOMSelectionMethod "empty" o = DOMDOMSelectionEmptyMethodInfo
    ResolveDOMDOMSelectionMethod "extend" o = DOMDOMSelectionExtendMethodInfo
    ResolveDOMDOMSelectionMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveDOMDOMSelectionMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveDOMDOMSelectionMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveDOMDOMSelectionMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveDOMDOMSelectionMethod "modify" o = DOMDOMSelectionModifyMethodInfo
    ResolveDOMDOMSelectionMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveDOMDOMSelectionMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveDOMDOMSelectionMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveDOMDOMSelectionMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveDOMDOMSelectionMethod "removeAllRanges" o = DOMDOMSelectionRemoveAllRangesMethodInfo
    ResolveDOMDOMSelectionMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveDOMDOMSelectionMethod "selectAllChildren" o = DOMDOMSelectionSelectAllChildrenMethodInfo
    ResolveDOMDOMSelectionMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveDOMDOMSelectionMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveDOMDOMSelectionMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveDOMDOMSelectionMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveDOMDOMSelectionMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveDOMDOMSelectionMethod "getAnchorNode" o = DOMDOMSelectionGetAnchorNodeMethodInfo
    ResolveDOMDOMSelectionMethod "getAnchorOffset" o = DOMDOMSelectionGetAnchorOffsetMethodInfo
    ResolveDOMDOMSelectionMethod "getBaseNode" o = DOMDOMSelectionGetBaseNodeMethodInfo
    ResolveDOMDOMSelectionMethod "getBaseOffset" o = DOMDOMSelectionGetBaseOffsetMethodInfo
    ResolveDOMDOMSelectionMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveDOMDOMSelectionMethod "getExtentNode" o = DOMDOMSelectionGetExtentNodeMethodInfo
    ResolveDOMDOMSelectionMethod "getExtentOffset" o = DOMDOMSelectionGetExtentOffsetMethodInfo
    ResolveDOMDOMSelectionMethod "getFocusNode" o = DOMDOMSelectionGetFocusNodeMethodInfo
    ResolveDOMDOMSelectionMethod "getFocusOffset" o = DOMDOMSelectionGetFocusOffsetMethodInfo
    ResolveDOMDOMSelectionMethod "getIsCollapsed" o = DOMDOMSelectionGetIsCollapsedMethodInfo
    ResolveDOMDOMSelectionMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveDOMDOMSelectionMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveDOMDOMSelectionMethod "getRangeAt" o = DOMDOMSelectionGetRangeAtMethodInfo
    ResolveDOMDOMSelectionMethod "getRangeCount" o = DOMDOMSelectionGetRangeCountMethodInfo
    ResolveDOMDOMSelectionMethod "getSelectionType" o = DOMDOMSelectionGetSelectionTypeMethodInfo
    ResolveDOMDOMSelectionMethod "setBaseAndExtent" o = DOMDOMSelectionSetBaseAndExtentMethodInfo
    ResolveDOMDOMSelectionMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveDOMDOMSelectionMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveDOMDOMSelectionMethod "setPosition" o = DOMDOMSelectionSetPositionMethodInfo
    ResolveDOMDOMSelectionMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveDOMDOMSelectionMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

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

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

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

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

-- | Get the value of the “@anchor-offset@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dOMDOMSelection #anchorOffset
-- @
getDOMDOMSelectionAnchorOffset :: (MonadIO m, IsDOMDOMSelection o) => o -> m CULong
getDOMDOMSelectionAnchorOffset :: forall (m :: * -> *) o.
(MonadIO m, IsDOMDOMSelection o) =>
o -> m CULong
getDOMDOMSelectionAnchorOffset o
obj = IO CULong -> m CULong
forall a. IO a -> m a
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
"anchor-offset"

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

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

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

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

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

-- | Get the value of the “@base-offset@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dOMDOMSelection #baseOffset
-- @
getDOMDOMSelectionBaseOffset :: (MonadIO m, IsDOMDOMSelection o) => o -> m CULong
getDOMDOMSelectionBaseOffset :: forall (m :: * -> *) o.
(MonadIO m, IsDOMDOMSelection o) =>
o -> m CULong
getDOMDOMSelectionBaseOffset o
obj = IO CULong -> m CULong
forall a. IO a -> m a
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
"base-offset"

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

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

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

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

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

-- | Get the value of the “@extent-offset@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dOMDOMSelection #extentOffset
-- @
getDOMDOMSelectionExtentOffset :: (MonadIO m, IsDOMDOMSelection o) => o -> m CULong
getDOMDOMSelectionExtentOffset :: forall (m :: * -> *) o.
(MonadIO m, IsDOMDOMSelection o) =>
o -> m CULong
getDOMDOMSelectionExtentOffset o
obj = IO CULong -> m CULong
forall a. IO a -> m a
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
"extent-offset"

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

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

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

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

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

-- | Get the value of the “@focus-offset@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dOMDOMSelection #focusOffset
-- @
getDOMDOMSelectionFocusOffset :: (MonadIO m, IsDOMDOMSelection o) => o -> m CULong
getDOMDOMSelectionFocusOffset :: forall (m :: * -> *) o.
(MonadIO m, IsDOMDOMSelection o) =>
o -> m CULong
getDOMDOMSelectionFocusOffset o
obj = IO CULong -> m CULong
forall a. IO a -> m a
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
"focus-offset"

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

-- VVV Prop "is-collapsed"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable]
   -- Nullable: (Just False,Nothing)

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

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

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

-- | Get the value of the “@range-count@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dOMDOMSelection #rangeCount
-- @
getDOMDOMSelectionRangeCount :: (MonadIO m, IsDOMDOMSelection o) => o -> m CULong
getDOMDOMSelectionRangeCount :: forall (m :: * -> *) o.
(MonadIO m, IsDOMDOMSelection o) =>
o -> m CULong
getDOMDOMSelectionRangeCount o
obj = IO CULong -> m CULong
forall a. IO a -> m a
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
"range-count"

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

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

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

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

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList DOMDOMSelection
type instance O.AttributeList DOMDOMSelection = DOMDOMSelectionAttributeList
type DOMDOMSelectionAttributeList = ('[ '("anchorNode", DOMDOMSelectionAnchorNodePropertyInfo), '("anchorOffset", DOMDOMSelectionAnchorOffsetPropertyInfo), '("baseNode", DOMDOMSelectionBaseNodePropertyInfo), '("baseOffset", DOMDOMSelectionBaseOffsetPropertyInfo), '("coreObject", WebKit2WebExtension.DOMObject.DOMObjectCoreObjectPropertyInfo), '("extentNode", DOMDOMSelectionExtentNodePropertyInfo), '("extentOffset", DOMDOMSelectionExtentOffsetPropertyInfo), '("focusNode", DOMDOMSelectionFocusNodePropertyInfo), '("focusOffset", DOMDOMSelectionFocusOffsetPropertyInfo), '("isCollapsed", DOMDOMSelectionIsCollapsedPropertyInfo), '("rangeCount", DOMDOMSelectionRangeCountPropertyInfo), '("type", DOMDOMSelectionTypePropertyInfo)] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
dOMDOMSelectionAnchorNode :: AttrLabelProxy "anchorNode"
dOMDOMSelectionAnchorNode = AttrLabelProxy

dOMDOMSelectionAnchorOffset :: AttrLabelProxy "anchorOffset"
dOMDOMSelectionAnchorOffset = AttrLabelProxy

dOMDOMSelectionBaseNode :: AttrLabelProxy "baseNode"
dOMDOMSelectionBaseNode = AttrLabelProxy

dOMDOMSelectionBaseOffset :: AttrLabelProxy "baseOffset"
dOMDOMSelectionBaseOffset = AttrLabelProxy

dOMDOMSelectionExtentNode :: AttrLabelProxy "extentNode"
dOMDOMSelectionExtentNode = AttrLabelProxy

dOMDOMSelectionExtentOffset :: AttrLabelProxy "extentOffset"
dOMDOMSelectionExtentOffset = AttrLabelProxy

dOMDOMSelectionFocusNode :: AttrLabelProxy "focusNode"
dOMDOMSelectionFocusNode = AttrLabelProxy

dOMDOMSelectionFocusOffset :: AttrLabelProxy "focusOffset"
dOMDOMSelectionFocusOffset = AttrLabelProxy

dOMDOMSelectionIsCollapsed :: AttrLabelProxy "isCollapsed"
dOMDOMSelectionIsCollapsed = AttrLabelProxy

dOMDOMSelectionRangeCount :: AttrLabelProxy "rangeCount"
dOMDOMSelectionRangeCount = AttrLabelProxy

dOMDOMSelectionType :: AttrLabelProxy "type"
dOMDOMSelectionType = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList DOMDOMSelection = DOMDOMSelectionSignalList
type DOMDOMSelectionSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, DK.Type)])

#endif

-- method DOMDOMSelection::add_range
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name
--                   { namespace = "WebKit2WebExtension" , name = "DOMDOMSelection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMDOMSelection"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "range"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit2WebExtension" , name = "DOMRange" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMRange" , 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_dom_selection_add_range" webkit_dom_dom_selection_add_range :: 
    Ptr DOMDOMSelection ->                  -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMDOMSelection"})
    Ptr WebKit2WebExtension.DOMRange.DOMRange -> -- range : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMRange"})
    IO ()

{-# DEPRECATED dOMDOMSelectionAddRange ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
-- 
-- /Since: 2.16/
dOMDOMSelectionAddRange ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMDOMSelection a, WebKit2WebExtension.DOMRange.IsDOMRange b) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMDOMSelection.DOMDOMSelection'
    -> b
    -- ^ /@range@/: A t'GI.WebKit2WebExtension.Objects.DOMRange.DOMRange'
    -> m ()
dOMDOMSelectionAddRange :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDOMDOMSelection a, IsDOMRange b) =>
a -> b -> m ()
dOMDOMSelectionAddRange a
self b
range = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMDOMSelection
self' <- a -> IO (Ptr DOMDOMSelection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr DOMRange
range' <- b -> IO (Ptr DOMRange)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
range
    Ptr DOMDOMSelection -> Ptr DOMRange -> IO ()
webkit_dom_dom_selection_add_range Ptr DOMDOMSelection
self' Ptr DOMRange
range'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
range
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DOMDOMSelectionAddRangeMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsDOMDOMSelection a, WebKit2WebExtension.DOMRange.IsDOMRange b) => O.OverloadedMethod DOMDOMSelectionAddRangeMethodInfo a signature where
    overloadedMethod = dOMDOMSelectionAddRange

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


#endif

-- method DOMDOMSelection::collapse
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name
--                   { namespace = "WebKit2WebExtension" , name = "DOMDOMSelection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMDOMSelection"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "node"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit2WebExtension" , name = "DOMNode" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMNode" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "offset"
--           , 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: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_dom_selection_collapse" webkit_dom_dom_selection_collapse :: 
    Ptr DOMDOMSelection ->                  -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMDOMSelection"})
    Ptr WebKit2WebExtension.DOMNode.DOMNode -> -- node : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMNode"})
    CULong ->                               -- offset : TBasicType TULong
    IO ()

{-# DEPRECATED dOMDOMSelectionCollapse ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
-- 
-- /Since: 2.16/
dOMDOMSelectionCollapse ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMDOMSelection a, WebKit2WebExtension.DOMNode.IsDOMNode b) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMDOMSelection.DOMDOMSelection'
    -> b
    -- ^ /@node@/: A t'GI.WebKit2WebExtension.Objects.DOMNode.DOMNode'
    -> CULong
    -- ^ /@offset@/: A @/gulong/@
    -> m ()
dOMDOMSelectionCollapse :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDOMDOMSelection a, IsDOMNode b) =>
a -> b -> CULong -> m ()
dOMDOMSelectionCollapse a
self b
node CULong
offset = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMDOMSelection
self' <- a -> IO (Ptr DOMDOMSelection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr DOMNode
node' <- b -> IO (Ptr DOMNode)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
node
    Ptr DOMDOMSelection -> Ptr DOMNode -> CULong -> IO ()
webkit_dom_dom_selection_collapse Ptr DOMDOMSelection
self' Ptr DOMNode
node' CULong
offset
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
node
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DOMDOMSelectionCollapseMethodInfo
instance (signature ~ (b -> CULong -> m ()), MonadIO m, IsDOMDOMSelection a, WebKit2WebExtension.DOMNode.IsDOMNode b) => O.OverloadedMethod DOMDOMSelectionCollapseMethodInfo a signature where
    overloadedMethod = dOMDOMSelectionCollapse

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


#endif

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

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

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

#if defined(ENABLE_OVERLOADING)
data DOMDOMSelectionCollapseToEndMethodInfo
instance (signature ~ (m ()), MonadIO m, IsDOMDOMSelection a) => O.OverloadedMethod DOMDOMSelectionCollapseToEndMethodInfo a signature where
    overloadedMethod = dOMDOMSelectionCollapseToEnd

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


#endif

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

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

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

#if defined(ENABLE_OVERLOADING)
data DOMDOMSelectionCollapseToStartMethodInfo
instance (signature ~ (m ()), MonadIO m, IsDOMDOMSelection a) => O.OverloadedMethod DOMDOMSelectionCollapseToStartMethodInfo a signature where
    overloadedMethod = dOMDOMSelectionCollapseToStart

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


#endif

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

foreign import ccall "webkit_dom_dom_selection_contains_node" webkit_dom_dom_selection_contains_node :: 
    Ptr DOMDOMSelection ->                  -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMDOMSelection"})
    Ptr WebKit2WebExtension.DOMNode.DOMNode -> -- node : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMNode"})
    CInt ->                                 -- allowPartial : TBasicType TBoolean
    IO CInt

{-# DEPRECATED dOMDOMSelectionContainsNode ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
-- 
-- /Since: 2.16/
dOMDOMSelectionContainsNode ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMDOMSelection a, WebKit2WebExtension.DOMNode.IsDOMNode b) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMDOMSelection.DOMDOMSelection'
    -> b
    -- ^ /@node@/: A t'GI.WebKit2WebExtension.Objects.DOMNode.DOMNode'
    -> Bool
    -- ^ /@allowPartial@/: A t'P.Bool'
    -> m Bool
    -- ^ __Returns:__ A t'P.Bool'
dOMDOMSelectionContainsNode :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDOMDOMSelection a, IsDOMNode b) =>
a -> b -> Bool -> m Bool
dOMDOMSelectionContainsNode a
self b
node Bool
allowPartial = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMDOMSelection
self' <- a -> IO (Ptr DOMDOMSelection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr DOMNode
node' <- b -> IO (Ptr DOMNode)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
node
    let allowPartial' :: CInt
allowPartial' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
P.fromEnum) Bool
allowPartial
    CInt
result <- Ptr DOMDOMSelection -> Ptr DOMNode -> CInt -> IO CInt
webkit_dom_dom_selection_contains_node Ptr DOMDOMSelection
self' Ptr DOMNode
node' CInt
allowPartial'
    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
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
node
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data DOMDOMSelectionContainsNodeMethodInfo
instance (signature ~ (b -> Bool -> m Bool), MonadIO m, IsDOMDOMSelection a, WebKit2WebExtension.DOMNode.IsDOMNode b) => O.OverloadedMethod DOMDOMSelectionContainsNodeMethodInfo a signature where
    overloadedMethod = dOMDOMSelectionContainsNode

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


#endif

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

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

#if defined(ENABLE_OVERLOADING)
data DOMDOMSelectionDeleteFromDocumentMethodInfo
instance (signature ~ (m ()), MonadIO m, IsDOMDOMSelection a) => O.OverloadedMethod DOMDOMSelectionDeleteFromDocumentMethodInfo a signature where
    overloadedMethod = dOMDOMSelectionDeleteFromDocument

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


#endif

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

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

#if defined(ENABLE_OVERLOADING)
data DOMDOMSelectionEmptyMethodInfo
instance (signature ~ (m ()), MonadIO m, IsDOMDOMSelection a) => O.OverloadedMethod DOMDOMSelectionEmptyMethodInfo a signature where
    overloadedMethod = dOMDOMSelectionEmpty

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


#endif

-- method DOMDOMSelection::extend
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name
--                   { namespace = "WebKit2WebExtension" , name = "DOMDOMSelection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMDOMSelection"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "node"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit2WebExtension" , name = "DOMNode" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMNode" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "offset"
--           , 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: Nothing
-- throws : True
-- Skip return : False

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

{-# DEPRECATED dOMDOMSelectionExtend ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
-- 
-- /Since: 2.16/
dOMDOMSelectionExtend ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMDOMSelection a, WebKit2WebExtension.DOMNode.IsDOMNode b) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMDOMSelection.DOMDOMSelection'
    -> b
    -- ^ /@node@/: A t'GI.WebKit2WebExtension.Objects.DOMNode.DOMNode'
    -> CULong
    -- ^ /@offset@/: A @/gulong/@
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
dOMDOMSelectionExtend :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDOMDOMSelection a, IsDOMNode b) =>
a -> b -> CULong -> m ()
dOMDOMSelectionExtend a
self b
node CULong
offset = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMDOMSelection
self' <- a -> IO (Ptr DOMDOMSelection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr DOMNode
node' <- b -> IO (Ptr DOMNode)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
node
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        (Ptr (Ptr GError) -> IO ()) -> IO ()
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO ()) -> IO ())
-> (Ptr (Ptr GError) -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ Ptr DOMDOMSelection
-> Ptr DOMNode -> CULong -> Ptr (Ptr GError) -> IO ()
webkit_dom_dom_selection_extend Ptr DOMDOMSelection
self' Ptr DOMNode
node' CULong
offset
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
        b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
node
        () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data DOMDOMSelectionExtendMethodInfo
instance (signature ~ (b -> CULong -> m ()), MonadIO m, IsDOMDOMSelection a, WebKit2WebExtension.DOMNode.IsDOMNode b) => O.OverloadedMethod DOMDOMSelectionExtendMethodInfo a signature where
    overloadedMethod = dOMDOMSelectionExtend

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


#endif

-- method DOMDOMSelection::get_anchor_node
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name
--                   { namespace = "WebKit2WebExtension" , name = "DOMDOMSelection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMDOMSelection"
--                 , 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_dom_selection_get_anchor_node" webkit_dom_dom_selection_get_anchor_node :: 
    Ptr DOMDOMSelection ->                  -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMDOMSelection"})
    IO (Ptr WebKit2WebExtension.DOMNode.DOMNode)

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

#if defined(ENABLE_OVERLOADING)
data DOMDOMSelectionGetAnchorNodeMethodInfo
instance (signature ~ (m WebKit2WebExtension.DOMNode.DOMNode), MonadIO m, IsDOMDOMSelection a) => O.OverloadedMethod DOMDOMSelectionGetAnchorNodeMethodInfo a signature where
    overloadedMethod = dOMDOMSelectionGetAnchorNode

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


#endif

-- method DOMDOMSelection::get_anchor_offset
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name
--                   { namespace = "WebKit2WebExtension" , name = "DOMDOMSelection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMDOMSelection"
--                 , 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_dom_selection_get_anchor_offset" webkit_dom_dom_selection_get_anchor_offset :: 
    Ptr DOMDOMSelection ->                  -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMDOMSelection"})
    IO CULong

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

#if defined(ENABLE_OVERLOADING)
data DOMDOMSelectionGetAnchorOffsetMethodInfo
instance (signature ~ (m CULong), MonadIO m, IsDOMDOMSelection a) => O.OverloadedMethod DOMDOMSelectionGetAnchorOffsetMethodInfo a signature where
    overloadedMethod = dOMDOMSelectionGetAnchorOffset

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


#endif

-- method DOMDOMSelection::get_base_node
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name
--                   { namespace = "WebKit2WebExtension" , name = "DOMDOMSelection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMDOMSelection"
--                 , 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_dom_selection_get_base_node" webkit_dom_dom_selection_get_base_node :: 
    Ptr DOMDOMSelection ->                  -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMDOMSelection"})
    IO (Ptr WebKit2WebExtension.DOMNode.DOMNode)

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

#if defined(ENABLE_OVERLOADING)
data DOMDOMSelectionGetBaseNodeMethodInfo
instance (signature ~ (m WebKit2WebExtension.DOMNode.DOMNode), MonadIO m, IsDOMDOMSelection a) => O.OverloadedMethod DOMDOMSelectionGetBaseNodeMethodInfo a signature where
    overloadedMethod = dOMDOMSelectionGetBaseNode

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


#endif

-- method DOMDOMSelection::get_base_offset
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name
--                   { namespace = "WebKit2WebExtension" , name = "DOMDOMSelection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMDOMSelection"
--                 , 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_dom_selection_get_base_offset" webkit_dom_dom_selection_get_base_offset :: 
    Ptr DOMDOMSelection ->                  -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMDOMSelection"})
    IO CULong

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

#if defined(ENABLE_OVERLOADING)
data DOMDOMSelectionGetBaseOffsetMethodInfo
instance (signature ~ (m CULong), MonadIO m, IsDOMDOMSelection a) => O.OverloadedMethod DOMDOMSelectionGetBaseOffsetMethodInfo a signature where
    overloadedMethod = dOMDOMSelectionGetBaseOffset

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


#endif

-- method DOMDOMSelection::get_extent_node
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name
--                   { namespace = "WebKit2WebExtension" , name = "DOMDOMSelection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMDOMSelection"
--                 , 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_dom_selection_get_extent_node" webkit_dom_dom_selection_get_extent_node :: 
    Ptr DOMDOMSelection ->                  -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMDOMSelection"})
    IO (Ptr WebKit2WebExtension.DOMNode.DOMNode)

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

#if defined(ENABLE_OVERLOADING)
data DOMDOMSelectionGetExtentNodeMethodInfo
instance (signature ~ (m WebKit2WebExtension.DOMNode.DOMNode), MonadIO m, IsDOMDOMSelection a) => O.OverloadedMethod DOMDOMSelectionGetExtentNodeMethodInfo a signature where
    overloadedMethod = dOMDOMSelectionGetExtentNode

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


#endif

-- method DOMDOMSelection::get_extent_offset
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name
--                   { namespace = "WebKit2WebExtension" , name = "DOMDOMSelection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMDOMSelection"
--                 , 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_dom_selection_get_extent_offset" webkit_dom_dom_selection_get_extent_offset :: 
    Ptr DOMDOMSelection ->                  -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMDOMSelection"})
    IO CULong

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

#if defined(ENABLE_OVERLOADING)
data DOMDOMSelectionGetExtentOffsetMethodInfo
instance (signature ~ (m CULong), MonadIO m, IsDOMDOMSelection a) => O.OverloadedMethod DOMDOMSelectionGetExtentOffsetMethodInfo a signature where
    overloadedMethod = dOMDOMSelectionGetExtentOffset

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


#endif

-- method DOMDOMSelection::get_focus_node
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name
--                   { namespace = "WebKit2WebExtension" , name = "DOMDOMSelection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMDOMSelection"
--                 , 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_dom_selection_get_focus_node" webkit_dom_dom_selection_get_focus_node :: 
    Ptr DOMDOMSelection ->                  -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMDOMSelection"})
    IO (Ptr WebKit2WebExtension.DOMNode.DOMNode)

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

#if defined(ENABLE_OVERLOADING)
data DOMDOMSelectionGetFocusNodeMethodInfo
instance (signature ~ (m WebKit2WebExtension.DOMNode.DOMNode), MonadIO m, IsDOMDOMSelection a) => O.OverloadedMethod DOMDOMSelectionGetFocusNodeMethodInfo a signature where
    overloadedMethod = dOMDOMSelectionGetFocusNode

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


#endif

-- method DOMDOMSelection::get_focus_offset
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name
--                   { namespace = "WebKit2WebExtension" , name = "DOMDOMSelection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMDOMSelection"
--                 , 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_dom_selection_get_focus_offset" webkit_dom_dom_selection_get_focus_offset :: 
    Ptr DOMDOMSelection ->                  -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMDOMSelection"})
    IO CULong

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

#if defined(ENABLE_OVERLOADING)
data DOMDOMSelectionGetFocusOffsetMethodInfo
instance (signature ~ (m CULong), MonadIO m, IsDOMDOMSelection a) => O.OverloadedMethod DOMDOMSelectionGetFocusOffsetMethodInfo a signature where
    overloadedMethod = dOMDOMSelectionGetFocusOffset

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


#endif

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

{-# DEPRECATED dOMDOMSelectionGetIsCollapsed ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
-- 
-- /Since: 2.16/
dOMDOMSelectionGetIsCollapsed ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMDOMSelection a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMDOMSelection.DOMDOMSelection'
    -> m Bool
    -- ^ __Returns:__ A t'P.Bool'
dOMDOMSelectionGetIsCollapsed :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDOMDOMSelection a) =>
a -> m Bool
dOMDOMSelectionGetIsCollapsed a
self = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMDOMSelection
self' <- a -> IO (Ptr DOMDOMSelection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CInt
result <- Ptr DOMDOMSelection -> IO CInt
webkit_dom_dom_selection_get_is_collapsed Ptr DOMDOMSelection
self'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data DOMDOMSelectionGetIsCollapsedMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsDOMDOMSelection a) => O.OverloadedMethod DOMDOMSelectionGetIsCollapsedMethodInfo a signature where
    overloadedMethod = dOMDOMSelectionGetIsCollapsed

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


#endif

-- method DOMDOMSelection::get_range_at
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name
--                   { namespace = "WebKit2WebExtension" , name = "DOMDOMSelection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMDOMSelection"
--                 , 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 = "DOMRange" })
-- throws : True
-- Skip return : False

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

{-# DEPRECATED dOMDOMSelectionGetRangeAt ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
-- 
-- /Since: 2.16/
dOMDOMSelectionGetRangeAt ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMDOMSelection a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMDOMSelection.DOMDOMSelection'
    -> CULong
    -- ^ /@index@/: A @/gulong/@
    -> m WebKit2WebExtension.DOMRange.DOMRange
    -- ^ __Returns:__ A t'GI.WebKit2WebExtension.Objects.DOMRange.DOMRange' /(Can throw 'Data.GI.Base.GError.GError')/
dOMDOMSelectionGetRangeAt :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDOMDOMSelection a) =>
a -> CULong -> m DOMRange
dOMDOMSelectionGetRangeAt a
self CULong
index = IO DOMRange -> m DOMRange
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DOMRange -> m DOMRange) -> IO DOMRange -> m DOMRange
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMDOMSelection
self' <- a -> IO (Ptr DOMDOMSelection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    IO DOMRange -> IO () -> IO DOMRange
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr DOMRange
result <- (Ptr (Ptr GError) -> IO (Ptr DOMRange)) -> IO (Ptr DOMRange)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr DOMRange)) -> IO (Ptr DOMRange))
-> (Ptr (Ptr GError) -> IO (Ptr DOMRange)) -> IO (Ptr DOMRange)
forall a b. (a -> b) -> a -> b
$ Ptr DOMDOMSelection
-> CULong -> Ptr (Ptr GError) -> IO (Ptr DOMRange)
webkit_dom_dom_selection_get_range_at Ptr DOMDOMSelection
self' CULong
index
        Text -> Ptr DOMRange -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"dOMDOMSelectionGetRangeAt" Ptr DOMRange
result
        DOMRange
result' <- ((ManagedPtr DOMRange -> DOMRange) -> Ptr DOMRange -> IO DOMRange
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr DOMRange -> DOMRange
WebKit2WebExtension.DOMRange.DOMRange) Ptr DOMRange
result
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
        DOMRange -> IO DOMRange
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return DOMRange
result'
     ) (do
        () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data DOMDOMSelectionGetRangeAtMethodInfo
instance (signature ~ (CULong -> m WebKit2WebExtension.DOMRange.DOMRange), MonadIO m, IsDOMDOMSelection a) => O.OverloadedMethod DOMDOMSelectionGetRangeAtMethodInfo a signature where
    overloadedMethod = dOMDOMSelectionGetRangeAt

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


#endif

-- method DOMDOMSelection::get_range_count
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name
--                   { namespace = "WebKit2WebExtension" , name = "DOMDOMSelection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMDOMSelection"
--                 , 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_dom_selection_get_range_count" webkit_dom_dom_selection_get_range_count :: 
    Ptr DOMDOMSelection ->                  -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMDOMSelection"})
    IO CULong

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

#if defined(ENABLE_OVERLOADING)
data DOMDOMSelectionGetRangeCountMethodInfo
instance (signature ~ (m CULong), MonadIO m, IsDOMDOMSelection a) => O.OverloadedMethod DOMDOMSelectionGetRangeCountMethodInfo a signature where
    overloadedMethod = dOMDOMSelectionGetRangeCount

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


#endif

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

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

{-# DEPRECATED dOMDOMSelectionGetSelectionType ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
-- 
-- /Since: 2.16/
dOMDOMSelectionGetSelectionType ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMDOMSelection a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMDOMSelection.DOMDOMSelection'
    -> m T.Text
    -- ^ __Returns:__ A @/gchar/@
dOMDOMSelectionGetSelectionType :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDOMDOMSelection a) =>
a -> m Text
dOMDOMSelectionGetSelectionType a
self = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMDOMSelection
self' <- a -> IO (Ptr DOMDOMSelection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
result <- Ptr DOMDOMSelection -> IO CString
webkit_dom_dom_selection_get_selection_type Ptr DOMDOMSelection
self'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"dOMDOMSelectionGetSelectionType" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data DOMDOMSelectionGetSelectionTypeMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsDOMDOMSelection a) => O.OverloadedMethod DOMDOMSelectionGetSelectionTypeMethodInfo a signature where
    overloadedMethod = dOMDOMSelectionGetSelectionType

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


#endif

-- method DOMDOMSelection::modify
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name
--                   { namespace = "WebKit2WebExtension" , name = "DOMDOMSelection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMDOMSelection"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "alter"
--           , 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
--           }
--       , Arg
--           { argCName = "direction"
--           , 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
--           }
--       , Arg
--           { argCName = "granularity"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #gchar" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_dom_selection_modify" webkit_dom_dom_selection_modify :: 
    Ptr DOMDOMSelection ->                  -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMDOMSelection"})
    CString ->                              -- alter : TBasicType TUTF8
    CString ->                              -- direction : TBasicType TUTF8
    CString ->                              -- granularity : TBasicType TUTF8
    IO ()

{-# DEPRECATED dOMDOMSelectionModify ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
-- 
-- /Since: 2.16/
dOMDOMSelectionModify ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMDOMSelection a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMDOMSelection.DOMDOMSelection'
    -> T.Text
    -- ^ /@alter@/: A @/gchar/@
    -> T.Text
    -- ^ /@direction@/: A @/gchar/@
    -> T.Text
    -- ^ /@granularity@/: A @/gchar/@
    -> m ()
dOMDOMSelectionModify :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDOMDOMSelection a) =>
a -> Text -> Text -> Text -> m ()
dOMDOMSelectionModify a
self Text
alter Text
direction Text
granularity = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMDOMSelection
self' <- a -> IO (Ptr DOMDOMSelection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
alter' <- Text -> IO CString
textToCString Text
alter
    CString
direction' <- Text -> IO CString
textToCString Text
direction
    CString
granularity' <- Text -> IO CString
textToCString Text
granularity
    Ptr DOMDOMSelection -> CString -> CString -> CString -> IO ()
webkit_dom_dom_selection_modify Ptr DOMDOMSelection
self' CString
alter' CString
direction' CString
granularity'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
alter'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
direction'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
granularity'
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DOMDOMSelectionModifyMethodInfo
instance (signature ~ (T.Text -> T.Text -> T.Text -> m ()), MonadIO m, IsDOMDOMSelection a) => O.OverloadedMethod DOMDOMSelectionModifyMethodInfo a signature where
    overloadedMethod = dOMDOMSelectionModify

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


#endif

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

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

#if defined(ENABLE_OVERLOADING)
data DOMDOMSelectionRemoveAllRangesMethodInfo
instance (signature ~ (m ()), MonadIO m, IsDOMDOMSelection a) => O.OverloadedMethod DOMDOMSelectionRemoveAllRangesMethodInfo a signature where
    overloadedMethod = dOMDOMSelectionRemoveAllRanges

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


#endif

-- method DOMDOMSelection::select_all_children
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name
--                   { namespace = "WebKit2WebExtension" , name = "DOMDOMSelection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMDOMSelection"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "node"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit2WebExtension" , name = "DOMNode" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMNode" , 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_dom_selection_select_all_children" webkit_dom_dom_selection_select_all_children :: 
    Ptr DOMDOMSelection ->                  -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMDOMSelection"})
    Ptr WebKit2WebExtension.DOMNode.DOMNode -> -- node : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMNode"})
    IO ()

{-# DEPRECATED dOMDOMSelectionSelectAllChildren ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
-- 
-- /Since: 2.16/
dOMDOMSelectionSelectAllChildren ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMDOMSelection a, WebKit2WebExtension.DOMNode.IsDOMNode b) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMDOMSelection.DOMDOMSelection'
    -> b
    -- ^ /@node@/: A t'GI.WebKit2WebExtension.Objects.DOMNode.DOMNode'
    -> m ()
dOMDOMSelectionSelectAllChildren :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDOMDOMSelection a, IsDOMNode b) =>
a -> b -> m ()
dOMDOMSelectionSelectAllChildren a
self b
node = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMDOMSelection
self' <- a -> IO (Ptr DOMDOMSelection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr DOMNode
node' <- b -> IO (Ptr DOMNode)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
node
    Ptr DOMDOMSelection -> Ptr DOMNode -> IO ()
webkit_dom_dom_selection_select_all_children Ptr DOMDOMSelection
self' Ptr DOMNode
node'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
node
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DOMDOMSelectionSelectAllChildrenMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsDOMDOMSelection a, WebKit2WebExtension.DOMNode.IsDOMNode b) => O.OverloadedMethod DOMDOMSelectionSelectAllChildrenMethodInfo a signature where
    overloadedMethod = dOMDOMSelectionSelectAllChildren

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


#endif

-- method DOMDOMSelection::set_base_and_extent
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name
--                   { namespace = "WebKit2WebExtension" , name = "DOMDOMSelection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMDOMSelection"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "baseNode"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit2WebExtension" , name = "DOMNode" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMNode" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "baseOffset"
--           , 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
--           }
--       , Arg
--           { argCName = "extentNode"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit2WebExtension" , name = "DOMNode" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMNode" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "extentOffset"
--           , 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: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_dom_selection_set_base_and_extent" webkit_dom_dom_selection_set_base_and_extent :: 
    Ptr DOMDOMSelection ->                  -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMDOMSelection"})
    Ptr WebKit2WebExtension.DOMNode.DOMNode -> -- baseNode : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMNode"})
    CULong ->                               -- baseOffset : TBasicType TULong
    Ptr WebKit2WebExtension.DOMNode.DOMNode -> -- extentNode : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMNode"})
    CULong ->                               -- extentOffset : TBasicType TULong
    IO ()

{-# DEPRECATED dOMDOMSelectionSetBaseAndExtent ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
-- 
-- /Since: 2.16/
dOMDOMSelectionSetBaseAndExtent ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMDOMSelection a, WebKit2WebExtension.DOMNode.IsDOMNode b, WebKit2WebExtension.DOMNode.IsDOMNode c) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMDOMSelection.DOMDOMSelection'
    -> b
    -- ^ /@baseNode@/: A t'GI.WebKit2WebExtension.Objects.DOMNode.DOMNode'
    -> CULong
    -- ^ /@baseOffset@/: A @/gulong/@
    -> c
    -- ^ /@extentNode@/: A t'GI.WebKit2WebExtension.Objects.DOMNode.DOMNode'
    -> CULong
    -- ^ /@extentOffset@/: A @/gulong/@
    -> m ()
dOMDOMSelectionSetBaseAndExtent :: forall (m :: * -> *) a b c.
(HasCallStack, MonadIO m, IsDOMDOMSelection a, IsDOMNode b,
 IsDOMNode c) =>
a -> b -> CULong -> c -> CULong -> m ()
dOMDOMSelectionSetBaseAndExtent a
self b
baseNode CULong
baseOffset c
extentNode CULong
extentOffset = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMDOMSelection
self' <- a -> IO (Ptr DOMDOMSelection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr DOMNode
baseNode' <- b -> IO (Ptr DOMNode)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
baseNode
    Ptr DOMNode
extentNode' <- c -> IO (Ptr DOMNode)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
extentNode
    Ptr DOMDOMSelection
-> Ptr DOMNode -> CULong -> Ptr DOMNode -> CULong -> IO ()
webkit_dom_dom_selection_set_base_and_extent Ptr DOMDOMSelection
self' Ptr DOMNode
baseNode' CULong
baseOffset Ptr DOMNode
extentNode' CULong
extentOffset
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
baseNode
    c -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr c
extentNode
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DOMDOMSelectionSetBaseAndExtentMethodInfo
instance (signature ~ (b -> CULong -> c -> CULong -> m ()), MonadIO m, IsDOMDOMSelection a, WebKit2WebExtension.DOMNode.IsDOMNode b, WebKit2WebExtension.DOMNode.IsDOMNode c) => O.OverloadedMethod DOMDOMSelectionSetBaseAndExtentMethodInfo a signature where
    overloadedMethod = dOMDOMSelectionSetBaseAndExtent

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


#endif

-- method DOMDOMSelection::set_position
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name
--                   { namespace = "WebKit2WebExtension" , name = "DOMDOMSelection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMDOMSelection"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "node"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit2WebExtension" , name = "DOMNode" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMNode" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "offset"
--           , 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: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_dom_selection_set_position" webkit_dom_dom_selection_set_position :: 
    Ptr DOMDOMSelection ->                  -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMDOMSelection"})
    Ptr WebKit2WebExtension.DOMNode.DOMNode -> -- node : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMNode"})
    CULong ->                               -- offset : TBasicType TULong
    IO ()

{-# DEPRECATED dOMDOMSelectionSetPosition ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
-- 
-- /Since: 2.16/
dOMDOMSelectionSetPosition ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMDOMSelection a, WebKit2WebExtension.DOMNode.IsDOMNode b) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMDOMSelection.DOMDOMSelection'
    -> b
    -- ^ /@node@/: A t'GI.WebKit2WebExtension.Objects.DOMNode.DOMNode'
    -> CULong
    -- ^ /@offset@/: A @/gulong/@
    -> m ()
dOMDOMSelectionSetPosition :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDOMDOMSelection a, IsDOMNode b) =>
a -> b -> CULong -> m ()
dOMDOMSelectionSetPosition a
self b
node CULong
offset = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMDOMSelection
self' <- a -> IO (Ptr DOMDOMSelection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr DOMNode
node' <- b -> IO (Ptr DOMNode)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
node
    Ptr DOMDOMSelection -> Ptr DOMNode -> CULong -> IO ()
webkit_dom_dom_selection_set_position Ptr DOMDOMSelection
self' Ptr DOMNode
node' CULong
offset
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
node
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DOMDOMSelectionSetPositionMethodInfo
instance (signature ~ (b -> CULong -> m ()), MonadIO m, IsDOMDOMSelection a, WebKit2WebExtension.DOMNode.IsDOMNode b) => O.OverloadedMethod DOMDOMSelectionSetPositionMethodInfo a signature where
    overloadedMethod = dOMDOMSelectionSetPosition

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


#endif