{-# LANGUAGE TypeApplications #-}


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

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

module GI.WebKit2WebExtension.Objects.DOMNode
    ( 

-- * Exported types
    DOMNode(..)                             ,
    IsDOMNode                               ,
    toDOMNode                               ,
    noDOMNode                               ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveDOMNodeMethod                    ,
#endif


-- ** appendChild #method:appendChild#

#if defined(ENABLE_OVERLOADING)
    DOMNodeAppendChildMethodInfo            ,
#endif
    dOMNodeAppendChild                      ,


-- ** cloneNodeWithError #method:cloneNodeWithError#

#if defined(ENABLE_OVERLOADING)
    DOMNodeCloneNodeWithErrorMethodInfo     ,
#endif
    dOMNodeCloneNodeWithError               ,


-- ** compareDocumentPosition #method:compareDocumentPosition#

#if defined(ENABLE_OVERLOADING)
    DOMNodeCompareDocumentPositionMethodInfo,
#endif
    dOMNodeCompareDocumentPosition          ,


-- ** contains #method:contains#

#if defined(ENABLE_OVERLOADING)
    DOMNodeContainsMethodInfo               ,
#endif
    dOMNodeContains                         ,


-- ** forJsValue #method:forJsValue#

    dOMNodeForJsValue                       ,


-- ** getBaseUri #method:getBaseUri#

#if defined(ENABLE_OVERLOADING)
    DOMNodeGetBaseUriMethodInfo             ,
#endif
    dOMNodeGetBaseUri                       ,


-- ** getChildNodes #method:getChildNodes#

#if defined(ENABLE_OVERLOADING)
    DOMNodeGetChildNodesMethodInfo          ,
#endif
    dOMNodeGetChildNodes                    ,


-- ** getFirstChild #method:getFirstChild#

#if defined(ENABLE_OVERLOADING)
    DOMNodeGetFirstChildMethodInfo          ,
#endif
    dOMNodeGetFirstChild                    ,


-- ** getLastChild #method:getLastChild#

#if defined(ENABLE_OVERLOADING)
    DOMNodeGetLastChildMethodInfo           ,
#endif
    dOMNodeGetLastChild                     ,


-- ** getLocalName #method:getLocalName#

#if defined(ENABLE_OVERLOADING)
    DOMNodeGetLocalNameMethodInfo           ,
#endif
    dOMNodeGetLocalName                     ,


-- ** getNamespaceUri #method:getNamespaceUri#

#if defined(ENABLE_OVERLOADING)
    DOMNodeGetNamespaceUriMethodInfo        ,
#endif
    dOMNodeGetNamespaceUri                  ,


-- ** getNextSibling #method:getNextSibling#

#if defined(ENABLE_OVERLOADING)
    DOMNodeGetNextSiblingMethodInfo         ,
#endif
    dOMNodeGetNextSibling                   ,


-- ** getNodeName #method:getNodeName#

#if defined(ENABLE_OVERLOADING)
    DOMNodeGetNodeNameMethodInfo            ,
#endif
    dOMNodeGetNodeName                      ,


-- ** getNodeType #method:getNodeType#

#if defined(ENABLE_OVERLOADING)
    DOMNodeGetNodeTypeMethodInfo            ,
#endif
    dOMNodeGetNodeType                      ,


-- ** getNodeValue #method:getNodeValue#

#if defined(ENABLE_OVERLOADING)
    DOMNodeGetNodeValueMethodInfo           ,
#endif
    dOMNodeGetNodeValue                     ,


-- ** getOwnerDocument #method:getOwnerDocument#

#if defined(ENABLE_OVERLOADING)
    DOMNodeGetOwnerDocumentMethodInfo       ,
#endif
    dOMNodeGetOwnerDocument                 ,


-- ** getParentElement #method:getParentElement#

#if defined(ENABLE_OVERLOADING)
    DOMNodeGetParentElementMethodInfo       ,
#endif
    dOMNodeGetParentElement                 ,


-- ** getParentNode #method:getParentNode#

#if defined(ENABLE_OVERLOADING)
    DOMNodeGetParentNodeMethodInfo          ,
#endif
    dOMNodeGetParentNode                    ,


-- ** getPrefix #method:getPrefix#

#if defined(ENABLE_OVERLOADING)
    DOMNodeGetPrefixMethodInfo              ,
#endif
    dOMNodeGetPrefix                        ,


-- ** getPreviousSibling #method:getPreviousSibling#

#if defined(ENABLE_OVERLOADING)
    DOMNodeGetPreviousSiblingMethodInfo     ,
#endif
    dOMNodeGetPreviousSibling               ,


-- ** getTextContent #method:getTextContent#

#if defined(ENABLE_OVERLOADING)
    DOMNodeGetTextContentMethodInfo         ,
#endif
    dOMNodeGetTextContent                   ,


-- ** hasChildNodes #method:hasChildNodes#

#if defined(ENABLE_OVERLOADING)
    DOMNodeHasChildNodesMethodInfo          ,
#endif
    dOMNodeHasChildNodes                    ,


-- ** insertBefore #method:insertBefore#

#if defined(ENABLE_OVERLOADING)
    DOMNodeInsertBeforeMethodInfo           ,
#endif
    dOMNodeInsertBefore                     ,


-- ** isDefaultNamespace #method:isDefaultNamespace#

#if defined(ENABLE_OVERLOADING)
    DOMNodeIsDefaultNamespaceMethodInfo     ,
#endif
    dOMNodeIsDefaultNamespace               ,


-- ** isEqualNode #method:isEqualNode#

#if defined(ENABLE_OVERLOADING)
    DOMNodeIsEqualNodeMethodInfo            ,
#endif
    dOMNodeIsEqualNode                      ,


-- ** isSameNode #method:isSameNode#

#if defined(ENABLE_OVERLOADING)
    DOMNodeIsSameNodeMethodInfo             ,
#endif
    dOMNodeIsSameNode                       ,


-- ** isSupported #method:isSupported#

#if defined(ENABLE_OVERLOADING)
    DOMNodeIsSupportedMethodInfo            ,
#endif
    dOMNodeIsSupported                      ,


-- ** lookupNamespaceUri #method:lookupNamespaceUri#

#if defined(ENABLE_OVERLOADING)
    DOMNodeLookupNamespaceUriMethodInfo     ,
#endif
    dOMNodeLookupNamespaceUri               ,


-- ** lookupPrefix #method:lookupPrefix#

#if defined(ENABLE_OVERLOADING)
    DOMNodeLookupPrefixMethodInfo           ,
#endif
    dOMNodeLookupPrefix                     ,


-- ** normalize #method:normalize#

#if defined(ENABLE_OVERLOADING)
    DOMNodeNormalizeMethodInfo              ,
#endif
    dOMNodeNormalize                        ,


-- ** removeChild #method:removeChild#

#if defined(ENABLE_OVERLOADING)
    DOMNodeRemoveChildMethodInfo            ,
#endif
    dOMNodeRemoveChild                      ,


-- ** replaceChild #method:replaceChild#

#if defined(ENABLE_OVERLOADING)
    DOMNodeReplaceChildMethodInfo           ,
#endif
    dOMNodeReplaceChild                     ,


-- ** setNodeValue #method:setNodeValue#

#if defined(ENABLE_OVERLOADING)
    DOMNodeSetNodeValueMethodInfo           ,
#endif
    dOMNodeSetNodeValue                     ,


-- ** setPrefix #method:setPrefix#

#if defined(ENABLE_OVERLOADING)
    DOMNodeSetPrefixMethodInfo              ,
#endif
    dOMNodeSetPrefix                        ,


-- ** setTextContent #method:setTextContent#

#if defined(ENABLE_OVERLOADING)
    DOMNodeSetTextContentMethodInfo         ,
#endif
    dOMNodeSetTextContent                   ,




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

#if defined(ENABLE_OVERLOADING)
    DOMNodeBaseUriPropertyInfo              ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMNodeBaseUri                          ,
#endif
    getDOMNodeBaseUri                       ,


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

#if defined(ENABLE_OVERLOADING)
    DOMNodeChildNodesPropertyInfo           ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMNodeChildNodes                       ,
#endif
    getDOMNodeChildNodes                    ,


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

#if defined(ENABLE_OVERLOADING)
    DOMNodeFirstChildPropertyInfo           ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMNodeFirstChild                       ,
#endif
    getDOMNodeFirstChild                    ,


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

#if defined(ENABLE_OVERLOADING)
    DOMNodeLastChildPropertyInfo            ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMNodeLastChild                        ,
#endif
    getDOMNodeLastChild                     ,


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

#if defined(ENABLE_OVERLOADING)
    DOMNodeNextSiblingPropertyInfo          ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMNodeNextSibling                      ,
#endif
    getDOMNodeNextSibling                   ,


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

#if defined(ENABLE_OVERLOADING)
    DOMNodeNodeNamePropertyInfo             ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMNodeNodeName                         ,
#endif
    getDOMNodeNodeName                      ,


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

#if defined(ENABLE_OVERLOADING)
    DOMNodeNodeTypePropertyInfo             ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMNodeNodeType                         ,
#endif
    getDOMNodeNodeType                      ,


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

#if defined(ENABLE_OVERLOADING)
    DOMNodeNodeValuePropertyInfo            ,
#endif
    clearDOMNodeNodeValue                   ,
    constructDOMNodeNodeValue               ,
#if defined(ENABLE_OVERLOADING)
    dOMNodeNodeValue                        ,
#endif
    getDOMNodeNodeValue                     ,
    setDOMNodeNodeValue                     ,


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

#if defined(ENABLE_OVERLOADING)
    DOMNodeOwnerDocumentPropertyInfo        ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMNodeOwnerDocument                    ,
#endif
    getDOMNodeOwnerDocument                 ,


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

#if defined(ENABLE_OVERLOADING)
    DOMNodeParentElementPropertyInfo        ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMNodeParentElement                    ,
#endif
    getDOMNodeParentElement                 ,


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

#if defined(ENABLE_OVERLOADING)
    DOMNodeParentNodePropertyInfo           ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMNodeParentNode                       ,
#endif
    getDOMNodeParentNode                    ,


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

#if defined(ENABLE_OVERLOADING)
    DOMNodePreviousSiblingPropertyInfo      ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMNodePreviousSibling                  ,
#endif
    getDOMNodePreviousSibling               ,


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

#if defined(ENABLE_OVERLOADING)
    DOMNodeTextContentPropertyInfo          ,
#endif
    clearDOMNodeTextContent                 ,
    constructDOMNodeTextContent             ,
#if defined(ENABLE_OVERLOADING)
    dOMNodeTextContent                      ,
#endif
    getDOMNodeTextContent                   ,
    setDOMNodeTextContent                   ,




    ) where

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

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

import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.JavaScriptCore.Objects.Value as JavaScriptCore.Value
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Interfaces.DOMEventTarget as WebKit2WebExtension.DOMEventTarget
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMDocument as WebKit2WebExtension.DOMDocument
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMElement as WebKit2WebExtension.DOMElement
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMNodeList as WebKit2WebExtension.DOMNodeList
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMObject as WebKit2WebExtension.DOMObject

-- | Memory-managed wrapper type.
newtype DOMNode = DOMNode (ManagedPtr DOMNode)
    deriving (DOMNode -> DOMNode -> Bool
(DOMNode -> DOMNode -> Bool)
-> (DOMNode -> DOMNode -> Bool) -> Eq DOMNode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DOMNode -> DOMNode -> Bool
$c/= :: DOMNode -> DOMNode -> Bool
== :: DOMNode -> DOMNode -> Bool
$c== :: DOMNode -> DOMNode -> Bool
Eq)
foreign import ccall "webkit_dom_node_get_type"
    c_webkit_dom_node_get_type :: IO GType

instance GObject DOMNode where
    gobjectType :: IO GType
gobjectType = IO GType
c_webkit_dom_node_get_type
    

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

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

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

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

-- | A convenience alias for `Nothing` :: `Maybe` `DOMNode`.
noDOMNode :: Maybe DOMNode
noDOMNode :: Maybe DOMNode
noDOMNode = Maybe DOMNode
forall a. Maybe a
Nothing

#if defined(ENABLE_OVERLOADING)
type family ResolveDOMNodeMethod (t :: Symbol) (o :: *) :: * where
    ResolveDOMNodeMethod "addEventListener" o = WebKit2WebExtension.DOMEventTarget.DOMEventTargetAddEventListenerMethodInfo
    ResolveDOMNodeMethod "appendChild" o = DOMNodeAppendChildMethodInfo
    ResolveDOMNodeMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveDOMNodeMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveDOMNodeMethod "cloneNodeWithError" o = DOMNodeCloneNodeWithErrorMethodInfo
    ResolveDOMNodeMethod "compareDocumentPosition" o = DOMNodeCompareDocumentPositionMethodInfo
    ResolveDOMNodeMethod "contains" o = DOMNodeContainsMethodInfo
    ResolveDOMNodeMethod "dispatchEvent" o = WebKit2WebExtension.DOMEventTarget.DOMEventTargetDispatchEventMethodInfo
    ResolveDOMNodeMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveDOMNodeMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveDOMNodeMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveDOMNodeMethod "hasChildNodes" o = DOMNodeHasChildNodesMethodInfo
    ResolveDOMNodeMethod "insertBefore" o = DOMNodeInsertBeforeMethodInfo
    ResolveDOMNodeMethod "isDefaultNamespace" o = DOMNodeIsDefaultNamespaceMethodInfo
    ResolveDOMNodeMethod "isEqualNode" o = DOMNodeIsEqualNodeMethodInfo
    ResolveDOMNodeMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveDOMNodeMethod "isSameNode" o = DOMNodeIsSameNodeMethodInfo
    ResolveDOMNodeMethod "isSupported" o = DOMNodeIsSupportedMethodInfo
    ResolveDOMNodeMethod "lookupNamespaceUri" o = DOMNodeLookupNamespaceUriMethodInfo
    ResolveDOMNodeMethod "lookupPrefix" o = DOMNodeLookupPrefixMethodInfo
    ResolveDOMNodeMethod "normalize" o = DOMNodeNormalizeMethodInfo
    ResolveDOMNodeMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveDOMNodeMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveDOMNodeMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveDOMNodeMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveDOMNodeMethod "removeChild" o = DOMNodeRemoveChildMethodInfo
    ResolveDOMNodeMethod "removeEventListener" o = WebKit2WebExtension.DOMEventTarget.DOMEventTargetRemoveEventListenerMethodInfo
    ResolveDOMNodeMethod "replaceChild" o = DOMNodeReplaceChildMethodInfo
    ResolveDOMNodeMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveDOMNodeMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveDOMNodeMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveDOMNodeMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveDOMNodeMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveDOMNodeMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveDOMNodeMethod "getBaseUri" o = DOMNodeGetBaseUriMethodInfo
    ResolveDOMNodeMethod "getChildNodes" o = DOMNodeGetChildNodesMethodInfo
    ResolveDOMNodeMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveDOMNodeMethod "getFirstChild" o = DOMNodeGetFirstChildMethodInfo
    ResolveDOMNodeMethod "getLastChild" o = DOMNodeGetLastChildMethodInfo
    ResolveDOMNodeMethod "getLocalName" o = DOMNodeGetLocalNameMethodInfo
    ResolveDOMNodeMethod "getNamespaceUri" o = DOMNodeGetNamespaceUriMethodInfo
    ResolveDOMNodeMethod "getNextSibling" o = DOMNodeGetNextSiblingMethodInfo
    ResolveDOMNodeMethod "getNodeName" o = DOMNodeGetNodeNameMethodInfo
    ResolveDOMNodeMethod "getNodeType" o = DOMNodeGetNodeTypeMethodInfo
    ResolveDOMNodeMethod "getNodeValue" o = DOMNodeGetNodeValueMethodInfo
    ResolveDOMNodeMethod "getOwnerDocument" o = DOMNodeGetOwnerDocumentMethodInfo
    ResolveDOMNodeMethod "getParentElement" o = DOMNodeGetParentElementMethodInfo
    ResolveDOMNodeMethod "getParentNode" o = DOMNodeGetParentNodeMethodInfo
    ResolveDOMNodeMethod "getPrefix" o = DOMNodeGetPrefixMethodInfo
    ResolveDOMNodeMethod "getPreviousSibling" o = DOMNodeGetPreviousSiblingMethodInfo
    ResolveDOMNodeMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveDOMNodeMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveDOMNodeMethod "getTextContent" o = DOMNodeGetTextContentMethodInfo
    ResolveDOMNodeMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveDOMNodeMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveDOMNodeMethod "setNodeValue" o = DOMNodeSetNodeValueMethodInfo
    ResolveDOMNodeMethod "setPrefix" o = DOMNodeSetPrefixMethodInfo
    ResolveDOMNodeMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveDOMNodeMethod "setTextContent" o = DOMNodeSetTextContentMethodInfo
    ResolveDOMNodeMethod l o = O.MethodResolutionFailed l o

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

#endif

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

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

#if defined(ENABLE_OVERLOADING)
data DOMNodeBaseUriPropertyInfo
instance AttrInfo DOMNodeBaseUriPropertyInfo where
    type AttrAllowedOps DOMNodeBaseUriPropertyInfo = '[ 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint DOMNodeBaseUriPropertyInfo = IsDOMNode
    type AttrSetTypeConstraint DOMNodeBaseUriPropertyInfo = (~) ()
    type AttrTransferTypeConstraint DOMNodeBaseUriPropertyInfo = (~) ()
    type AttrTransferType DOMNodeBaseUriPropertyInfo = ()
    type AttrGetType DOMNodeBaseUriPropertyInfo = (Maybe T.Text)
    type AttrLabel DOMNodeBaseUriPropertyInfo = "base-uri"
    type AttrOrigin DOMNodeBaseUriPropertyInfo = DOMNode
    attrGet = getDOMNodeBaseUri
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

-- VVV Prop "child-nodes"
   -- Type: TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMNodeList"})
   -- Flags: [PropertyReadable]
   -- Nullable: (Nothing,Nothing)

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

#if defined(ENABLE_OVERLOADING)
data DOMNodeChildNodesPropertyInfo
instance AttrInfo DOMNodeChildNodesPropertyInfo where
    type AttrAllowedOps DOMNodeChildNodesPropertyInfo = '[ 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint DOMNodeChildNodesPropertyInfo = IsDOMNode
    type AttrSetTypeConstraint DOMNodeChildNodesPropertyInfo = (~) ()
    type AttrTransferTypeConstraint DOMNodeChildNodesPropertyInfo = (~) ()
    type AttrTransferType DOMNodeChildNodesPropertyInfo = ()
    type AttrGetType DOMNodeChildNodesPropertyInfo = (Maybe WebKit2WebExtension.DOMNodeList.DOMNodeList)
    type AttrLabel DOMNodeChildNodesPropertyInfo = "child-nodes"
    type AttrOrigin DOMNodeChildNodesPropertyInfo = DOMNode
    attrGet = getDOMNodeChildNodes
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

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

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

#if defined(ENABLE_OVERLOADING)
data DOMNodeFirstChildPropertyInfo
instance AttrInfo DOMNodeFirstChildPropertyInfo where
    type AttrAllowedOps DOMNodeFirstChildPropertyInfo = '[ 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint DOMNodeFirstChildPropertyInfo = IsDOMNode
    type AttrSetTypeConstraint DOMNodeFirstChildPropertyInfo = (~) ()
    type AttrTransferTypeConstraint DOMNodeFirstChildPropertyInfo = (~) ()
    type AttrTransferType DOMNodeFirstChildPropertyInfo = ()
    type AttrGetType DOMNodeFirstChildPropertyInfo = DOMNode
    type AttrLabel DOMNodeFirstChildPropertyInfo = "first-child"
    type AttrOrigin DOMNodeFirstChildPropertyInfo = DOMNode
    attrGet = getDOMNodeFirstChild
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

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

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

#if defined(ENABLE_OVERLOADING)
data DOMNodeLastChildPropertyInfo
instance AttrInfo DOMNodeLastChildPropertyInfo where
    type AttrAllowedOps DOMNodeLastChildPropertyInfo = '[ 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint DOMNodeLastChildPropertyInfo = IsDOMNode
    type AttrSetTypeConstraint DOMNodeLastChildPropertyInfo = (~) ()
    type AttrTransferTypeConstraint DOMNodeLastChildPropertyInfo = (~) ()
    type AttrTransferType DOMNodeLastChildPropertyInfo = ()
    type AttrGetType DOMNodeLastChildPropertyInfo = DOMNode
    type AttrLabel DOMNodeLastChildPropertyInfo = "last-child"
    type AttrOrigin DOMNodeLastChildPropertyInfo = DOMNode
    attrGet = getDOMNodeLastChild
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

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

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

#if defined(ENABLE_OVERLOADING)
data DOMNodeNextSiblingPropertyInfo
instance AttrInfo DOMNodeNextSiblingPropertyInfo where
    type AttrAllowedOps DOMNodeNextSiblingPropertyInfo = '[ 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint DOMNodeNextSiblingPropertyInfo = IsDOMNode
    type AttrSetTypeConstraint DOMNodeNextSiblingPropertyInfo = (~) ()
    type AttrTransferTypeConstraint DOMNodeNextSiblingPropertyInfo = (~) ()
    type AttrTransferType DOMNodeNextSiblingPropertyInfo = ()
    type AttrGetType DOMNodeNextSiblingPropertyInfo = DOMNode
    type AttrLabel DOMNodeNextSiblingPropertyInfo = "next-sibling"
    type AttrOrigin DOMNodeNextSiblingPropertyInfo = DOMNode
    attrGet = getDOMNodeNextSibling
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

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

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

#if defined(ENABLE_OVERLOADING)
data DOMNodeNodeNamePropertyInfo
instance AttrInfo DOMNodeNodeNamePropertyInfo where
    type AttrAllowedOps DOMNodeNodeNamePropertyInfo = '[ 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint DOMNodeNodeNamePropertyInfo = IsDOMNode
    type AttrSetTypeConstraint DOMNodeNodeNamePropertyInfo = (~) ()
    type AttrTransferTypeConstraint DOMNodeNodeNamePropertyInfo = (~) ()
    type AttrTransferType DOMNodeNodeNamePropertyInfo = ()
    type AttrGetType DOMNodeNodeNamePropertyInfo = (Maybe T.Text)
    type AttrLabel DOMNodeNodeNamePropertyInfo = "node-name"
    type AttrOrigin DOMNodeNodeNamePropertyInfo = DOMNode
    attrGet = getDOMNodeNodeName
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

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

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

#if defined(ENABLE_OVERLOADING)
data DOMNodeNodeTypePropertyInfo
instance AttrInfo DOMNodeNodeTypePropertyInfo where
    type AttrAllowedOps DOMNodeNodeTypePropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint DOMNodeNodeTypePropertyInfo = IsDOMNode
    type AttrSetTypeConstraint DOMNodeNodeTypePropertyInfo = (~) ()
    type AttrTransferTypeConstraint DOMNodeNodeTypePropertyInfo = (~) ()
    type AttrTransferType DOMNodeNodeTypePropertyInfo = ()
    type AttrGetType DOMNodeNodeTypePropertyInfo = Word32
    type AttrLabel DOMNodeNodeTypePropertyInfo = "node-type"
    type AttrOrigin DOMNodeNodeTypePropertyInfo = DOMNode
    attrGet = getDOMNodeNodeType
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

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

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

-- | Set the value of the “@node-value@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' dOMNode [ #nodeValue 'Data.GI.Base.Attributes.:=' value ]
-- @
setDOMNodeNodeValue :: (MonadIO m, IsDOMNode o) => o -> T.Text -> m ()
setDOMNodeNodeValue :: o -> Text -> m ()
setDOMNodeNodeValue obj :: o
obj val :: Text
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj "node-value" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Construct a `GValueConstruct` with valid value for the “@node-value@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructDOMNodeNodeValue :: (IsDOMNode o) => T.Text -> IO (GValueConstruct o)
constructDOMNodeNodeValue :: Text -> IO (GValueConstruct o)
constructDOMNodeNodeValue val :: Text
val = String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString "node-value" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Set the value of the “@node-value@” property to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #nodeValue
-- @
clearDOMNodeNodeValue :: (MonadIO m, IsDOMNode o) => o -> m ()
clearDOMNodeNodeValue :: o -> m ()
clearDOMNodeNodeValue obj :: o
obj = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj "node-value" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

#if defined(ENABLE_OVERLOADING)
data DOMNodeNodeValuePropertyInfo
instance AttrInfo DOMNodeNodeValuePropertyInfo where
    type AttrAllowedOps DOMNodeNodeValuePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint DOMNodeNodeValuePropertyInfo = IsDOMNode
    type AttrSetTypeConstraint DOMNodeNodeValuePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint DOMNodeNodeValuePropertyInfo = (~) T.Text
    type AttrTransferType DOMNodeNodeValuePropertyInfo = T.Text
    type AttrGetType DOMNodeNodeValuePropertyInfo = (Maybe T.Text)
    type AttrLabel DOMNodeNodeValuePropertyInfo = "node-value"
    type AttrOrigin DOMNodeNodeValuePropertyInfo = DOMNode
    attrGet = getDOMNodeNodeValue
    attrSet = setDOMNodeNodeValue
    attrTransfer _ v = do
        return v
    attrConstruct = constructDOMNodeNodeValue
    attrClear = clearDOMNodeNodeValue
#endif

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

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

#if defined(ENABLE_OVERLOADING)
data DOMNodeOwnerDocumentPropertyInfo
instance AttrInfo DOMNodeOwnerDocumentPropertyInfo where
    type AttrAllowedOps DOMNodeOwnerDocumentPropertyInfo = '[ 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint DOMNodeOwnerDocumentPropertyInfo = IsDOMNode
    type AttrSetTypeConstraint DOMNodeOwnerDocumentPropertyInfo = (~) ()
    type AttrTransferTypeConstraint DOMNodeOwnerDocumentPropertyInfo = (~) ()
    type AttrTransferType DOMNodeOwnerDocumentPropertyInfo = ()
    type AttrGetType DOMNodeOwnerDocumentPropertyInfo = WebKit2WebExtension.DOMDocument.DOMDocument
    type AttrLabel DOMNodeOwnerDocumentPropertyInfo = "owner-document"
    type AttrOrigin DOMNodeOwnerDocumentPropertyInfo = DOMNode
    attrGet = getDOMNodeOwnerDocument
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

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

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

#if defined(ENABLE_OVERLOADING)
data DOMNodeParentElementPropertyInfo
instance AttrInfo DOMNodeParentElementPropertyInfo where
    type AttrAllowedOps DOMNodeParentElementPropertyInfo = '[ 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint DOMNodeParentElementPropertyInfo = IsDOMNode
    type AttrSetTypeConstraint DOMNodeParentElementPropertyInfo = (~) ()
    type AttrTransferTypeConstraint DOMNodeParentElementPropertyInfo = (~) ()
    type AttrTransferType DOMNodeParentElementPropertyInfo = ()
    type AttrGetType DOMNodeParentElementPropertyInfo = WebKit2WebExtension.DOMElement.DOMElement
    type AttrLabel DOMNodeParentElementPropertyInfo = "parent-element"
    type AttrOrigin DOMNodeParentElementPropertyInfo = DOMNode
    attrGet = getDOMNodeParentElement
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

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

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

#if defined(ENABLE_OVERLOADING)
data DOMNodeParentNodePropertyInfo
instance AttrInfo DOMNodeParentNodePropertyInfo where
    type AttrAllowedOps DOMNodeParentNodePropertyInfo = '[ 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint DOMNodeParentNodePropertyInfo = IsDOMNode
    type AttrSetTypeConstraint DOMNodeParentNodePropertyInfo = (~) ()
    type AttrTransferTypeConstraint DOMNodeParentNodePropertyInfo = (~) ()
    type AttrTransferType DOMNodeParentNodePropertyInfo = ()
    type AttrGetType DOMNodeParentNodePropertyInfo = DOMNode
    type AttrLabel DOMNodeParentNodePropertyInfo = "parent-node"
    type AttrOrigin DOMNodeParentNodePropertyInfo = DOMNode
    attrGet = getDOMNodeParentNode
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

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

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

#if defined(ENABLE_OVERLOADING)
data DOMNodePreviousSiblingPropertyInfo
instance AttrInfo DOMNodePreviousSiblingPropertyInfo where
    type AttrAllowedOps DOMNodePreviousSiblingPropertyInfo = '[ 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint DOMNodePreviousSiblingPropertyInfo = IsDOMNode
    type AttrSetTypeConstraint DOMNodePreviousSiblingPropertyInfo = (~) ()
    type AttrTransferTypeConstraint DOMNodePreviousSiblingPropertyInfo = (~) ()
    type AttrTransferType DOMNodePreviousSiblingPropertyInfo = ()
    type AttrGetType DOMNodePreviousSiblingPropertyInfo = DOMNode
    type AttrLabel DOMNodePreviousSiblingPropertyInfo = "previous-sibling"
    type AttrOrigin DOMNodePreviousSiblingPropertyInfo = DOMNode
    attrGet = getDOMNodePreviousSibling
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

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

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

-- | Set the value of the “@text-content@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' dOMNode [ #textContent 'Data.GI.Base.Attributes.:=' value ]
-- @
setDOMNodeTextContent :: (MonadIO m, IsDOMNode o) => o -> T.Text -> m ()
setDOMNodeTextContent :: o -> Text -> m ()
setDOMNodeTextContent obj :: o
obj val :: Text
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj "text-content" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Construct a `GValueConstruct` with valid value for the “@text-content@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructDOMNodeTextContent :: (IsDOMNode o) => T.Text -> IO (GValueConstruct o)
constructDOMNodeTextContent :: Text -> IO (GValueConstruct o)
constructDOMNodeTextContent val :: Text
val = String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString "text-content" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Set the value of the “@text-content@” property to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #textContent
-- @
clearDOMNodeTextContent :: (MonadIO m, IsDOMNode o) => o -> m ()
clearDOMNodeTextContent :: o -> m ()
clearDOMNodeTextContent obj :: o
obj = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj "text-content" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

#if defined(ENABLE_OVERLOADING)
data DOMNodeTextContentPropertyInfo
instance AttrInfo DOMNodeTextContentPropertyInfo where
    type AttrAllowedOps DOMNodeTextContentPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint DOMNodeTextContentPropertyInfo = IsDOMNode
    type AttrSetTypeConstraint DOMNodeTextContentPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint DOMNodeTextContentPropertyInfo = (~) T.Text
    type AttrTransferType DOMNodeTextContentPropertyInfo = T.Text
    type AttrGetType DOMNodeTextContentPropertyInfo = (Maybe T.Text)
    type AttrLabel DOMNodeTextContentPropertyInfo = "text-content"
    type AttrOrigin DOMNodeTextContentPropertyInfo = DOMNode
    attrGet = getDOMNodeTextContent
    attrSet = setDOMNodeTextContent
    attrTransfer _ v = do
        return v
    attrConstruct = constructDOMNodeTextContent
    attrClear = clearDOMNodeTextContent
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList DOMNode
type instance O.AttributeList DOMNode = DOMNodeAttributeList
type DOMNodeAttributeList = ('[ '("baseUri", DOMNodeBaseUriPropertyInfo), '("childNodes", DOMNodeChildNodesPropertyInfo), '("coreObject", WebKit2WebExtension.DOMObject.DOMObjectCoreObjectPropertyInfo), '("firstChild", DOMNodeFirstChildPropertyInfo), '("lastChild", DOMNodeLastChildPropertyInfo), '("nextSibling", DOMNodeNextSiblingPropertyInfo), '("nodeName", DOMNodeNodeNamePropertyInfo), '("nodeType", DOMNodeNodeTypePropertyInfo), '("nodeValue", DOMNodeNodeValuePropertyInfo), '("ownerDocument", DOMNodeOwnerDocumentPropertyInfo), '("parentElement", DOMNodeParentElementPropertyInfo), '("parentNode", DOMNodeParentNodePropertyInfo), '("previousSibling", DOMNodePreviousSiblingPropertyInfo), '("textContent", DOMNodeTextContentPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
dOMNodeBaseUri :: AttrLabelProxy "baseUri"
dOMNodeBaseUri = AttrLabelProxy

dOMNodeChildNodes :: AttrLabelProxy "childNodes"
dOMNodeChildNodes = AttrLabelProxy

dOMNodeFirstChild :: AttrLabelProxy "firstChild"
dOMNodeFirstChild = AttrLabelProxy

dOMNodeLastChild :: AttrLabelProxy "lastChild"
dOMNodeLastChild = AttrLabelProxy

dOMNodeNextSibling :: AttrLabelProxy "nextSibling"
dOMNodeNextSibling = AttrLabelProxy

dOMNodeNodeName :: AttrLabelProxy "nodeName"
dOMNodeNodeName = AttrLabelProxy

dOMNodeNodeType :: AttrLabelProxy "nodeType"
dOMNodeNodeType = AttrLabelProxy

dOMNodeNodeValue :: AttrLabelProxy "nodeValue"
dOMNodeNodeValue = AttrLabelProxy

dOMNodeOwnerDocument :: AttrLabelProxy "ownerDocument"
dOMNodeOwnerDocument = AttrLabelProxy

dOMNodeParentElement :: AttrLabelProxy "parentElement"
dOMNodeParentElement = AttrLabelProxy

dOMNodeParentNode :: AttrLabelProxy "parentNode"
dOMNodeParentNode = AttrLabelProxy

dOMNodePreviousSibling :: AttrLabelProxy "previousSibling"
dOMNodePreviousSibling = AttrLabelProxy

dOMNodeTextContent :: AttrLabelProxy "textContent"
dOMNodeTextContent = AttrLabelProxy

#endif

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

#endif

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

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

{-# DEPRECATED dOMNodeAppendChild ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMNodeAppendChild ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMNode a, IsDOMNode b) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMNode.DOMNode'
    -> b
    -- ^ /@newChild@/: A t'GI.WebKit2WebExtension.Objects.DOMNode.DOMNode'
    -> m DOMNode
    -- ^ __Returns:__ A t'GI.WebKit2WebExtension.Objects.DOMNode.DOMNode' /(Can throw 'Data.GI.Base.GError.GError')/
dOMNodeAppendChild :: a -> b -> m DOMNode
dOMNodeAppendChild self :: a
self newChild :: b
newChild = 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 DOMNode
self' <- a -> IO (Ptr DOMNode)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr DOMNode
newChild' <- b -> IO (Ptr DOMNode)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
newChild
    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 DOMNode -> Ptr DOMNode -> Ptr (Ptr GError) -> IO (Ptr DOMNode)
webkit_dom_node_append_child Ptr DOMNode
self' Ptr DOMNode
newChild'
        Text -> Ptr DOMNode -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dOMNodeAppendChild" 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
DOMNode) Ptr DOMNode
result
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
        b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
newChild
        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 DOMNodeAppendChildMethodInfo
instance (signature ~ (b -> m DOMNode), MonadIO m, IsDOMNode a, IsDOMNode b) => O.MethodInfo DOMNodeAppendChildMethodInfo a signature where
    overloadedMethod = dOMNodeAppendChild

#endif

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

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

{-# DEPRECATED dOMNodeCloneNodeWithError ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
-- 
-- /Since: 2.14/
dOMNodeCloneNodeWithError ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMNode a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMNode.DOMNode'
    -> Bool
    -- ^ /@deep@/: A t'P.Bool'
    -> m DOMNode
    -- ^ __Returns:__ A t'GI.WebKit2WebExtension.Objects.DOMNode.DOMNode' /(Can throw 'Data.GI.Base.GError.GError')/
dOMNodeCloneNodeWithError :: a -> Bool -> m DOMNode
dOMNodeCloneNodeWithError self :: a
self deep :: Bool
deep = 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 DOMNode
self' <- a -> IO (Ptr DOMNode)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    let deep' :: CInt
deep' = (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
deep
    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 DOMNode -> CInt -> Ptr (Ptr GError) -> IO (Ptr DOMNode)
webkit_dom_node_clone_node_with_error Ptr DOMNode
self' CInt
deep'
        Text -> Ptr DOMNode -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dOMNodeCloneNodeWithError" 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
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 DOMNodeCloneNodeWithErrorMethodInfo
instance (signature ~ (Bool -> m DOMNode), MonadIO m, IsDOMNode a) => O.MethodInfo DOMNodeCloneNodeWithErrorMethodInfo a signature where
    overloadedMethod = dOMNodeCloneNodeWithError

#endif

-- method DOMNode::compare_document_position
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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 = "other"
--           , 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 TUInt16)
-- throws : False
-- Skip return : False

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

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

#if defined(ENABLE_OVERLOADING)
data DOMNodeCompareDocumentPositionMethodInfo
instance (signature ~ (b -> m Word16), MonadIO m, IsDOMNode a, IsDOMNode b) => O.MethodInfo DOMNodeCompareDocumentPositionMethodInfo a signature where
    overloadedMethod = dOMNodeCompareDocumentPosition

#endif

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

foreign import ccall "webkit_dom_node_contains" webkit_dom_node_contains :: 
    Ptr DOMNode ->                          -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMNode"})
    Ptr DOMNode ->                          -- other : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMNode"})
    IO CInt

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

#if defined(ENABLE_OVERLOADING)
data DOMNodeContainsMethodInfo
instance (signature ~ (b -> m Bool), MonadIO m, IsDOMNode a, IsDOMNode b) => O.MethodInfo DOMNodeContainsMethodInfo a signature where
    overloadedMethod = dOMNodeContains

#endif

-- method DOMNode::get_base_uri
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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 TUTF8)
-- throws : False
-- Skip return : False

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

{-# DEPRECATED dOMNodeGetBaseUri ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMNodeGetBaseUri ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMNode a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMNode.DOMNode'
    -> m T.Text
    -- ^ __Returns:__ A @/gchar/@
dOMNodeGetBaseUri :: a -> m Text
dOMNodeGetBaseUri self :: 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 DOMNode
self' <- a -> IO (Ptr DOMNode)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
result <- Ptr DOMNode -> IO CString
webkit_dom_node_get_base_uri Ptr DOMNode
self'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dOMNodeGetBaseUri" 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 DOMNodeGetBaseUriMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsDOMNode a) => O.MethodInfo DOMNodeGetBaseUriMethodInfo a signature where
    overloadedMethod = dOMNodeGetBaseUri

#endif

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

foreign import ccall "webkit_dom_node_get_child_nodes" webkit_dom_node_get_child_nodes :: 
    Ptr DOMNode ->                          -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMNode"})
    IO (Ptr WebKit2WebExtension.DOMNodeList.DOMNodeList)

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

#if defined(ENABLE_OVERLOADING)
data DOMNodeGetChildNodesMethodInfo
instance (signature ~ (m WebKit2WebExtension.DOMNodeList.DOMNodeList), MonadIO m, IsDOMNode a) => O.MethodInfo DOMNodeGetChildNodesMethodInfo a signature where
    overloadedMethod = dOMNodeGetChildNodes

#endif

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

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

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

#if defined(ENABLE_OVERLOADING)
data DOMNodeGetFirstChildMethodInfo
instance (signature ~ (m DOMNode), MonadIO m, IsDOMNode a) => O.MethodInfo DOMNodeGetFirstChildMethodInfo a signature where
    overloadedMethod = dOMNodeGetFirstChild

#endif

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

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

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

#if defined(ENABLE_OVERLOADING)
data DOMNodeGetLastChildMethodInfo
instance (signature ~ (m DOMNode), MonadIO m, IsDOMNode a) => O.MethodInfo DOMNodeGetLastChildMethodInfo a signature where
    overloadedMethod = dOMNodeGetLastChild

#endif

-- method DOMNode::get_local_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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 TUTF8)
-- throws : False
-- Skip return : False

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

{-# DEPRECATED dOMNodeGetLocalName ["(Since version 2.14)","Use 'GI.WebKit2WebExtension.Objects.DOMAttr.dOMAttrGetLocalName' or 'GI.WebKit2WebExtension.Objects.DOMElement.dOMElementGetLocalName' instead."] #-}
-- | /No description available in the introspection data./
dOMNodeGetLocalName ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMNode a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMNode.DOMNode'
    -> m T.Text
    -- ^ __Returns:__ A @/gchar/@
dOMNodeGetLocalName :: a -> m Text
dOMNodeGetLocalName self :: 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 DOMNode
self' <- a -> IO (Ptr DOMNode)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
result <- Ptr DOMNode -> IO CString
webkit_dom_node_get_local_name Ptr DOMNode
self'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dOMNodeGetLocalName" 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 DOMNodeGetLocalNameMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsDOMNode a) => O.MethodInfo DOMNodeGetLocalNameMethodInfo a signature where
    overloadedMethod = dOMNodeGetLocalName

#endif

-- method DOMNode::get_namespace_uri
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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 TUTF8)
-- throws : False
-- Skip return : False

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

{-# DEPRECATED dOMNodeGetNamespaceUri ["(Since version 2.14)","Use 'GI.WebKit2WebExtension.Objects.DOMAttr.dOMAttrGetNamespaceUri' or 'GI.WebKit2WebExtension.Objects.DOMElement.dOMElementGetNamespaceUri' instead."] #-}
-- | /No description available in the introspection data./
dOMNodeGetNamespaceUri ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMNode a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMNode.DOMNode'
    -> m T.Text
    -- ^ __Returns:__ A @/gchar/@
dOMNodeGetNamespaceUri :: a -> m Text
dOMNodeGetNamespaceUri self :: 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 DOMNode
self' <- a -> IO (Ptr DOMNode)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
result <- Ptr DOMNode -> IO CString
webkit_dom_node_get_namespace_uri Ptr DOMNode
self'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dOMNodeGetNamespaceUri" 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 DOMNodeGetNamespaceUriMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsDOMNode a) => O.MethodInfo DOMNodeGetNamespaceUriMethodInfo a signature where
    overloadedMethod = dOMNodeGetNamespaceUri

#endif

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

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

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

#if defined(ENABLE_OVERLOADING)
data DOMNodeGetNextSiblingMethodInfo
instance (signature ~ (m DOMNode), MonadIO m, IsDOMNode a) => O.MethodInfo DOMNodeGetNextSiblingMethodInfo a signature where
    overloadedMethod = dOMNodeGetNextSibling

#endif

-- method DOMNode::get_node_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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 TUTF8)
-- throws : False
-- Skip return : False

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

{-# DEPRECATED dOMNodeGetNodeName ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMNodeGetNodeName ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMNode a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMNode.DOMNode'
    -> m T.Text
    -- ^ __Returns:__ A @/gchar/@
dOMNodeGetNodeName :: a -> m Text
dOMNodeGetNodeName self :: 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 DOMNode
self' <- a -> IO (Ptr DOMNode)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
result <- Ptr DOMNode -> IO CString
webkit_dom_node_get_node_name Ptr DOMNode
self'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dOMNodeGetNodeName" 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 DOMNodeGetNodeNameMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsDOMNode a) => O.MethodInfo DOMNodeGetNodeNameMethodInfo a signature where
    overloadedMethod = dOMNodeGetNodeName

#endif

-- method DOMNode::get_node_type
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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 TUInt16)
-- throws : False
-- Skip return : False

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

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

#if defined(ENABLE_OVERLOADING)
data DOMNodeGetNodeTypeMethodInfo
instance (signature ~ (m Word16), MonadIO m, IsDOMNode a) => O.MethodInfo DOMNodeGetNodeTypeMethodInfo a signature where
    overloadedMethod = dOMNodeGetNodeType

#endif

-- method DOMNode::get_node_value
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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 TUTF8)
-- throws : False
-- Skip return : False

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

