module Graphics.UI.Gtk.WebKit.DOM.NodeList
(nodeListItem, nodeListGetLength, NodeList, NodeListClass,
castToNodeList, gTypeNodeList, toNodeList)
where
import System.Glib.FFI
import System.Glib.UTFString
import Control.Applicative
import Graphics.UI.Gtk.WebKit.Types
import System.Glib.GError
import Graphics.UI.Gtk.WebKit.DOM.EventM
nodeListItem ::
(NodeListClass self) => self -> Word -> IO (Maybe Node)
nodeListItem self index
= maybeNull (makeNewGObject mkNode)
((\(NodeList arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_node_list_item argPtr1 arg2) (toNodeList self)
(fromIntegral index))
nodeListGetLength :: (NodeListClass self) => self -> IO Word
nodeListGetLength self
= fromIntegral <$>
((\(NodeList arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_node_list_get_length argPtr1) (toNodeList self))
foreign import ccall safe "webkit_dom_node_list_item"
webkit_dom_node_list_item :: ((Ptr NodeList) -> (CULong -> (IO (Ptr Node))))
foreign import ccall safe "webkit_dom_node_list_get_length"
webkit_dom_node_list_get_length :: ((Ptr NodeList) -> (IO CULong))