module Graphics.UI.Gtk.WebKit.DOM.HTMLOptionElement(
setDisabled,
getDisabled,
getForm,
setLabel,
getLabel,
setDefaultSelected,
getDefaultSelected,
setSelected,
getSelected,
setValue,
getValue,
getText,
getIndex,
HTMLOptionElement,
castToHTMLOptionElement,
gTypeHTMLOptionElement,
HTMLOptionElementClass,
toHTMLOptionElement,
) 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
setDisabled ::
(MonadIO m, HTMLOptionElementClass self) => self -> Bool -> m ()
setDisabled self val
= liftIO
((\(HTMLOptionElement arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_option_element_set_disabled argPtr1 arg2)
(toHTMLOptionElement self)
(fromBool val))
getDisabled ::
(MonadIO m, HTMLOptionElementClass self) => self -> m Bool
getDisabled self
= liftIO
(toBool <$>
((\(HTMLOptionElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_option_element_get_disabled argPtr1)
(toHTMLOptionElement self)))
getForm ::
(MonadIO m, HTMLOptionElementClass self) =>
self -> m (Maybe HTMLFormElement)
getForm self
= liftIO
(maybeNull (makeNewGObject mkHTMLFormElement)
((\(HTMLOptionElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_option_element_get_form argPtr1)
(toHTMLOptionElement self)))
setLabel ::
(MonadIO m, HTMLOptionElementClass self, GlibString string) =>
self -> string -> m ()
setLabel self val
= liftIO
(withUTFString val $
\ valPtr ->
(\(HTMLOptionElement arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_option_element_set_label argPtr1 arg2)
(toHTMLOptionElement self)
valPtr)
getLabel ::
(MonadIO m, HTMLOptionElementClass self, GlibString string) =>
self -> m string
getLabel self
= liftIO
(((\(HTMLOptionElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_option_element_get_label argPtr1)
(toHTMLOptionElement self))
>>=
readUTFString)
setDefaultSelected ::
(MonadIO m, HTMLOptionElementClass self) => self -> Bool -> m ()
setDefaultSelected self val
= liftIO
((\(HTMLOptionElement arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_option_element_set_default_selected argPtr1 arg2)
(toHTMLOptionElement self)
(fromBool val))
getDefaultSelected ::
(MonadIO m, HTMLOptionElementClass self) => self -> m Bool
getDefaultSelected self
= liftIO
(toBool <$>
((\(HTMLOptionElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_option_element_get_default_selected argPtr1)
(toHTMLOptionElement self)))
setSelected ::
(MonadIO m, HTMLOptionElementClass self) => self -> Bool -> m ()
setSelected self val
= liftIO
((\(HTMLOptionElement arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_option_element_set_selected argPtr1 arg2)
(toHTMLOptionElement self)
(fromBool val))
getSelected ::
(MonadIO m, HTMLOptionElementClass self) => self -> m Bool
getSelected self
= liftIO
(toBool <$>
((\(HTMLOptionElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_option_element_get_selected argPtr1)
(toHTMLOptionElement self)))
setValue ::
(MonadIO m, HTMLOptionElementClass self, GlibString string) =>
self -> string -> m ()
setValue self val
= liftIO
(withUTFString val $
\ valPtr ->
(\(HTMLOptionElement arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_option_element_set_value argPtr1 arg2)
(toHTMLOptionElement self)
valPtr)
getValue ::
(MonadIO m, HTMLOptionElementClass self, GlibString string) =>
self -> m string
getValue self
= liftIO
(((\(HTMLOptionElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_option_element_get_value argPtr1)
(toHTMLOptionElement self))
>>=
readUTFString)
getText ::
(MonadIO m, HTMLOptionElementClass self, GlibString string) =>
self -> m string
getText self
= liftIO
(((\(HTMLOptionElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_option_element_get_text argPtr1)
(toHTMLOptionElement self))
>>=
readUTFString)
getIndex ::
(MonadIO m, HTMLOptionElementClass self) => self -> m Int
getIndex self
= liftIO
(fromIntegral <$>
((\(HTMLOptionElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_option_element_get_index argPtr1)
(toHTMLOptionElement self)))
foreign import ccall safe "webkit_dom_html_option_element_set_disabled"
webkit_dom_html_option_element_set_disabled :: ((Ptr HTMLOptionElement) -> (CInt -> (IO ())))
foreign import ccall safe "webkit_dom_html_option_element_get_disabled"
webkit_dom_html_option_element_get_disabled :: ((Ptr HTMLOptionElement) -> (IO CInt))
foreign import ccall safe "webkit_dom_html_option_element_get_form"
webkit_dom_html_option_element_get_form :: ((Ptr HTMLOptionElement) -> (IO (Ptr HTMLFormElement)))
foreign import ccall safe "webkit_dom_html_option_element_set_label"
webkit_dom_html_option_element_set_label :: ((Ptr HTMLOptionElement) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "webkit_dom_html_option_element_get_label"
webkit_dom_html_option_element_get_label :: ((Ptr HTMLOptionElement) -> (IO (Ptr CChar)))
foreign import ccall safe "webkit_dom_html_option_element_set_default_selected"
webkit_dom_html_option_element_set_default_selected :: ((Ptr HTMLOptionElement) -> (CInt -> (IO ())))
foreign import ccall safe "webkit_dom_html_option_element_get_default_selected"
webkit_dom_html_option_element_get_default_selected :: ((Ptr HTMLOptionElement) -> (IO CInt))
foreign import ccall safe "webkit_dom_html_option_element_set_selected"
webkit_dom_html_option_element_set_selected :: ((Ptr HTMLOptionElement) -> (CInt -> (IO ())))
foreign import ccall safe "webkit_dom_html_option_element_get_selected"
webkit_dom_html_option_element_get_selected :: ((Ptr HTMLOptionElement) -> (IO CInt))
foreign import ccall safe "webkit_dom_html_option_element_set_value"
webkit_dom_html_option_element_set_value :: ((Ptr HTMLOptionElement) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "webkit_dom_html_option_element_get_value"
webkit_dom_html_option_element_get_value :: ((Ptr HTMLOptionElement) -> (IO (Ptr CChar)))
foreign import ccall safe "webkit_dom_html_option_element_get_text"
webkit_dom_html_option_element_get_text :: ((Ptr HTMLOptionElement) -> (IO (Ptr CChar)))
foreign import ccall safe "webkit_dom_html_option_element_get_index"
webkit_dom_html_option_element_get_index :: ((Ptr HTMLOptionElement) -> (IO CLong))