{-# DEPRECATED dOMNodeGetNodeValue ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMNodeGetNodeValue ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMNode a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMNode.DOMNode'
    -> m T.Text
    -- ^ __Returns:__ A @/gchar/@
dOMNodeGetNodeValue :: a -> m Text
dOMNodeGetNodeValue self :: 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 DOMNode
self' <- a -> IO (Ptr DOMNode)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
result <- Ptr DOMNode -> IO CString
webkit_dom_node_get_node_value Ptr DOMNode
self'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dOMNodeGetNodeValue" 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 DOMNodeGetNodeValueMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsDOMNode a) => O.MethodInfo DOMNodeGetNodeValueMethodInfo a signature where
    overloadedMethod = dOMNodeGetNodeValue

#endif

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

foreign import ccall "webkit_dom_node_get_owner_document" webkit_dom_node_get_owner_document :: 
    Ptr DOMNode ->                          -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMNode"})
    IO (Ptr WebKit2WebExtension.DOMDocument.DOMDocument)

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

#if defined(ENABLE_OVERLOADING)
data DOMNodeGetOwnerDocumentMethodInfo
instance (signature ~ (m WebKit2WebExtension.DOMDocument.DOMDocument), MonadIO m, IsDOMNode a) => O.MethodInfo DOMNodeGetOwnerDocumentMethodInfo a signature where
    overloadedMethod = dOMNodeGetOwnerDocument

#endif

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

foreign import ccall "webkit_dom_node_get_parent_element" webkit_dom_node_get_parent_element :: 
    Ptr DOMNode ->                          -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMNode"})
    IO (Ptr WebKit2WebExtension.DOMElement.DOMElement)

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

#if defined(ENABLE_OVERLOADING)
data DOMNodeGetParentElementMethodInfo
instance (signature ~ (m WebKit2WebExtension.DOMElement.DOMElement), MonadIO m, IsDOMNode a) => O.MethodInfo DOMNodeGetParentElementMethodInfo a signature where
    overloadedMethod = dOMNodeGetParentElement

#endif

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

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

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

#if defined(ENABLE_OVERLOADING)
data DOMNodeGetParentNodeMethodInfo
instance (signature ~ (m DOMNode), MonadIO m, IsDOMNode a) => O.MethodInfo DOMNodeGetParentNodeMethodInfo a signature where
    overloadedMethod = dOMNodeGetParentNode

#endif

-- method DOMNode::get_prefix
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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 TUTF8)
-- throws : False
-- Skip return : False

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

