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

-- * Exported types
    DOMRange(..)                            ,
    IsDOMRange                              ,
    toDOMRange                              ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [cloneContents]("GI.WebKit2WebExtension.Objects.DOMRange#g:method:cloneContents"), [cloneRange]("GI.WebKit2WebExtension.Objects.DOMRange#g:method:cloneRange"), [collapse]("GI.WebKit2WebExtension.Objects.DOMRange#g:method:collapse"), [compareBoundaryPoints]("GI.WebKit2WebExtension.Objects.DOMRange#g:method:compareBoundaryPoints"), [compareNode]("GI.WebKit2WebExtension.Objects.DOMRange#g:method:compareNode"), [comparePoint]("GI.WebKit2WebExtension.Objects.DOMRange#g:method:comparePoint"), [createContextualFragment]("GI.WebKit2WebExtension.Objects.DOMRange#g:method:createContextualFragment"), [deleteContents]("GI.WebKit2WebExtension.Objects.DOMRange#g:method:deleteContents"), [detach]("GI.WebKit2WebExtension.Objects.DOMRange#g:method:detach"), [expand]("GI.WebKit2WebExtension.Objects.DOMRange#g:method:expand"), [extractContents]("GI.WebKit2WebExtension.Objects.DOMRange#g:method:extractContents"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [insertNode]("GI.WebKit2WebExtension.Objects.DOMRange#g:method:insertNode"), [intersectsNode]("GI.WebKit2WebExtension.Objects.DOMRange#g:method:intersectsNode"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [isPointInRange]("GI.WebKit2WebExtension.Objects.DOMRange#g:method:isPointInRange"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [selectNode]("GI.WebKit2WebExtension.Objects.DOMRange#g:method:selectNode"), [selectNodeContents]("GI.WebKit2WebExtension.Objects.DOMRange#g:method:selectNodeContents"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [surroundContents]("GI.WebKit2WebExtension.Objects.DOMRange#g:method:surroundContents"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [toString]("GI.WebKit2WebExtension.Objects.DOMRange#g:method:toString"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getCollapsed]("GI.WebKit2WebExtension.Objects.DOMRange#g:method:getCollapsed"), [getCommonAncestorContainer]("GI.WebKit2WebExtension.Objects.DOMRange#g:method:getCommonAncestorContainer"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getEndContainer]("GI.WebKit2WebExtension.Objects.DOMRange#g:method:getEndContainer"), [getEndOffset]("GI.WebKit2WebExtension.Objects.DOMRange#g:method:getEndOffset"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getStartContainer]("GI.WebKit2WebExtension.Objects.DOMRange#g:method:getStartContainer"), [getStartOffset]("GI.WebKit2WebExtension.Objects.DOMRange#g:method:getStartOffset"), [getText]("GI.WebKit2WebExtension.Objects.DOMRange#g:method:getText").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setEnd]("GI.WebKit2WebExtension.Objects.DOMRange#g:method:setEnd"), [setEndAfter]("GI.WebKit2WebExtension.Objects.DOMRange#g:method:setEndAfter"), [setEndBefore]("GI.WebKit2WebExtension.Objects.DOMRange#g:method:setEndBefore"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setStart]("GI.WebKit2WebExtension.Objects.DOMRange#g:method:setStart"), [setStartAfter]("GI.WebKit2WebExtension.Objects.DOMRange#g:method:setStartAfter"), [setStartBefore]("GI.WebKit2WebExtension.Objects.DOMRange#g:method:setStartBefore").

#if defined(ENABLE_OVERLOADING)
    ResolveDOMRangeMethod                   ,
#endif

-- ** cloneContents #method:cloneContents#

#if defined(ENABLE_OVERLOADING)
    DOMRangeCloneContentsMethodInfo         ,
#endif
    dOMRangeCloneContents                   ,


-- ** cloneRange #method:cloneRange#

#if defined(ENABLE_OVERLOADING)
    DOMRangeCloneRangeMethodInfo            ,
#endif
    dOMRangeCloneRange                      ,


-- ** collapse #method:collapse#

#if defined(ENABLE_OVERLOADING)
    DOMRangeCollapseMethodInfo              ,
#endif
    dOMRangeCollapse                        ,


-- ** compareBoundaryPoints #method:compareBoundaryPoints#

#if defined(ENABLE_OVERLOADING)
    DOMRangeCompareBoundaryPointsMethodInfo ,
#endif
    dOMRangeCompareBoundaryPoints           ,


-- ** compareNode #method:compareNode#

#if defined(ENABLE_OVERLOADING)
    DOMRangeCompareNodeMethodInfo           ,
#endif
    dOMRangeCompareNode                     ,


-- ** comparePoint #method:comparePoint#

#if defined(ENABLE_OVERLOADING)
    DOMRangeComparePointMethodInfo          ,
#endif
    dOMRangeComparePoint                    ,


-- ** createContextualFragment #method:createContextualFragment#

#if defined(ENABLE_OVERLOADING)
    DOMRangeCreateContextualFragmentMethodInfo,
#endif
    dOMRangeCreateContextualFragment        ,


-- ** deleteContents #method:deleteContents#

#if defined(ENABLE_OVERLOADING)
    DOMRangeDeleteContentsMethodInfo        ,
#endif
    dOMRangeDeleteContents                  ,


-- ** detach #method:detach#

#if defined(ENABLE_OVERLOADING)
    DOMRangeDetachMethodInfo                ,
#endif
    dOMRangeDetach                          ,


-- ** expand #method:expand#

#if defined(ENABLE_OVERLOADING)
    DOMRangeExpandMethodInfo                ,
#endif
    dOMRangeExpand                          ,


-- ** extractContents #method:extractContents#

#if defined(ENABLE_OVERLOADING)
    DOMRangeExtractContentsMethodInfo       ,
#endif
    dOMRangeExtractContents                 ,


-- ** getCollapsed #method:getCollapsed#

#if defined(ENABLE_OVERLOADING)
    DOMRangeGetCollapsedMethodInfo          ,
#endif
    dOMRangeGetCollapsed                    ,


-- ** getCommonAncestorContainer #method:getCommonAncestorContainer#

#if defined(ENABLE_OVERLOADING)
    DOMRangeGetCommonAncestorContainerMethodInfo,
#endif
    dOMRangeGetCommonAncestorContainer      ,


-- ** getEndContainer #method:getEndContainer#

#if defined(ENABLE_OVERLOADING)
    DOMRangeGetEndContainerMethodInfo       ,
#endif
    dOMRangeGetEndContainer                 ,


-- ** getEndOffset #method:getEndOffset#

#if defined(ENABLE_OVERLOADING)
    DOMRangeGetEndOffsetMethodInfo          ,
#endif
    dOMRangeGetEndOffset                    ,


-- ** getStartContainer #method:getStartContainer#

#if defined(ENABLE_OVERLOADING)
    DOMRangeGetStartContainerMethodInfo     ,
#endif
    dOMRangeGetStartContainer               ,


-- ** getStartOffset #method:getStartOffset#

#if defined(ENABLE_OVERLOADING)
    DOMRangeGetStartOffsetMethodInfo        ,
#endif
    dOMRangeGetStartOffset                  ,


-- ** getText #method:getText#

#if defined(ENABLE_OVERLOADING)
    DOMRangeGetTextMethodInfo               ,
#endif
    dOMRangeGetText                         ,


-- ** insertNode #method:insertNode#

#if defined(ENABLE_OVERLOADING)
    DOMRangeInsertNodeMethodInfo            ,
#endif
    dOMRangeInsertNode                      ,


-- ** intersectsNode #method:intersectsNode#

#if defined(ENABLE_OVERLOADING)
    DOMRangeIntersectsNodeMethodInfo        ,
#endif
    dOMRangeIntersectsNode                  ,


-- ** isPointInRange #method:isPointInRange#

#if defined(ENABLE_OVERLOADING)
    DOMRangeIsPointInRangeMethodInfo        ,
#endif
    dOMRangeIsPointInRange                  ,


-- ** selectNode #method:selectNode#

#if defined(ENABLE_OVERLOADING)
    DOMRangeSelectNodeMethodInfo            ,
#endif
    dOMRangeSelectNode                      ,


-- ** selectNodeContents #method:selectNodeContents#

#if defined(ENABLE_OVERLOADING)
    DOMRangeSelectNodeContentsMethodInfo    ,
#endif
    dOMRangeSelectNodeContents              ,


-- ** setEnd #method:setEnd#

#if defined(ENABLE_OVERLOADING)
    DOMRangeSetEndMethodInfo                ,
#endif
    dOMRangeSetEnd                          ,


-- ** setEndAfter #method:setEndAfter#

#if defined(ENABLE_OVERLOADING)
    DOMRangeSetEndAfterMethodInfo           ,
#endif
    dOMRangeSetEndAfter                     ,


-- ** setEndBefore #method:setEndBefore#

#if defined(ENABLE_OVERLOADING)
    DOMRangeSetEndBeforeMethodInfo          ,
#endif
    dOMRangeSetEndBefore                    ,


-- ** setStart #method:setStart#

#if defined(ENABLE_OVERLOADING)
    DOMRangeSetStartMethodInfo              ,
#endif
    dOMRangeSetStart                        ,


-- ** setStartAfter #method:setStartAfter#

#if defined(ENABLE_OVERLOADING)
    DOMRangeSetStartAfterMethodInfo         ,
#endif
    dOMRangeSetStartAfter                   ,


-- ** setStartBefore #method:setStartBefore#

#if defined(ENABLE_OVERLOADING)
    DOMRangeSetStartBeforeMethodInfo        ,
#endif
    dOMRangeSetStartBefore                  ,


-- ** surroundContents #method:surroundContents#

#if defined(ENABLE_OVERLOADING)
    DOMRangeSurroundContentsMethodInfo      ,
#endif
    dOMRangeSurroundContents                ,


-- ** toString #method:toString#

#if defined(ENABLE_OVERLOADING)
    DOMRangeToStringMethodInfo              ,
#endif
    dOMRangeToString                        ,




 -- * Properties


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

#if defined(ENABLE_OVERLOADING)
    DOMRangeCollapsedPropertyInfo           ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMRangeCollapsed                       ,
#endif
    getDOMRangeCollapsed                    ,


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

#if defined(ENABLE_OVERLOADING)
    DOMRangeCommonAncestorContainerPropertyInfo,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMRangeCommonAncestorContainer         ,
#endif
    getDOMRangeCommonAncestorContainer      ,


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

#if defined(ENABLE_OVERLOADING)
    DOMRangeEndContainerPropertyInfo        ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMRangeEndContainer                    ,
#endif
    getDOMRangeEndContainer                 ,


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

#if defined(ENABLE_OVERLOADING)
    DOMRangeEndOffsetPropertyInfo           ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMRangeEndOffset                       ,
#endif
    getDOMRangeEndOffset                    ,


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

#if defined(ENABLE_OVERLOADING)
    DOMRangeStartContainerPropertyInfo      ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMRangeStartContainer                  ,
#endif
    getDOMRangeStartContainer               ,


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

#if defined(ENABLE_OVERLOADING)
    DOMRangeStartOffsetPropertyInfo         ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMRangeStartOffset                     ,
#endif
    getDOMRangeStartOffset                  ,


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

#if defined(ENABLE_OVERLOADING)
    DOMRangeTextPropertyInfo                ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMRangeText                            ,
#endif
    getDOMRangeText                         ,




    ) where

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

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R

import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMDocumentFragment as WebKit2WebExtension.DOMDocumentFragment
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMNode as WebKit2WebExtension.DOMNode
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMObject as WebKit2WebExtension.DOMObject

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

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

foreign import ccall "webkit_dom_range_get_type"
    c_webkit_dom_range_get_type :: IO B.Types.GType

instance B.Types.TypedObject DOMRange where
    glibType :: IO GType
glibType = IO GType
c_webkit_dom_range_get_type

instance B.Types.GObject DOMRange

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

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

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveDOMRangeMethod (t :: Symbol) (o :: *) :: * where
    ResolveDOMRangeMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveDOMRangeMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveDOMRangeMethod "cloneContents" o = DOMRangeCloneContentsMethodInfo
    ResolveDOMRangeMethod "cloneRange" o = DOMRangeCloneRangeMethodInfo
    ResolveDOMRangeMethod "collapse" o = DOMRangeCollapseMethodInfo
    ResolveDOMRangeMethod "compareBoundaryPoints" o = DOMRangeCompareBoundaryPointsMethodInfo
    ResolveDOMRangeMethod "compareNode" o = DOMRangeCompareNodeMethodInfo
    ResolveDOMRangeMethod "comparePoint" o = DOMRangeComparePointMethodInfo
    ResolveDOMRangeMethod "createContextualFragment" o = DOMRangeCreateContextualFragmentMethodInfo
    ResolveDOMRangeMethod "deleteContents" o = DOMRangeDeleteContentsMethodInfo
    ResolveDOMRangeMethod "detach" o = DOMRangeDetachMethodInfo
    ResolveDOMRangeMethod "expand" o = DOMRangeExpandMethodInfo
    ResolveDOMRangeMethod "extractContents" o = DOMRangeExtractContentsMethodInfo
    ResolveDOMRangeMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveDOMRangeMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveDOMRangeMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveDOMRangeMethod "insertNode" o = DOMRangeInsertNodeMethodInfo
    ResolveDOMRangeMethod "intersectsNode" o = DOMRangeIntersectsNodeMethodInfo
    ResolveDOMRangeMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveDOMRangeMethod "isPointInRange" o = DOMRangeIsPointInRangeMethodInfo
    ResolveDOMRangeMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveDOMRangeMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveDOMRangeMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveDOMRangeMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveDOMRangeMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveDOMRangeMethod "selectNode" o = DOMRangeSelectNodeMethodInfo
    ResolveDOMRangeMethod "selectNodeContents" o = DOMRangeSelectNodeContentsMethodInfo
    ResolveDOMRangeMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveDOMRangeMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveDOMRangeMethod "surroundContents" o = DOMRangeSurroundContentsMethodInfo
    ResolveDOMRangeMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveDOMRangeMethod "toString" o = DOMRangeToStringMethodInfo
    ResolveDOMRangeMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveDOMRangeMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveDOMRangeMethod "getCollapsed" o = DOMRangeGetCollapsedMethodInfo
    ResolveDOMRangeMethod "getCommonAncestorContainer" o = DOMRangeGetCommonAncestorContainerMethodInfo
    ResolveDOMRangeMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveDOMRangeMethod "getEndContainer" o = DOMRangeGetEndContainerMethodInfo
    ResolveDOMRangeMethod "getEndOffset" o = DOMRangeGetEndOffsetMethodInfo
    ResolveDOMRangeMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveDOMRangeMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveDOMRangeMethod "getStartContainer" o = DOMRangeGetStartContainerMethodInfo
    ResolveDOMRangeMethod "getStartOffset" o = DOMRangeGetStartOffsetMethodInfo
    ResolveDOMRangeMethod "getText" o = DOMRangeGetTextMethodInfo
    ResolveDOMRangeMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveDOMRangeMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveDOMRangeMethod "setEnd" o = DOMRangeSetEndMethodInfo
    ResolveDOMRangeMethod "setEndAfter" o = DOMRangeSetEndAfterMethodInfo
    ResolveDOMRangeMethod "setEndBefore" o = DOMRangeSetEndBeforeMethodInfo
    ResolveDOMRangeMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveDOMRangeMethod "setStart" o = DOMRangeSetStartMethodInfo
    ResolveDOMRangeMethod "setStartAfter" o = DOMRangeSetStartAfterMethodInfo
    ResolveDOMRangeMethod "setStartBefore" o = DOMRangeSetStartBeforeMethodInfo
    ResolveDOMRangeMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

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

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

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

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

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

#if defined(ENABLE_OVERLOADING)
data DOMRangeCommonAncestorContainerPropertyInfo
instance AttrInfo DOMRangeCommonAncestorContainerPropertyInfo where
    type AttrAllowedOps DOMRangeCommonAncestorContainerPropertyInfo = '[ 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint DOMRangeCommonAncestorContainerPropertyInfo = IsDOMRange
    type AttrSetTypeConstraint DOMRangeCommonAncestorContainerPropertyInfo = (~) ()
    type AttrTransferTypeConstraint DOMRangeCommonAncestorContainerPropertyInfo = (~) ()
    type AttrTransferType DOMRangeCommonAncestorContainerPropertyInfo = ()
    type AttrGetType DOMRangeCommonAncestorContainerPropertyInfo = (Maybe WebKit2WebExtension.DOMNode.DOMNode)
    type AttrLabel DOMRangeCommonAncestorContainerPropertyInfo = "common-ancestor-container"
    type AttrOrigin DOMRangeCommonAncestorContainerPropertyInfo = DOMRange
    attrGet = getDOMRangeCommonAncestorContainer
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2WebExtension.Objects.DOMRange.commonAncestorContainer"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.27/docs/GI-WebKit2WebExtension-Objects-DOMRange.html#g:attr:commonAncestorContainer"
        })
#endif

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

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

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

-- VVV Prop "end-offset"
   -- Type: TBasicType TLong
   -- Flags: [PropertyReadable]
   -- Nullable: (Nothing,Nothing)

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

#if defined(ENABLE_OVERLOADING)
data DOMRangeEndOffsetPropertyInfo
instance AttrInfo DOMRangeEndOffsetPropertyInfo where
    type AttrAllowedOps DOMRangeEndOffsetPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint DOMRangeEndOffsetPropertyInfo = IsDOMRange
    type AttrSetTypeConstraint DOMRangeEndOffsetPropertyInfo = (~) ()
    type AttrTransferTypeConstraint DOMRangeEndOffsetPropertyInfo = (~) ()
    type AttrTransferType DOMRangeEndOffsetPropertyInfo = ()
    type AttrGetType DOMRangeEndOffsetPropertyInfo = CLong
    type AttrLabel DOMRangeEndOffsetPropertyInfo = "end-offset"
    type AttrOrigin DOMRangeEndOffsetPropertyInfo = DOMRange
    attrGet = getDOMRangeEndOffset
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2WebExtension.Objects.DOMRange.endOffset"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.27/docs/GI-WebKit2WebExtension-Objects-DOMRange.html#g:attr:endOffset"
        })
