module Graphics.UI.Gtk.WebKit.DOM.HTMLCollection
(htmlCollectionItem,
htmlCollectionNamedItem,
htmlCollectionGetLength, HTMLCollection, HTMLCollectionClass,
castToHTMLCollection, gTypeHTMLCollection, toHTMLCollection)
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
htmlCollectionItem ::
(HTMLCollectionClass self) => self -> Word -> IO (Maybe Node)
htmlCollectionItem self index
= maybeNull (makeNewGObject mkNode)
((\(HTMLCollection arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_collection_item argPtr1 arg2) (toHTMLCollection self)
(fromIntegral index))
htmlCollectionNamedItem ::
(HTMLCollectionClass self, GlibString string) =>
self -> string -> IO (Maybe Node)
htmlCollectionNamedItem self name
= maybeNull (makeNewGObject mkNode)
(withUTFString name $
\ namePtr ->
(\(HTMLCollection arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_collection_named_item argPtr1 arg2)
(toHTMLCollection self)
namePtr)
htmlCollectionGetLength ::
(HTMLCollectionClass self) => self -> IO Word
htmlCollectionGetLength self
= fromIntegral <$>
((\(HTMLCollection arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_collection_get_length argPtr1)
(toHTMLCollection self))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLCollection.h webkit_dom_html_collection_item"
webkit_dom_html_collection_item :: ((Ptr HTMLCollection) -> (CULong -> (IO (Ptr Node))))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLCollection.h webkit_dom_html_collection_named_item"
webkit_dom_html_collection_named_item :: ((Ptr HTMLCollection) -> ((Ptr CChar) -> (IO (Ptr Node))))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLCollection.h webkit_dom_html_collection_get_length"
webkit_dom_html_collection_get_length :: ((Ptr HTMLCollection) -> (IO CULong))