{-# DEPRECATED dOMNodeGetPrefix ["(Since version 2.14)","Use 'GI.WebKit2WebExtension.Objects.DOMAttr.dOMAttrGetPrefix' or 'GI.WebKit2WebExtension.Objects.DOMElement.dOMElementGetPrefix' instead."] #-}
-- | /No description available in the introspection data./
dOMNodeGetPrefix ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMNode a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMNode.DOMNode'
    -> m T.Text
    -- ^ __Returns:__ A @/gchar/@
dOMNodeGetPrefix :: a -> m Text
dOMNodeGetPrefix self :: 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 DOMNode
self' <- a -> IO (Ptr DOMNode)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
result <- Ptr DOMNode -> IO CString
webkit_dom_node_get_prefix Ptr DOMNode
self'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dOMNodeGetPrefix" 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 DOMNodeGetPrefixMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsDOMNode a) => O.MethodInfo DOMNodeGetPrefixMethodInfo a signature where
    overloadedMethod = dOMNodeGetPrefix

#endif

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

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

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

#if defined(ENABLE_OVERLOADING)
data DOMNodeGetPreviousSiblingMethodInfo
instance (signature ~ (m DOMNode), MonadIO m, IsDOMNode a) => O.MethodInfo DOMNodeGetPreviousSiblingMethodInfo a signature where
    overloadedMethod = dOMNodeGetPreviousSibling

#endif

-- method DOMNode::get_text_content
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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 TUTF8)
-- throws : False
-- Skip return : False

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