#endif

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

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

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

-- VVV Prop "start-offset"
   -- Type: TBasicType TLong
   -- Flags: [PropertyReadable]
   -- Nullable: (Nothing,Nothing)

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

#if defined(ENABLE_OVERLOADING)
data DOMRangeStartOffsetPropertyInfo
instance AttrInfo DOMRangeStartOffsetPropertyInfo where
    type AttrAllowedOps DOMRangeStartOffsetPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint DOMRangeStartOffsetPropertyInfo = IsDOMRange
    type AttrSetTypeConstraint DOMRangeStartOffsetPropertyInfo = (~) ()
    type AttrTransferTypeConstraint DOMRangeStartOffsetPropertyInfo = (~) ()
    type AttrTransferType DOMRangeStartOffsetPropertyInfo = ()
    type AttrGetType DOMRangeStartOffsetPropertyInfo = CLong
    type AttrLabel DOMRangeStartOffsetPropertyInfo = "start-offset"
    type AttrOrigin DOMRangeStartOffsetPropertyInfo = DOMRange
    attrGet = getDOMRangeStartOffset
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2WebExtension.Objects.DOMRange.startOffset"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.27/docs/GI-WebKit2WebExtension-Objects-DOMRange.html#g:attr:startOffset"
        })
#endif

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

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

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

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList DOMRange
type instance O.AttributeList DOMRange = DOMRangeAttributeList
type DOMRangeAttributeList = ('[ '("collapsed", DOMRangeCollapsedPropertyInfo), '("commonAncestorContainer", DOMRangeCommonAncestorContainerPropertyInfo), '("coreObject", WebKit2WebExtension.DOMObject.DOMObjectCoreObjectPropertyInfo), '("endContainer", DOMRangeEndContainerPropertyInfo), '("endOffset", DOMRangeEndOffsetPropertyInfo), '("startContainer", DOMRangeStartContainerPropertyInfo), '("startOffset", DOMRangeStartOffsetPropertyInfo), '("text", DOMRangeTextPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
dOMRangeCollapsed :: AttrLabelProxy "collapsed"
dOMRangeCollapsed = AttrLabelProxy

dOMRangeCommonAncestorContainer :: AttrLabelProxy "commonAncestorContainer"
dOMRangeCommonAncestorContainer = AttrLabelProxy

dOMRangeEndContainer :: AttrLabelProxy "endContainer"
dOMRangeEndContainer = AttrLabelProxy

dOMRangeEndOffset :: AttrLabelProxy "endOffset"
dOMRangeEndOffset = AttrLabelProxy

dOMRangeStartContainer :: AttrLabelProxy "startContainer"
dOMRangeStartContainer = AttrLabelProxy

dOMRangeStartOffset :: AttrLabelProxy "startOffset"
dOMRangeStartOffset = AttrLabelProxy

dOMRangeText :: AttrLabelProxy "text"
dOMRangeText = AttrLabelProxy

#endif

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

#endif

-- method DOMRange::clone_contents
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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: Just
--               (TInterface
--                  Name
--                    { namespace = "WebKit2WebExtension"
--                    , name = "DOMDocumentFragment"
--                    })
-- throws : True
-- Skip return : False

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

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

#if defined(ENABLE_OVERLOADING)
data DOMRangeCloneContentsMethodInfo
instance (signature ~ (m WebKit2WebExtension.DOMDocumentFragment.DOMDocumentFragment), MonadIO m, IsDOMRange a) => O.OverloadedMethod DOMRangeCloneContentsMethodInfo a signature where
    overloadedMethod = dOMRangeCloneContents

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


#endif

-- method DOMRange::clone_range
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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: Just
--               (TInterface
--                  Name { namespace = "WebKit2WebExtension" , name = "DOMRange" })
-- throws : True
-- Skip return : False

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

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

#if defined(ENABLE_OVERLOADING)
data DOMRangeCloneRangeMethodInfo
instance (signature ~ (m DOMRange), MonadIO m, IsDOMRange a) => O.OverloadedMethod DOMRangeCloneRangeMethodInfo a signature where
    overloadedMethod = dOMRangeCloneRange

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


#endif

-- method DOMRange::collapse
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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
--           }
--       , Arg
--           { argCName = "toStart"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #gboolean" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : True
-- Skip return : False

foreign import ccall "webkit_dom_range_collapse" webkit_dom_range_collapse :: 
    Ptr DOMRange ->                         -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMRange"})
    CInt ->                                 -- toStart : TBasicType TBoolean
    Ptr (Ptr GError) ->                     -- error
    IO ()

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

#if defined(ENABLE_OVERLOADING)
data DOMRangeCollapseMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsDOMRange a) => O.OverloadedMethod DOMRangeCollapseMethodInfo a signature where
    overloadedMethod = dOMRangeCollapse

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


