module Graphics.UI.Gtk.WebKit.DOM.HTMLOptionsCollection
(
htmlOptionsCollectionNamedItem,
htmlOptionsCollectionSetSelectedIndex,
htmlOptionsCollectionGetSelectedIndex, HTMLOptionsCollection,
HTMLOptionsCollectionClass, castToHTMLOptionsCollection,
gTypeHTMLOptionsCollection, toHTMLOptionsCollection)
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
htmlOptionsCollectionNamedItem ::
(HTMLOptionsCollectionClass self, GlibString string) =>
self -> string -> IO (Maybe Node)
htmlOptionsCollectionNamedItem self name
= maybeNull (makeNewGObject mkNode)
(withUTFString name $
\ namePtr ->
(\(HTMLOptionsCollection arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_options_collection_named_item argPtr1 arg2)
(toHTMLOptionsCollection self)
namePtr)
htmlOptionsCollectionSetSelectedIndex ::
(HTMLOptionsCollectionClass self) => self -> Int -> IO ()
htmlOptionsCollectionSetSelectedIndex self val
= (\(HTMLOptionsCollection arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_options_collection_set_selected_index argPtr1 arg2)
(toHTMLOptionsCollection self)
(fromIntegral val)
htmlOptionsCollectionGetSelectedIndex ::
(HTMLOptionsCollectionClass self) => self -> IO Int
htmlOptionsCollectionGetSelectedIndex self
= fromIntegral <$>
((\(HTMLOptionsCollection arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_options_collection_get_selected_index argPtr1)
(toHTMLOptionsCollection self))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLOptionsCollection.h webkit_dom_html_options_collection_named_item"
webkit_dom_html_options_collection_named_item :: ((Ptr HTMLOptionsCollection) -> ((Ptr CChar) -> (IO (Ptr Node))))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLOptionsCollection.h webkit_dom_html_options_collection_set_selected_index"
webkit_dom_html_options_collection_set_selected_index :: ((Ptr HTMLOptionsCollection) -> (CLong -> (IO ())))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLOptionsCollection.h webkit_dom_html_options_collection_get_selected_index"
webkit_dom_html_options_collection_get_selected_index :: ((Ptr HTMLOptionsCollection) -> (IO CLong))