module Graphics.UI.Gtk.WebKit.DOM.HTMLOptionsCollection(
namedItem,
setSelectedIndex,
getSelectedIndex,
HTMLOptionsCollection,
castToHTMLOptionsCollection,
gTypeHTMLOptionsCollection,
HTMLOptionsCollectionClass,
toHTMLOptionsCollection,
) where
import Prelude hiding (drop, error, print)
import Data.Typeable (Typeable)
import Foreign.Marshal (maybePeek, maybeWith)
import System.Glib.FFI (maybeNull, withForeignPtr, nullForeignPtr, Ptr, nullPtr, castPtr, Word, Int64, Word64, CChar(..), CInt(..), CUInt(..), CLong(..), CULong(..), CLLong(..), CULLong(..), CShort(..), CUShort(..), CFloat(..), CDouble(..), toBool, fromBool)
import System.Glib.UTFString (GlibString(..), readUTFString)
import Control.Applicative ((<$>))
import Control.Monad (void)
import Control.Monad.IO.Class (MonadIO(..))
import System.Glib.GError
import Graphics.UI.Gtk.WebKit.DOM.EventTargetClosures
import Graphics.UI.Gtk.WebKit.DOM.EventM
import Graphics.UI.Gtk.WebKit.Types
import Graphics.UI.Gtk.WebKit.DOM.Enums
namedItem ::
(MonadIO m, HTMLOptionsCollectionClass self, GlibString string) =>
self -> string -> m (Maybe Node)
namedItem self name
= liftIO
(maybeNull (makeNewGObject mkNode)
(withUTFString name $
\ namePtr ->
(\(HTMLOptionsCollection arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_options_collection_named_item argPtr1 arg2)
(toHTMLOptionsCollection self)
namePtr))
setSelectedIndex ::
(MonadIO m, HTMLOptionsCollectionClass self) => self -> Int -> m ()
setSelectedIndex self val
= liftIO
((\(HTMLOptionsCollection arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_options_collection_set_selected_index argPtr1 arg2)
(toHTMLOptionsCollection self)
(fromIntegral val))
getSelectedIndex ::
(MonadIO m, HTMLOptionsCollectionClass self) => self -> m Int
getSelectedIndex self
= liftIO
(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))