#endif

-- method DOMRange::compare_boundary_points
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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
--           }
--       , Arg
--           { argCName = "how"
--           , argType = TBasicType TUInt16
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #gushort" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "sourceRange"
--           , 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: Just (TBasicType TInt16)
-- throws : True
-- Skip return : False

foreign import ccall "webkit_dom_range_compare_boundary_points" webkit_dom_range_compare_boundary_points :: 
    Ptr DOMRange ->                         -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMRange"})
    Word16 ->                               -- how : TBasicType TUInt16
    Ptr DOMRange ->                         -- sourceRange : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMRange"})
    Ptr (Ptr GError) ->                     -- error
    IO Int16

{-# DEPRECATED dOMRangeCompareBoundaryPoints ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMRangeCompareBoundaryPoints ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMRange a, IsDOMRange b) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMRange.DOMRange'
    -> Word16
    -- ^ /@how@/: A @/gushort/@
    -> b
    -- ^ /@sourceRange@/: A t'GI.WebKit2WebExtension.Objects.DOMRange.DOMRange'
    -> m Int16
    -- ^ __Returns:__ A @/gshort/@ /(Can throw 'Data.GI.Base.GError.GError')/
dOMRangeCompareBoundaryPoints :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDOMRange a, IsDOMRange b) =>
a -> Word16 -> b -> m Int16
dOMRangeCompareBoundaryPoints a
self Word16
how b
sourceRange = IO Int16 -> m Int16
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int16 -> m Int16) -> IO Int16 -> m Int16
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMRange
self' <- a -> IO (Ptr DOMRange)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr DOMRange
sourceRange' <- b -> IO (Ptr DOMRange)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
sourceRange
    IO Int16 -> IO () -> IO Int16
