{-# LANGUAGE TypeApplications #-}


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

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

module GI.WebKit2WebExtension.Interfaces.DOMNodeFilter
    ( 

-- * Exported types
    DOMNodeFilter(..)                       ,
    IsDOMNodeFilter                         ,
    toDOMNodeFilter                         ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [acceptNode]("GI.WebKit2WebExtension.Interfaces.DOMNodeFilter#g:method:acceptNode"), [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getData]("GI.GObject.Objects.Object#g:method:getData"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolveDOMNodeFilterMethod              ,
#endif

-- ** acceptNode #method:acceptNode#

#if defined(ENABLE_OVERLOADING)
    DOMNodeFilterAcceptNodeMethodInfo       ,
#endif
    dOMNodeFilterAcceptNode                 ,




    ) where

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

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.Kind as DK
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R
import qualified Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT

-- Workaround for https://gitlab.haskell.org/ghc/ghc/-/issues/23392
#if MIN_VERSION_base(4,18,0)
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.Interfaces.DOMXPathNSResolver as WebKit2WebExtension.DOMXPathNSResolver
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMAttr as WebKit2WebExtension.DOMAttr
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMCDATASection as WebKit2WebExtension.DOMCDATASection
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMCSSRule as WebKit2WebExtension.DOMCSSRule
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMCSSRuleList as WebKit2WebExtension.DOMCSSRuleList
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMCSSStyleDeclaration as WebKit2WebExtension.DOMCSSStyleDeclaration
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMCSSStyleSheet as WebKit2WebExtension.DOMCSSStyleSheet
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMCharacterData as WebKit2WebExtension.DOMCharacterData
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMClientRect as WebKit2WebExtension.DOMClientRect
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMClientRectList as WebKit2WebExtension.DOMClientRectList
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMComment as WebKit2WebExtension.DOMComment
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMDOMImplementation as WebKit2WebExtension.DOMDOMImplementation
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMDOMSelection as WebKit2WebExtension.DOMDOMSelection
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMDOMTokenList as WebKit2WebExtension.DOMDOMTokenList
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMDOMWindow as WebKit2WebExtension.DOMDOMWindow
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMDocument as WebKit2WebExtension.DOMDocument
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMDocumentFragment as WebKit2WebExtension.DOMDocumentFragment
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMDocumentType as WebKit2WebExtension.DOMDocumentType
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMElement as WebKit2WebExtension.DOMElement
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMEntityReference as WebKit2WebExtension.DOMEntityReference
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMEvent as WebKit2WebExtension.DOMEvent
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMHTMLCollection as WebKit2WebExtension.DOMHTMLCollection
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMHTMLDocument as WebKit2WebExtension.DOMHTMLDocument
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMHTMLElement as WebKit2WebExtension.DOMHTMLElement
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMHTMLHeadElement as WebKit2WebExtension.DOMHTMLHeadElement
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMHTMLScriptElement as WebKit2WebExtension.DOMHTMLScriptElement
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMMediaList as WebKit2WebExtension.DOMMediaList
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMNamedNodeMap as WebKit2WebExtension.DOMNamedNodeMap
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMNode as WebKit2WebExtension.DOMNode
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMNodeIterator as WebKit2WebExtension.DOMNodeIterator
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMNodeList as WebKit2WebExtension.DOMNodeList
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMObject as WebKit2WebExtension.DOMObject
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMProcessingInstruction as WebKit2WebExtension.DOMProcessingInstruction
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMRange as WebKit2WebExtension.DOMRange
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMStyleSheet as WebKit2WebExtension.DOMStyleSheet
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMStyleSheetList as WebKit2WebExtension.DOMStyleSheetList
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMText as WebKit2WebExtension.DOMText
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMTreeWalker as WebKit2WebExtension.DOMTreeWalker
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMXPathExpression as WebKit2WebExtension.DOMXPathExpression
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMXPathResult as WebKit2WebExtension.DOMXPathResult

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

#endif

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

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

foreign import ccall "webkit_dom_node_filter_get_type"
    c_webkit_dom_node_filter_get_type :: IO B.Types.GType

instance B.Types.TypedObject DOMNodeFilter where
    glibType :: IO GType
glibType = IO GType
c_webkit_dom_node_filter_get_type

instance B.Types.GObject DOMNodeFilter

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

instance O.HasParentTypes DOMNodeFilter
type instance O.ParentTypes DOMNodeFilter = '[GObject.Object.Object]

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

-- | Convert 'DOMNodeFilter' to and from 'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue (Maybe DOMNodeFilter) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_webkit_dom_node_filter_get_type
    gvalueSet_ :: Ptr GValue -> Maybe DOMNodeFilter -> IO ()
gvalueSet_ Ptr GValue
gv Maybe DOMNodeFilter
P.Nothing = Ptr GValue -> Ptr DOMNodeFilter -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr DOMNodeFilter
forall a. Ptr a
FP.nullPtr :: FP.Ptr DOMNodeFilter)
    gvalueSet_ Ptr GValue
gv (P.Just DOMNodeFilter
obj) = DOMNodeFilter -> (Ptr DOMNodeFilter -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr DOMNodeFilter
obj (Ptr GValue -> Ptr DOMNodeFilter -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe DOMNodeFilter)
gvalueGet_ Ptr GValue
gv = do
        Ptr DOMNodeFilter
ptr <- Ptr GValue -> IO (Ptr DOMNodeFilter)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr DOMNodeFilter)
        if Ptr DOMNodeFilter
ptr Ptr DOMNodeFilter -> Ptr DOMNodeFilter -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr DOMNodeFilter
forall a. Ptr a
FP.nullPtr
        then DOMNodeFilter -> Maybe DOMNodeFilter
forall a. a -> Maybe a
P.Just (DOMNodeFilter -> Maybe DOMNodeFilter)
-> IO DOMNodeFilter -> IO (Maybe DOMNodeFilter)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr DOMNodeFilter -> DOMNodeFilter)
-> Ptr DOMNodeFilter -> IO DOMNodeFilter
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr DOMNodeFilter -> DOMNodeFilter
DOMNodeFilter Ptr DOMNodeFilter
ptr
        else Maybe DOMNodeFilter -> IO (Maybe DOMNodeFilter)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe DOMNodeFilter