{-# DEPRECATED dOMNodeGetTextContent ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMNodeGetTextContent ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMNode a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMNode.DOMNode'
    -> m T.Text
    -- ^ __Returns:__ A @/gchar/@
dOMNodeGetTextContent :: a -> m Text
dOMNodeGetTextContent self :: 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 DOMNode
self' <- a -> IO (Ptr DOMNode)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
result <- Ptr DOMNode -> IO CString
webkit_dom_node_get_text_content Ptr DOMNode
self'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dOMNodeGetTextContent" 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 DOMNodeGetTextContentMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsDOMNode a) => O.MethodInfo DOMNodeGetTextContentMethodInfo a signature where
    overloadedMethod = dOMNodeGetTextContent

#endif

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

foreign import ccall "webkit_dom_node_has_child_nodes" webkit_dom_node_has_child_nodes :: 
    Ptr DOMNode ->                          -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMNode"})
    IO CInt

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

#if defined(ENABLE_OVERLOADING)
data DOMNodeHasChildNodesMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsDOMNode a) => O.MethodInfo DOMNodeHasChildNodesMethodInfo a signature where
    overloadedMethod = dOMNodeHasChildNodes

#endif

-- method DOMNode::insert_before
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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 = "newChild"
--           , 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 = "refChild"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit2WebExtension" , name = "DOMNode" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMNode" , 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_node_insert_before" webkit_dom_node_insert_before :: 
    Ptr DOMNode ->                          -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMNode"})
    Ptr DOMNode ->                          -- newChild : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMNode"})
    Ptr DOMNode ->                          -- refChild : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMNode"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr DOMNode)