forall a b. IO a -> IO b -> IO a
onException (do
        Int16
result <- (Ptr (Ptr GError) -> IO Int16) -> IO Int16
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO Int16) -> IO Int16)
-> (Ptr (Ptr GError) -> IO Int16) -> IO Int16
forall a b. (a -> b) -> a -> b
$ Ptr DOMRange
-> Word16 -> Ptr DOMRange -> Ptr (Ptr GError) -> IO Int16
webkit_dom_range_compare_boundary_points Ptr DOMRange
self' Word16
how Ptr DOMRange
sourceRange'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
        b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
sourceRange
        Int16 -> IO Int16
forall (m :: * -> *) a. Monad m => a -> m a
return Int16
result
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data DOMRangeCompareBoundaryPointsMethodInfo
instance (signature ~ (Word16 -> b -> m Int16), MonadIO m, IsDOMRange a, IsDOMRange b) => O.OverloadedMethod DOMRangeCompareBoundaryPointsMethodInfo a signature where
    overloadedMethod = dOMRangeCompareBoundaryPoints

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


#endif

-- method DOMRange::compare_node
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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
--           }
--       , Arg
--           { argCName = "refNode"
--           , 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: Just (TBasicType TInt16)
-- throws : True
-- Skip return : False

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

{-# DEPRECATED dOMRangeCompareNode ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMRangeCompareNode ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMRange a, WebKit2WebExtension.DOMNode.IsDOMNode b) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMRange.DOMRange'
    -> b
    -- ^ /@refNode@/: A t'GI.WebKit2WebExtension.Objects.DOMNode.DOMNode'
    -> m Int16
    -- ^ __Returns:__ A @/gshort/@ /(Can throw 'Data.GI.Base.GError.GError')/
dOMRangeCompareNode :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDOMRange a, IsDOMNode b) =>
a -> b -> m Int16
dOMRangeCompareNode a
self b
refNode = IO Int16 -> m Int16
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int16 -> m Int16) -> IO Int16 -> m Int16
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMRange
self' <- a -> IO (Ptr DOMRange)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr DOMNode
refNode' <- b -> IO (Ptr DOMNode)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
refNode
    IO Int16 -> IO () -> IO Int16
