{- |
Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
License    : LGPL-2.1
Maintainer : Iñaki García Etxebarria (garetxe@gmail.com)
-}

module GI.WebKit.Objects.DOMNodeFilter
    ( 

-- * Exported types
    DOMNodeFilter(..)                       ,
    DOMNodeFilterK                          ,
    toDOMNodeFilter                         ,
    noDOMNodeFilter                         ,


 -- * Methods
-- ** dOMNodeFilterAcceptNode
    dOMNodeFilterAcceptNode                 ,




    ) where

import Prelude ()
import Data.GI.Base.ShortPrelude

import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map

import GI.WebKit.Types
import GI.WebKit.Callbacks
import qualified GI.GObject as GObject

newtype DOMNodeFilter = DOMNodeFilter (ForeignPtr DOMNodeFilter)
foreign import ccall "webkit_dom_node_filter_get_type"
    c_webkit_dom_node_filter_get_type :: IO GType

type instance ParentTypes DOMNodeFilter = DOMNodeFilterParentTypes
type DOMNodeFilterParentTypes = '[DOMObject, GObject.Object]

instance GObject DOMNodeFilter where
    gobjectIsInitiallyUnowned _ = False
    gobjectType _ = c_webkit_dom_node_filter_get_type
    

class GObject o => DOMNodeFilterK o
instance (GObject o, IsDescendantOf DOMNodeFilter o) => DOMNodeFilterK o

toDOMNodeFilter :: DOMNodeFilterK o => o -> IO DOMNodeFilter
toDOMNodeFilter = unsafeCastTo DOMNodeFilter

noDOMNodeFilter :: Maybe DOMNodeFilter
noDOMNodeFilter = Nothing

type instance AttributeList DOMNodeFilter = DOMNodeFilterAttributeList
type DOMNodeFilterAttributeList = ('[ '("core-object", DOMObjectCoreObjectPropertyInfo)] :: [(Symbol, *)])

type instance SignalList DOMNodeFilter = DOMNodeFilterSignalList
type DOMNodeFilterSignalList = ('[ '("notify", GObject.ObjectNotifySignalInfo), '("notify::[property]", GObjectNotifySignalInfo)] :: [(Symbol, *)])

-- method DOMNodeFilter::accept_node
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMNodeFilter", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "n", argType = TInterface "WebKit" "DOMNode", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMNodeFilter", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "n", argType = TInterface "WebKit" "DOMNode", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TInt16
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_node_filter_accept_node" webkit_dom_node_filter_accept_node :: 
    Ptr DOMNodeFilter ->                    -- _obj : TInterface "WebKit" "DOMNodeFilter"
    Ptr DOMNode ->                          -- n : TInterface "WebKit" "DOMNode"
    IO Int16


dOMNodeFilterAcceptNode ::
    (MonadIO m, DOMNodeFilterK a, DOMNodeK b) =>
    a ->                                    -- _obj
    b ->                                    -- n
    m Int16
dOMNodeFilterAcceptNode _obj n = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let n' = unsafeManagedPtrCastPtr n
    result <- webkit_dom_node_filter_accept_node _obj' n'
    touchManagedPtr _obj
    touchManagedPtr n
    return result