{-# DEPRECATED dOMNodeInsertBefore ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMNodeInsertBefore ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMNode a, IsDOMNode b, IsDOMNode c) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMNode.DOMNode'
    -> b
    -- ^ /@newChild@/: A t'GI.WebKit2WebExtension.Objects.DOMNode.DOMNode'
    -> Maybe (c)
    -- ^ /@refChild@/: A t'GI.WebKit2WebExtension.Objects.DOMNode.DOMNode'
    -> m DOMNode
    -- ^ __Returns:__ A t'GI.WebKit2WebExtension.Objects.DOMNode.DOMNode' /(Can throw 'Data.GI.Base.GError.GError')/
dOMNodeInsertBefore :: a -> b -> Maybe c -> m DOMNode
dOMNodeInsertBefore self :: a
self newChild :: b
newChild refChild :: Maybe c
refChild = 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 DOMNode
self' <- a -> IO (Ptr DOMNode)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr DOMNode
newChild' <- b -> IO (Ptr DOMNode)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
newChild
    Ptr DOMNode
maybeRefChild <- case Maybe c
refChild of
        Nothing -> Ptr DOMNode -> IO (Ptr DOMNode)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr DOMNode
forall a. Ptr a
nullPtr
        Just jRefChild :: c
jRefChild -> do
            Ptr DOMNode
jRefChild' <- c -> IO (Ptr DOMNode)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
jRefChild
            Ptr DOMNode -> IO (Ptr DOMNode)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr DOMNode
jRefChild'
    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 DOMNode
-> Ptr DOMNode
-> Ptr DOMNode
-> Ptr (Ptr GError)
-> IO (Ptr DOMNode)
webkit_dom_node_insert_before Ptr DOMNode
self' Ptr DOMNode
newChild' Ptr DOMNode
maybeRefChild
        Text -> Ptr DOMNode -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dOMNodeInsertBefore" 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
DOMNode) Ptr DOMNode
result
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
        b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