forall a b. IO a -> IO b -> IO a
onException (do
        Int16
result <- (Ptr (Ptr GError) -> IO Int16) -> IO Int16
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO Int16) -> IO Int16)
-> (Ptr (Ptr GError) -> IO Int16) -> IO Int16
forall a b. (a -> b) -> a -> b
$ Ptr DOMRange -> Ptr DOMNode -> Ptr (Ptr GError) -> IO Int16
webkit_dom_range_compare_node Ptr DOMRange
self' Ptr DOMNode
refNode'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
        b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
refNode
        Int16 -> IO Int16
forall (m :: * -> *) a. Monad m => a -> m a
return Int16
result
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data DOMRangeCompareNodeMethodInfo
instance (signature ~ (b -> m Int16), MonadIO m, IsDOMRange a, WebKit2WebExtension.DOMNode.IsDOMNode b) => O.OverloadedMethod DOMRangeCompareNodeMethodInfo a signature where
    overloadedMethod = dOMRangeCompareNode

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


#endif

-- method DOMRange::compare_point
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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
--           }
--       , Arg
--           { argCName = "refNode"
--           , 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 TLong
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #glong" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt16)
-- throws : True
-- Skip return : False

foreign import ccall "webkit_dom_range_compare_point" webkit_dom_range_compare_point :: 
    Ptr DOMRange ->                         -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMRange"})
    Ptr WebKit2WebExtension.DOMNode.DOMNode -> -- refNode : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMNode"})
    CLong ->                                -- offset : TBasicType TLong
    Ptr (Ptr GError) ->                     -- error
    IO Int16

{-# DEPRECATED dOMRangeComparePoint ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMRangeComparePoint ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMRange a, WebKit2WebExtension.DOMNode.IsDOMNode b) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMRange.DOMRange'
    -> b
    -- ^ /@refNode@/: A t'GI.WebKit2WebExtension.Objects.DOMNode.DOMNode'
    -> CLong
    -- ^ /@offset@/: A @/glong/@
    -> m Int16
    -- ^ __Returns:__ A @/gshort/@ /(Can throw 'Data.GI.Base.GError.GError')/
dOMRangeComparePoint :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDOMRange a, IsDOMNode b) =>
a -> b -> CLong -> m Int16
dOMRangeComparePoint a
self b
refNode CLong
offset = IO Int16 -> m Int16
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int16 -> m Int16) -> IO Int16 -> m Int16
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMRange
self' <- a -> IO (Ptr DOMRange)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr DOMNode
refNode' <- b -> IO (Ptr DOMNode)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
refNode
    IO Int16 -> IO () -> IO Int16