forall a. Maybe a
P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList DOMNodeFilter
type instance O.AttributeList DOMNodeFilter = DOMNodeFilterAttributeList
type DOMNodeFilterAttributeList = ('[ ] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveDOMNodeFilterMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveDOMNodeFilterMethod "acceptNode" o = DOMNodeFilterAcceptNodeMethodInfo
    ResolveDOMNodeFilterMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveDOMNodeFilterMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveDOMNodeFilterMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveDOMNodeFilterMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveDOMNodeFilterMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveDOMNodeFilterMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveDOMNodeFilterMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveDOMNodeFilterMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveDOMNodeFilterMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveDOMNodeFilterMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveDOMNodeFilterMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveDOMNodeFilterMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveDOMNodeFilterMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveDOMNodeFilterMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveDOMNodeFilterMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveDOMNodeFilterMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveDOMNodeFilterMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveDOMNodeFilterMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveDOMNodeFilterMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveDOMNodeFilterMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveDOMNodeFilterMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveDOMNodeFilterMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveDOMNodeFilterMethod l o = O.MethodResolutionFailed l o

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

#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveDOMNodeFilterMethod t DOMNodeFilter, O.OverloadedMethod info DOMNodeFilter p, R.HasField t DOMNodeFilter p) => R.HasField t DOMNodeFilter p where
    getField = O.overloadedMethod @info

#endif

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

#endif

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

foreign import ccall "webkit_dom_node_filter_accept_node" webkit_dom_node_filter_accept_node :: 
    Ptr DOMNodeFilter ->                    -- filter : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMNodeFilter"})
    Ptr WebKit2WebExtension.DOMNode.DOMNode -> -- node : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMNode"})
    IO FCT.CShort

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

#if defined(ENABLE_OVERLOADING)
data DOMNodeFilterAcceptNodeMethodInfo
instance (signature ~ (b -> m FCT.CShort), MonadIO m, IsDOMNodeFilter a, WebKit2WebExtension.DOMNode.IsDOMNode b) => O.OverloadedMethod DOMNodeFilterAcceptNodeMethodInfo a signature where
    overloadedMethod = dOMNodeFilterAcceptNode

instance O.OverloadedMethodInfo DOMNodeFilterAcceptNodeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2WebExtension.Interfaces.DOMNodeFilter.dOMNodeFilterAcceptNode",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.31/docs/GI-WebKit2WebExtension-Interfaces-DOMNodeFilter.html#v:dOMNodeFilterAcceptNode"
        })


#endif

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

#endif