newChild
        Maybe c -> (c -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe c
refChild c -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
        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 DOMNodeInsertBeforeMethodInfo
instance (signature ~ (b -> Maybe (c) -> m DOMNode), MonadIO m, IsDOMNode a, IsDOMNode b, IsDOMNode c) => O.MethodInfo DOMNodeInsertBeforeMethodInfo a signature where
    overloadedMethod = dOMNodeInsertBefore

#endif

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

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

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

#if defined(ENABLE_OVERLOADING)
data DOMNodeIsDefaultNamespaceMethodInfo
instance (signature ~ (T.Text -> m Bool), MonadIO m, IsDOMNode a) => O.MethodInfo DOMNodeIsDefaultNamespaceMethodInfo a signature where
    overloadedMethod = dOMNodeIsDefaultNamespace

#endif

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

foreign import ccall "webkit_dom_node_is_equal_node" webkit_dom_node_is_equal_node :: 
    Ptr DOMNode ->                          -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMNode"})
    Ptr DOMNode ->                          -- other : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMNode"})
    IO CInt

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

#if defined(ENABLE_OVERLOADING)
data DOMNodeIsEqualNodeMethodInfo
instance (signature ~ (b -> m Bool), MonadIO m, IsDOMNode a, IsDOMNode b) => O.MethodInfo DOMNodeIsEqualNodeMethodInfo a signature where
    overloadedMethod = dOMNodeIsEqualNode

#endif

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

foreign import ccall "webkit_dom_node_is_same_node" webkit_dom_node_is_same_node :: 
    Ptr DOMNode ->                          -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMNode"})
    Ptr DOMNode ->                          -- other : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMNode"})
    IO CInt

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

#if defined(ENABLE_OVERLOADING)
data DOMNodeIsSameNodeMethodInfo
instance (signature ~ (b -> m Bool), MonadIO m, IsDOMNode a, IsDOMNode b) => O.MethodInfo DOMNodeIsSameNodeMethodInfo a signature where
    overloadedMethod = dOMNodeIsSameNode

#endif

-- method DOMNode::is_supported
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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 = "feature"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #gchar" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "version"
--           , 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 (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_node_is_supported" webkit_dom_node_is_supported :: 
    Ptr DOMNode ->                          -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMNode"})
    CString ->                              -- feature : TBasicType TUTF8
    CString ->                              -- version : TBasicType TUTF8
    IO CInt

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

#if defined(ENABLE_OVERLOADING)
data DOMNodeIsSupportedMethodInfo
instance (signature ~ (T.Text -> T.Text -> m Bool), MonadIO m, IsDOMNode a) => O.MethodInfo DOMNodeIsSupportedMethodInfo a signature where
    overloadedMethod = dOMNodeIsSupported

#endif

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

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

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

#if defined(ENABLE_OVERLOADING)
data DOMNodeLookupNamespaceUriMethodInfo
instance (signature ~ (T.Text -> m T.Text), MonadIO m, IsDOMNode a) => O.MethodInfo DOMNodeLookupNamespaceUriMethodInfo a signature where
    overloadedMethod = dOMNodeLookupNamespaceUri

#endif

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

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

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

#if defined(ENABLE_OVERLOADING)
data DOMNodeLookupPrefixMethodInfo
instance (signature ~ (T.Text -> m T.Text), MonadIO m, IsDOMNode a) => O.MethodInfo DOMNodeLookupPrefixMethodInfo a signature where
    overloadedMethod = dOMNodeLookupPrefix

#endif

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

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

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

#if defined(ENABLE_OVERLOADING)
data DOMNodeNormalizeMethodInfo
instance (signature ~ (m ()), MonadIO m, IsDOMNode a) => O.MethodInfo DOMNodeNormalizeMethodInfo a signature where
    overloadedMethod = dOMNodeNormalize

#endif

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

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

{-# DEPRECATED dOMNodeRemoveChild ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMNodeRemoveChild ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMNode a, IsDOMNode b) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMNode.DOMNode'
    -> b
    -- ^ /@oldChild@/: A t'GI.WebKit2WebExtension.Objects.DOMNode.DOMNode'
    -> m DOMNode
    -- ^ __Returns:__ A t'GI.WebKit2WebExtension.Objects.DOMNode.DOMNode' /(Can throw 'Data.GI.Base.GError.GError')/
dOMNodeRemoveChild :: a -> b -> m DOMNode
dOMNodeRemoveChild self :: a
self oldChild :: b
oldChild = 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 DOMNode
self' <- a -> IO (Ptr DOMNode)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr DOMNode
oldChild' <- b -> IO (Ptr DOMNode)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
oldChild
    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 DOMNode -> Ptr DOMNode -> Ptr (Ptr GError) -> IO (Ptr DOMNode)
webkit_dom_node_remove_child Ptr DOMNode
self' Ptr DOMNode
oldChild'
        Text -> Ptr DOMNode -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dOMNodeRemoveChild" 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
DOMNode) Ptr DOMNode
result
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
        b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
oldChild
        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 DOMNodeRemoveChildMethodInfo
instance (signature ~ (b -> m DOMNode), MonadIO m, IsDOMNode a, IsDOMNode b) => O.MethodInfo DOMNodeRemoveChildMethodInfo a signature where
    overloadedMethod = dOMNodeRemoveChild

#endif

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

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

{-# DEPRECATED dOMNodeReplaceChild ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMNodeReplaceChild ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMNode a, IsDOMNode b, IsDOMNode c) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMNode.DOMNode'
    -> b
    -- ^ /@newChild@/: A t'GI.WebKit2WebExtension.Objects.DOMNode.DOMNode'
    -> c
    -- ^ /@oldChild@/: A t'GI.WebKit2WebExtension.Objects.DOMNode.DOMNode'
    -> m DOMNode
    -- ^ __Returns:__ A t'GI.WebKit2WebExtension.Objects.DOMNode.DOMNode' /(Can throw 'Data.GI.Base.GError.GError')/
dOMNodeReplaceChild :: a -> b -> c -> m DOMNode
dOMNodeReplaceChild self :: a
self newChild :: b
newChild oldChild :: c
oldChild = 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 DOMNode
self' <- a -> IO (Ptr DOMNode)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr DOMNode
newChild' <- b -> IO (Ptr DOMNode)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
newChild
    Ptr DOMNode
oldChild' <- c -> IO (Ptr DOMNode)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
oldChild
    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 DOMNode
-> Ptr DOMNode
-> Ptr DOMNode
-> Ptr (Ptr GError)
-> IO (Ptr DOMNode)
webkit_dom_node_replace_child Ptr DOMNode
self' Ptr DOMNode
newChild' Ptr DOMNode
oldChild'
        Text -> Ptr DOMNode -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dOMNodeReplaceChild" 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
DOMNode) Ptr DOMNode
result
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
        b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
newChild
        c -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr c
oldChild
        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 DOMNodeReplaceChildMethodInfo
instance (signature ~ (b -> c -> m DOMNode), MonadIO m, IsDOMNode a, IsDOMNode b, IsDOMNode c) => O.MethodInfo DOMNodeReplaceChildMethodInfo a signature where
    overloadedMethod = dOMNodeReplaceChild

#endif

-- method DOMNode::set_node_value
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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 = "value"
--           , 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_node_set_node_value" webkit_dom_node_set_node_value :: 
    Ptr DOMNode ->                          -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMNode"})
    CString ->                              -- value : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO ()

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

#if defined(ENABLE_OVERLOADING)
data DOMNodeSetNodeValueMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsDOMNode a) => O.MethodInfo DOMNodeSetNodeValueMethodInfo a signature where
    overloadedMethod = dOMNodeSetNodeValue

#endif

-- method DOMNode::set_prefix
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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 = "value"
--           , 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_node_set_prefix" webkit_dom_node_set_prefix :: 
    Ptr DOMNode ->                          -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMNode"})
    CString ->                              -- value : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO ()

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

#if defined(ENABLE_OVERLOADING)
data DOMNodeSetPrefixMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsDOMNode a) => O.MethodInfo DOMNodeSetPrefixMethodInfo a signature where
    overloadedMethod = dOMNodeSetPrefix