forall a b. IO a -> IO b -> IO a
onException (do
        Int16
result <- (Ptr (Ptr GError) -> IO Int16) -> IO Int16
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO Int16) -> IO Int16)
-> (Ptr (Ptr GError) -> IO Int16) -> IO Int16
forall a b. (a -> b) -> a -> b
$ Ptr DOMRange
-> Ptr DOMNode -> CLong -> Ptr (Ptr GError) -> IO Int16
webkit_dom_range_compare_point Ptr DOMRange
self' Ptr DOMNode
refNode' CLong
offset
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
        b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
refNode
        Int16 -> IO Int16
forall (m :: * -> *) a. Monad m => a -> m a
return Int16
result
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data DOMRangeComparePointMethodInfo
instance (signature ~ (b -> CLong -> m Int16), MonadIO m, IsDOMRange a, WebKit2WebExtension.DOMNode.IsDOMNode b) => O.OverloadedMethod DOMRangeComparePointMethodInfo a signature where
    overloadedMethod = dOMRangeComparePoint

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


#endif

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

foreign import ccall "webkit_dom_range_create_contextual_fragment" webkit_dom_range_create_contextual_fragment :: 
    Ptr DOMRange ->                         -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMRange"})
    CString ->                              -- html : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr WebKit2WebExtension.DOMDocumentFragment.DOMDocumentFragment)

{-# DEPRECATED dOMRangeCreateContextualFragment ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMRangeCreateContextualFragment ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMRange a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMRange.DOMRange'
    -> T.Text
    -- ^ /@html@/: A @/gchar/@
    -> m WebKit2WebExtension.DOMDocumentFragment.DOMDocumentFragment
    -- ^ __Returns:__ A t'GI.WebKit2WebExtension.Objects.DOMDocumentFragment.DOMDocumentFragment' /(Can throw 'Data.GI.Base.GError.GError')/
dOMRangeCreateContextualFragment :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDOMRange a) =>
a -> Text -> m DOMDocumentFragment
dOMRangeCreateContextualFragment a
self Text
html = IO DOMDocumentFragment -> m DOMDocumentFragment
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DOMDocumentFragment -> m DOMDocumentFragment)
-> IO DOMDocumentFragment -> m DOMDocumentFragment
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMRange
self' <- a -> IO (Ptr DOMRange)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
html' <- Text -> IO CString
textToCString Text
html
    IO DOMDocumentFragment -> IO () -> IO DOMDocumentFragment
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr DOMDocumentFragment
result <- (Ptr (Ptr GError) -> IO (Ptr DOMDocumentFragment))
-> IO (Ptr DOMDocumentFragment)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr DOMDocumentFragment))
 -> IO (Ptr DOMDocumentFragment))
-> (Ptr (Ptr GError) -> IO (Ptr DOMDocumentFragment))
-> IO (Ptr DOMDocumentFragment)
forall a b. (a -> b) -> a -> b
$ Ptr DOMRange
-> CString -> Ptr (Ptr GError) -> IO (Ptr DOMDocumentFragment)
webkit_dom_range_create_contextual_fragment Ptr DOMRange
self' CString
html'
        Text -> Ptr DOMDocumentFragment -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"dOMRangeCreateContextualFragment" Ptr DOMDocumentFragment
result
        DOMDocumentFragment
result' <- ((ManagedPtr DOMDocumentFragment -> DOMDocumentFragment)
-> Ptr DOMDocumentFragment -> IO DOMDocumentFragment
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr DOMDocumentFragment -> DOMDocumentFragment
WebKit2WebExtension.DOMDocumentFragment.DOMDocumentFragment) Ptr DOMDocumentFragment
result
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
html'
        DOMDocumentFragment -> IO DOMDocumentFragment
forall (m :: * -> *) a. Monad m => a -> m a
return DOMDocumentFragment
result'
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
html'
     )

#if defined(ENABLE_OVERLOADING)
data DOMRangeCreateContextualFragmentMethodInfo
instance (signature ~ (T.Text -> m WebKit2WebExtension.DOMDocumentFragment.DOMDocumentFragment), MonadIO m, IsDOMRange a) => O.OverloadedMethod DOMRangeCreateContextualFragmentMethodInfo a signature where
    overloadedMethod = dOMRangeCreateContextualFragment

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


#endif

-- method DOMRange::delete_contents
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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 : True
-- Skip return : False

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

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

#if defined(ENABLE_OVERLOADING)
data DOMRangeDeleteContentsMethodInfo
instance (signature ~ (m ()), MonadIO m, IsDOMRange a) => O.OverloadedMethod DOMRangeDeleteContentsMethodInfo a signature where
    overloadedMethod = dOMRangeDeleteContents

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


#endif

-- method DOMRange::detach
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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 : True
-- Skip return : False

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

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

#if defined(ENABLE_OVERLOADING)
data DOMRangeDetachMethodInfo
instance (signature ~ (m ()), MonadIO m, IsDOMRange a) => O.OverloadedMethod DOMRangeDetachMethodInfo a signature where
    overloadedMethod = dOMRangeDetach

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


#endif

-- method DOMRange::expand
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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
--           }
--       , Arg
--           { argCName = "unit"
--           , 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 : True
-- Skip return : False

foreign import ccall "webkit_dom_range_expand" webkit_dom_range_expand :: 
    Ptr DOMRange ->                         -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMRange"})
    CString ->                              -- unit : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO ()

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

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

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


#endif

-- method DOMRange::extract_contents
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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: Just
--               (TInterface
--                  Name
--                    { namespace = "WebKit2WebExtension"
--                    , name = "DOMDocumentFragment"
--                    })
-- throws : True
-- Skip return : False

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

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

#if defined(ENABLE_OVERLOADING)
data DOMRangeExtractContentsMethodInfo
instance (signature ~ (m WebKit2WebExtension.DOMDocumentFragment.DOMDocumentFragment), MonadIO m, IsDOMRange a) => O.OverloadedMethod DOMRangeExtractContentsMethodInfo a signature where
    overloadedMethod = dOMRangeExtractContents

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


#endif

-- method DOMRange::get_collapsed
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

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

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

#if defined(ENABLE_OVERLOADING)
data DOMRangeGetCollapsedMethodInfo
instance (signature ~ (m ()), MonadIO m, IsDOMRange a) => O.OverloadedMethod DOMRangeGetCollapsedMethodInfo a signature where
    overloadedMethod = dOMRangeGetCollapsed

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


#endif

-- method DOMRange::get_common_ancestor_container
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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: Just
--               (TInterface
--                  Name { namespace = "WebKit2WebExtension" , name = "DOMNode" })
-- throws : True
-- Skip return : False

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

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

#if defined(ENABLE_OVERLOADING)
data DOMRangeGetCommonAncestorContainerMethodInfo
instance (signature ~ (m WebKit2WebExtension.DOMNode.DOMNode), MonadIO m, IsDOMRange a) => O.OverloadedMethod DOMRangeGetCommonAncestorContainerMethodInfo a signature where
    overloadedMethod = dOMRangeGetCommonAncestorContainer

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


#endif

-- method DOMRange::get_end_container
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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: Just
--               (TInterface
--                  Name { namespace = "WebKit2WebExtension" , name = "DOMNode" })
-- throws : True
-- Skip return : False

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

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

#if defined(ENABLE_OVERLOADING)
data DOMRangeGetEndContainerMethodInfo
instance (signature ~ (m WebKit2WebExtension.DOMNode.DOMNode), MonadIO m, IsDOMRange a) => O.OverloadedMethod DOMRangeGetEndContainerMethodInfo a signature where
    overloadedMethod = dOMRangeGetEndContainer

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


#endif

-- method DOMRange::get_end_offset
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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: Just (TBasicType TLong)
-- throws : True
-- Skip return : False

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

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

#if defined(ENABLE_OVERLOADING)
data DOMRangeGetEndOffsetMethodInfo
instance (signature ~ (m CLong), MonadIO m, IsDOMRange a) => O.OverloadedMethod DOMRangeGetEndOffsetMethodInfo a signature where
    overloadedMethod = dOMRangeGetEndOffset

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


#endif

-- method DOMRange::get_start_container
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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: Just
--               (TInterface
--                  Name { namespace = "WebKit2WebExtension" , name = "DOMNode" })
-- throws : True
-- Skip return : False

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

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

#if defined(ENABLE_OVERLOADING)
data DOMRangeGetStartContainerMethodInfo
instance (signature ~ (m WebKit2WebExtension.DOMNode.DOMNode), MonadIO m, IsDOMRange a) => O.OverloadedMethod DOMRangeGetStartContainerMethodInfo a signature where
    overloadedMethod = dOMRangeGetStartContainer

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


#endif

-- method DOMRange::get_start_offset
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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: Just (TBasicType TLong)
-- throws : True
-- Skip return : False

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

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

#if defined(ENABLE_OVERLOADING)
data DOMRangeGetStartOffsetMethodInfo
instance (signature ~ (m CLong), MonadIO m, IsDOMRange a) => O.OverloadedMethod DOMRangeGetStartOffsetMethodInfo a signature where
    overloadedMethod = dOMRangeGetStartOffset

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


#endif

-- method DOMRange::get_text
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

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

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

#if defined(ENABLE_OVERLOADING)
data DOMRangeGetTextMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsDOMRange a) => O.OverloadedMethod DOMRangeGetTextMethodInfo a signature where
    overloadedMethod = dOMRangeGetText

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