#endif

-- method DOMNode::set_text_content
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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 = "value"
--           , 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_node_set_text_content" webkit_dom_node_set_text_content :: 
    Ptr DOMNode ->                          -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMNode"})
    CString ->                              -- value : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO ()

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

#if defined(ENABLE_OVERLOADING)
data DOMNodeSetTextContentMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsDOMNode a) => O.MethodInfo DOMNodeSetTextContentMethodInfo a signature where
    overloadedMethod = dOMNodeSetTextContent

#endif

-- method DOMNode::for_js_value
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "value"
--           , argType =
--               TInterface Name { namespace = "JavaScriptCore" , name = "Value" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #JSCValue" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "WebKit2WebExtension" , name = "DOMNode" })
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_node_for_js_value" webkit_dom_node_for_js_value :: 
    Ptr JavaScriptCore.Value.Value ->       -- value : TInterface (Name {namespace = "JavaScriptCore", name = "Value"})
    IO (Ptr DOMNode)

-- | Get the t'GI.WebKit2WebExtension.Objects.DOMNode.DOMNode' for the DOM node referenced by /@value@/.
-- 
-- /Since: 2.22/
dOMNodeForJsValue ::
    (B.CallStack.HasCallStack, MonadIO m, JavaScriptCore.Value.IsValue a) =>
    a
    -- ^ /@value@/: a t'GI.JavaScriptCore.Objects.Value.Value'
    -> m DOMNode
    -- ^ __Returns:__ a t'GI.WebKit2WebExtension.Objects.DOMNode.DOMNode', or 'P.Nothing' if /@value@/ doesn\'t reference a DOM node.
dOMNodeForJsValue :: a -> m DOMNode
dOMNodeForJsValue value :: a
value = 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 Value
value' <- a -> IO (Ptr Value)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
value
    Ptr DOMNode
result <- Ptr Value -> IO (Ptr DOMNode)
webkit_dom_node_for_js_value Ptr Value
value'
    Text -> Ptr DOMNode -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dOMNodeForJsValue" 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
DOMNode) Ptr DOMNode
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
value
    DOMNode -> IO DOMNode
forall (m :: * -> *) a. Monad m => a -> m a
return DOMNode
result'

#if defined(ENABLE_OVERLOADING)
#endif