#endif

-- method DOMRange::insert_node
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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
--           }
--       , Arg
--           { argCName = "newNode"
--           , 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 : True
-- Skip return : False

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

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

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

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


#endif

-- method DOMRange::intersects_node
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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
--           }
--       , Arg
--           { argCName = "refNode"
--           , 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: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

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

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

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

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


#endif

-- method DOMRange::is_point_in_range
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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
--           }
--       , Arg
--           { argCName = "refNode"
--           , 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 TLong
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #glong" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "webkit_dom_range_is_point_in_range" webkit_dom_range_is_point_in_range :: 
    Ptr DOMRange ->                         -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMRange"})
    Ptr WebKit2WebExtension.DOMNode.DOMNode -> -- refNode : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMNode"})
    CLong ->                                -- offset : TBasicType TLong
    Ptr (Ptr GError) ->                     -- error
    IO CInt

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

#if defined(ENABLE_OVERLOADING)
data DOMRangeIsPointInRangeMethodInfo
instance (signature ~ (b -> CLong -> m ()), MonadIO m, IsDOMRange a, WebKit2WebExtension.DOMNode.IsDOMNode b) => O.OverloadedMethod DOMRangeIsPointInRangeMethodInfo a signature where
    overloadedMethod = dOMRangeIsPointInRange

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


#endif

-- method DOMRange::select_node
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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
--           }
--       , Arg
--           { argCName = "refNode"
--           , 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 : True
-- Skip return : False

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

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

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

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


#endif

-- method DOMRange::select_node_contents
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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
--           }
--       , Arg
--           { argCName = "refNode"
--           , 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 : True
-- Skip return : False

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

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

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

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


#endif

-- method DOMRange::set_end
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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
--           }
--       , Arg
--           { argCName = "refNode"
--           , 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 TLong
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #glong" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : True
-- Skip return : False

foreign import ccall "webkit_dom_range_set_end" webkit_dom_range_set_end :: 
    Ptr DOMRange ->                         -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMRange"})
    Ptr WebKit2WebExtension.DOMNode.DOMNode -> -- refNode : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMNode"})
    CLong ->                                -- offset : TBasicType TLong
    Ptr (Ptr GError) ->                     -- error
    IO ()

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

#if defined(ENABLE_OVERLOADING)
data DOMRangeSetEndMethodInfo
instance (signature ~ (b -> CLong -> m ()), MonadIO m, IsDOMRange a, WebKit2WebExtension.DOMNode.IsDOMNode b) => O.OverloadedMethod DOMRangeSetEndMethodInfo a signature where
    overloadedMethod = dOMRangeSetEnd

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


#endif

-- method DOMRange::set_end_after
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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
--           }
--       , Arg
--           { argCName = "refNode"
--           , 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 : True
-- Skip return : False

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

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

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

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


#endif

-- method DOMRange::set_end_before
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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
--           }
--       , Arg
--           { argCName = "refNode"
--           , 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 : True
-- Skip return : False

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

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

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

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


#endif

-- method DOMRange::set_start
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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
--           }
--       , Arg
--           { argCName = "refNode"
--           , 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 TLong
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #glong" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : True
-- Skip return : False

foreign import ccall "webkit_dom_range_set_start" webkit_dom_range_set_start :: 
    Ptr DOMRange ->                         -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMRange"})
    Ptr WebKit2WebExtension.DOMNode.DOMNode -> -- refNode : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMNode"})
    CLong ->                                -- offset : TBasicType TLong
    Ptr (Ptr GError) ->                     -- error
    IO ()

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

#if defined(ENABLE_OVERLOADING)
data DOMRangeSetStartMethodInfo
instance (signature ~ (b -> CLong -> m ()), MonadIO m, IsDOMRange a, WebKit2WebExtension.DOMNode.IsDOMNode b) => O.OverloadedMethod DOMRangeSetStartMethodInfo a signature where
    overloadedMethod = dOMRangeSetStart

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


#endif

-- method DOMRange::set_start_after
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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
--           }
--       , Arg
--           { argCName = "refNode"
--           , 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 : True
-- Skip return : False

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

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

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

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


#endif

-- method DOMRange::set_start_before
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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
--           }
--       , Arg
--           { argCName = "refNode"
--           , 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 : True
-- Skip return : False

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

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

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

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


#endif

-- method DOMRange::surround_contents
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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
--           }
--       , Arg
--           { argCName = "newParent"
--           , 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 : True
-- Skip return : False

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

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

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

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


#endif

-- method DOMRange::to_string
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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: Just (TBasicType TUTF8)
-- throws : True
-- Skip return : False

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

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

#if defined(ENABLE_OVERLOADING)
data DOMRangeToStringMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsDOMRange a) => O.OverloadedMethod DOMRangeToStringMethodInfo a signature where
    overloadedMethod = dOMRangeToString

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


#endif