module Graphics.UI.Gtk.WebKit.DOM.HTMLInputElement(
stepUp,
stepDown,
checkValidity,
setCustomValidity,
select,
setRangeText4,
setValueForUser,
setAccept,
getAccept,
setAlt,
getAlt,
setAutocomplete,
getAutocomplete,
setAutofocus,
getAutofocus,
setDefaultChecked,
getDefaultChecked,
setChecked,
getChecked,
setDirName,
getDirName,
setDisabled,
getDisabled,
getForm,
setFiles,
getFiles,
setFormAction,
getFormAction,
setFormEnctype,
getFormEnctype,
setFormMethod,
getFormMethod,
setFormNoValidate,
getFormNoValidate,
setFormTarget,
getFormTarget,
setHeight,
getHeight,
setIndeterminate,
getIndeterminate,
getList,
setMax,
getMax,
setMaxLength,
getMaxLength,
setMin,
getMin,
setMultiple,
getMultiple,
setName,
getName,
setPattern,
getPattern,
setPlaceholder,
getPlaceholder,
setReadOnly,
getReadOnly,
setRequired,
getRequired,
setSize,
getSize,
setSrc,
getSrc,
setStep,
getStep,
setDefaultValue,
getDefaultValue,
setValue,
getValue,
setValueAsNumber,
getValueAsNumber,
setWidth,
getWidth,
getWillValidate,
getValidity,
getValidationMessage,
getLabels,
setAlign,
getAlign,
setUseMap,
getUseMap,
setIncremental,
getIncremental,
setAutocorrect,
getAutocorrect,
setAutocapitalize,
getAutocapitalize,
HTMLInputElement,
castToHTMLInputElement,
gTypeHTMLInputElement,
HTMLInputElementClass,
toHTMLInputElement,
) 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
stepUp ::
(MonadIO m, HTMLInputElementClass self) => self -> Int -> m ()
stepUp self n
= liftIO
(propagateGError $
\ errorPtr_ ->
(\(HTMLInputElement arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_step_up argPtr1 arg2 arg3)
(toHTMLInputElement self)
(fromIntegral n)
errorPtr_)
stepDown ::
(MonadIO m, HTMLInputElementClass self) => self -> Int -> m ()
stepDown self n
= liftIO
(propagateGError $
\ errorPtr_ ->
(\(HTMLInputElement arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_step_down argPtr1 arg2 arg3)
(toHTMLInputElement self)
(fromIntegral n)
errorPtr_)
checkValidity ::
(MonadIO m, HTMLInputElementClass self) => self -> m Bool
checkValidity self
= liftIO
(toBool <$>
((\(HTMLInputElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_check_validity argPtr1)
(toHTMLInputElement self)))
setCustomValidity ::
(MonadIO m, HTMLInputElementClass self, GlibString string) =>
self -> (Maybe string) -> m ()
setCustomValidity self error
= liftIO
(maybeWith withUTFString error $
\ errorPtr ->
(\(HTMLInputElement arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_set_custom_validity argPtr1 arg2)
(toHTMLInputElement self)
errorPtr)
select :: (MonadIO m, HTMLInputElementClass self) => self -> m ()
select self
= liftIO
((\(HTMLInputElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_select argPtr1)
(toHTMLInputElement self))
setRangeText4 ::
(MonadIO m, HTMLInputElementClass self, GlibString string) =>
self -> string -> Word -> Word -> string -> m ()
setRangeText4 self replacement start end selectionMode
= liftIO
(propagateGError $
\ errorPtr_ ->
withUTFString selectionMode $
\ selectionModePtr ->
withUTFString replacement $
\ replacementPtr ->
(\(HTMLInputElement arg1) arg2 arg3 arg4 arg5 arg6 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_set_range_text argPtr1 arg2 arg3 arg4 arg5 arg6)
(toHTMLInputElement self)
replacementPtr
(fromIntegral start)
(fromIntegral end)
selectionModePtr
errorPtr_)
setValueForUser ::
(MonadIO m, HTMLInputElementClass self, GlibString string) =>
self -> (Maybe string) -> m ()
setValueForUser self value
= liftIO
(maybeWith withUTFString value $
\ valuePtr ->
(\(HTMLInputElement arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_set_value_for_user argPtr1 arg2)
(toHTMLInputElement self)
valuePtr)
setAccept ::
(MonadIO m, HTMLInputElementClass self, GlibString string) =>
self -> string -> m ()
setAccept self val
= liftIO
(withUTFString val $
\ valPtr ->
(\(HTMLInputElement arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_set_accept argPtr1 arg2)
(toHTMLInputElement self)
valPtr)
getAccept ::
(MonadIO m, HTMLInputElementClass self, GlibString string) =>
self -> m string
getAccept self
= liftIO
(((\(HTMLInputElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_get_accept argPtr1)
(toHTMLInputElement self))
>>=
readUTFString)
setAlt ::
(MonadIO m, HTMLInputElementClass self, GlibString string) =>
self -> string -> m ()
setAlt self val
= liftIO
(withUTFString val $
\ valPtr ->
(\(HTMLInputElement arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_set_alt argPtr1 arg2)
(toHTMLInputElement self)
valPtr)
getAlt ::
(MonadIO m, HTMLInputElementClass self, GlibString string) =>
self -> m string
getAlt self
= liftIO
(((\(HTMLInputElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_get_alt argPtr1)
(toHTMLInputElement self))
>>=
readUTFString)
setAutocomplete ::
(MonadIO m, HTMLInputElementClass self, GlibString string) =>
self -> string -> m ()
setAutocomplete self val
= liftIO
(withUTFString val $
\ valPtr ->
(\(HTMLInputElement arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_set_autocomplete argPtr1 arg2)
(toHTMLInputElement self)
valPtr)
getAutocomplete ::
(MonadIO m, HTMLInputElementClass self, GlibString string) =>
self -> m string
getAutocomplete self
= liftIO
(((\(HTMLInputElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_get_autocomplete argPtr1)
(toHTMLInputElement self))
>>=
readUTFString)
setAutofocus ::
(MonadIO m, HTMLInputElementClass self) => self -> Bool -> m ()
setAutofocus self val
= liftIO
((\(HTMLInputElement arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_set_autofocus argPtr1 arg2)
(toHTMLInputElement self)
(fromBool val))
getAutofocus ::
(MonadIO m, HTMLInputElementClass self) => self -> m Bool
getAutofocus self
= liftIO
(toBool <$>
((\(HTMLInputElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_get_autofocus argPtr1)
(toHTMLInputElement self)))
setDefaultChecked ::
(MonadIO m, HTMLInputElementClass self) => self -> Bool -> m ()
setDefaultChecked self val
= liftIO
((\(HTMLInputElement arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_set_default_checked argPtr1 arg2)
(toHTMLInputElement self)
(fromBool val))
getDefaultChecked ::
(MonadIO m, HTMLInputElementClass self) => self -> m Bool
getDefaultChecked self
= liftIO
(toBool <$>
((\(HTMLInputElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_get_default_checked argPtr1)
(toHTMLInputElement self)))
setChecked ::
(MonadIO m, HTMLInputElementClass self) => self -> Bool -> m ()
setChecked self val
= liftIO
((\(HTMLInputElement arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_set_checked argPtr1 arg2)
(toHTMLInputElement self)
(fromBool val))
getChecked ::
(MonadIO m, HTMLInputElementClass self) => self -> m Bool
getChecked self
= liftIO
(toBool <$>
((\(HTMLInputElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_get_checked argPtr1)
(toHTMLInputElement self)))
setDirName ::
(MonadIO m, HTMLInputElementClass self, GlibString string) =>
self -> string -> m ()
setDirName self val
= liftIO
(withUTFString val $
\ valPtr ->
(\(HTMLInputElement arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_set_dir_name argPtr1 arg2)
(toHTMLInputElement self)
valPtr)
getDirName ::
(MonadIO m, HTMLInputElementClass self, GlibString string) =>
self -> m string
getDirName self
= liftIO
(((\(HTMLInputElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_get_dir_name argPtr1)
(toHTMLInputElement self))
>>=
readUTFString)
setDisabled ::
(MonadIO m, HTMLInputElementClass self) => self -> Bool -> m ()
setDisabled self val
= liftIO
((\(HTMLInputElement arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_set_disabled argPtr1 arg2)
(toHTMLInputElement self)
(fromBool val))
getDisabled ::
(MonadIO m, HTMLInputElementClass self) => self -> m Bool
getDisabled self
= liftIO
(toBool <$>
((\(HTMLInputElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_get_disabled argPtr1)
(toHTMLInputElement self)))
getForm ::
(MonadIO m, HTMLInputElementClass self) =>
self -> m (Maybe HTMLFormElement)
getForm self
= liftIO
(maybeNull (makeNewGObject mkHTMLFormElement)
((\(HTMLInputElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_get_form argPtr1)
(toHTMLInputElement self)))
setFiles ::
(MonadIO m, FileListClass val, HTMLInputElementClass self) =>
self -> Maybe val -> m ()
setFiles self val
= liftIO
((\(HTMLInputElement arg1) (FileList arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->webkit_dom_html_input_element_set_files argPtr1 argPtr2)
(toHTMLInputElement self)
(maybe (FileList nullForeignPtr) toFileList val))
getFiles ::
(MonadIO m, HTMLInputElementClass self) =>
self -> m (Maybe FileList)
getFiles self
= liftIO
(maybeNull (makeNewGObject mkFileList)
((\(HTMLInputElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_get_files argPtr1)
(toHTMLInputElement self)))
setFormAction ::
(MonadIO m, HTMLInputElementClass self, GlibString string) =>
self -> string -> m ()
setFormAction self val
= liftIO
(withUTFString val $
\ valPtr ->
(\(HTMLInputElement arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_set_form_action argPtr1 arg2)
(toHTMLInputElement self)
valPtr)
getFormAction ::
(MonadIO m, HTMLInputElementClass self, GlibString string) =>
self -> m string
getFormAction self
= liftIO
(((\(HTMLInputElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_get_form_action argPtr1)
(toHTMLInputElement self))
>>=
readUTFString)
setFormEnctype ::
(MonadIO m, HTMLInputElementClass self, GlibString string) =>
self -> (Maybe string) -> m ()
setFormEnctype self val
= liftIO
(maybeWith withUTFString val $
\ valPtr ->
(\(HTMLInputElement arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_set_form_enctype argPtr1 arg2)
(toHTMLInputElement self)
valPtr)
getFormEnctype ::
(MonadIO m, HTMLInputElementClass self, GlibString string) =>
self -> m (Maybe string)
getFormEnctype self
= liftIO
(((\(HTMLInputElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_get_form_enctype argPtr1)
(toHTMLInputElement self))
>>=
maybePeek readUTFString)
setFormMethod ::
(MonadIO m, HTMLInputElementClass self, GlibString string) =>
self -> (Maybe string) -> m ()
setFormMethod self val
= liftIO
(maybeWith withUTFString val $
\ valPtr ->
(\(HTMLInputElement arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_set_form_method argPtr1 arg2)
(toHTMLInputElement self)
valPtr)
getFormMethod ::
(MonadIO m, HTMLInputElementClass self, GlibString string) =>
self -> m (Maybe string)
getFormMethod self
= liftIO
(((\(HTMLInputElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_get_form_method argPtr1)
(toHTMLInputElement self))
>>=
maybePeek readUTFString)
setFormNoValidate ::
(MonadIO m, HTMLInputElementClass self) => self -> Bool -> m ()
setFormNoValidate self val
= liftIO
((\(HTMLInputElement arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_set_form_no_validate argPtr1 arg2)
(toHTMLInputElement self)
(fromBool val))
getFormNoValidate ::
(MonadIO m, HTMLInputElementClass self) => self -> m Bool
getFormNoValidate self
= liftIO
(toBool <$>
((\(HTMLInputElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_get_form_no_validate argPtr1)
(toHTMLInputElement self)))
setFormTarget ::
(MonadIO m, HTMLInputElementClass self, GlibString string) =>
self -> string -> m ()
setFormTarget self val
= liftIO
(withUTFString val $
\ valPtr ->
(\(HTMLInputElement arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_set_form_target argPtr1 arg2)
(toHTMLInputElement self)
valPtr)
getFormTarget ::
(MonadIO m, HTMLInputElementClass self, GlibString string) =>
self -> m string
getFormTarget self
= liftIO
(((\(HTMLInputElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_get_form_target argPtr1)
(toHTMLInputElement self))
>>=
readUTFString)
setHeight ::
(MonadIO m, HTMLInputElementClass self) => self -> Word -> m ()
setHeight self val
= liftIO
((\(HTMLInputElement arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_set_height argPtr1 arg2)
(toHTMLInputElement self)
(fromIntegral val))
getHeight ::
(MonadIO m, HTMLInputElementClass self) => self -> m Word
getHeight self
= liftIO
(fromIntegral <$>
((\(HTMLInputElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_get_height argPtr1)
(toHTMLInputElement self)))
setIndeterminate ::
(MonadIO m, HTMLInputElementClass self) => self -> Bool -> m ()
setIndeterminate self val
= liftIO
((\(HTMLInputElement arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_set_indeterminate argPtr1 arg2)
(toHTMLInputElement self)
(fromBool val))
getIndeterminate ::
(MonadIO m, HTMLInputElementClass self) => self -> m Bool
getIndeterminate self
= liftIO
(toBool <$>
((\(HTMLInputElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_get_indeterminate argPtr1)
(toHTMLInputElement self)))
getList ::
(MonadIO m, HTMLInputElementClass self) =>
self -> m (Maybe HTMLElement)
getList self
= liftIO
(maybeNull (makeNewGObject mkHTMLElement)
((\(HTMLInputElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_get_list argPtr1)
(toHTMLInputElement self)))
setMax ::
(MonadIO m, HTMLInputElementClass self, GlibString string) =>
self -> string -> m ()
setMax self val
= liftIO
(withUTFString val $
\ valPtr ->
(\(HTMLInputElement arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_set_max argPtr1 arg2)
(toHTMLInputElement self)
valPtr)
getMax ::
(MonadIO m, HTMLInputElementClass self, GlibString string) =>
self -> m string
getMax self
= liftIO
(((\(HTMLInputElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_get_max argPtr1)
(toHTMLInputElement self))
>>=
readUTFString)
setMaxLength ::
(MonadIO m, HTMLInputElementClass self) => self -> Int -> m ()
setMaxLength self val
= liftIO
(propagateGError $
\ errorPtr_ ->
(\(HTMLInputElement arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_set_max_length argPtr1 arg2 arg3)
(toHTMLInputElement self)
(fromIntegral val)
errorPtr_)
getMaxLength ::
(MonadIO m, HTMLInputElementClass self) => self -> m Int
getMaxLength self
= liftIO
(fromIntegral <$>
((\(HTMLInputElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_get_max_length argPtr1)
(toHTMLInputElement self)))
setMin ::
(MonadIO m, HTMLInputElementClass self, GlibString string) =>
self -> string -> m ()
setMin self val
= liftIO
(withUTFString val $
\ valPtr ->
(\(HTMLInputElement arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_set_min argPtr1 arg2)
(toHTMLInputElement self)
valPtr)
getMin ::
(MonadIO m, HTMLInputElementClass self, GlibString string) =>
self -> m string
getMin self
= liftIO
(((\(HTMLInputElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_get_min argPtr1)
(toHTMLInputElement self))
>>=
readUTFString)
setMultiple ::
(MonadIO m, HTMLInputElementClass self) => self -> Bool -> m ()
setMultiple self val
= liftIO
((\(HTMLInputElement arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_set_multiple argPtr1 arg2)
(toHTMLInputElement self)
(fromBool val))
getMultiple ::
(MonadIO m, HTMLInputElementClass self) => self -> m Bool
getMultiple self
= liftIO
(toBool <$>
((\(HTMLInputElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_get_multiple argPtr1)
(toHTMLInputElement self)))
setName ::
(MonadIO m, HTMLInputElementClass self, GlibString string) =>
self -> string -> m ()
setName self val
= liftIO
(withUTFString val $
\ valPtr ->
(\(HTMLInputElement arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_set_name argPtr1 arg2)
(toHTMLInputElement self)
valPtr)
getName ::
(MonadIO m, HTMLInputElementClass self, GlibString string) =>
self -> m string
getName self
= liftIO
(((\(HTMLInputElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_get_name argPtr1)
(toHTMLInputElement self))
>>=
readUTFString)
setPattern ::
(MonadIO m, HTMLInputElementClass self, GlibString string) =>
self -> string -> m ()
setPattern self val
= liftIO
(withUTFString val $
\ valPtr ->
(\(HTMLInputElement arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_set_pattern argPtr1 arg2)
(toHTMLInputElement self)
valPtr)
getPattern ::
(MonadIO m, HTMLInputElementClass self, GlibString string) =>
self -> m string
getPattern self
= liftIO
(((\(HTMLInputElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_get_pattern argPtr1)
(toHTMLInputElement self))
>>=
readUTFString)
setPlaceholder ::
(MonadIO m, HTMLInputElementClass self, GlibString string) =>
self -> string -> m ()
setPlaceholder self val
= liftIO
(withUTFString val $
\ valPtr ->
(\(HTMLInputElement arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_set_placeholder argPtr1 arg2)
(toHTMLInputElement self)
valPtr)
getPlaceholder ::
(MonadIO m, HTMLInputElementClass self, GlibString string) =>
self -> m string
getPlaceholder self
= liftIO
(((\(HTMLInputElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_get_placeholder argPtr1)
(toHTMLInputElement self))
>>=
readUTFString)
setReadOnly ::
(MonadIO m, HTMLInputElementClass self) => self -> Bool -> m ()
setReadOnly self val
= liftIO
((\(HTMLInputElement arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_set_read_only argPtr1 arg2)
(toHTMLInputElement self)
(fromBool val))
getReadOnly ::
(MonadIO m, HTMLInputElementClass self) => self -> m Bool
getReadOnly self
= liftIO
(toBool <$>
((\(HTMLInputElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_get_read_only argPtr1)
(toHTMLInputElement self)))
setRequired ::
(MonadIO m, HTMLInputElementClass self) => self -> Bool -> m ()
setRequired self val
= liftIO
((\(HTMLInputElement arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_set_required argPtr1 arg2)
(toHTMLInputElement self)
(fromBool val))
getRequired ::
(MonadIO m, HTMLInputElementClass self) => self -> m Bool
getRequired self
= liftIO
(toBool <$>
((\(HTMLInputElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_get_required argPtr1)
(toHTMLInputElement self)))
setSize ::
(MonadIO m, HTMLInputElementClass self) => self -> Word -> m ()
setSize self val
= liftIO
(propagateGError $
\ errorPtr_ ->
(\(HTMLInputElement arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_set_size argPtr1 arg2 arg3)
(toHTMLInputElement self)
(fromIntegral val)
errorPtr_)
getSize ::
(MonadIO m, HTMLInputElementClass self) => self -> m Word
getSize self
= liftIO
(fromIntegral <$>
((\(HTMLInputElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_get_size argPtr1)
(toHTMLInputElement self)))
setSrc ::
(MonadIO m, HTMLInputElementClass self, GlibString string) =>
self -> string -> m ()
setSrc self val
= liftIO
(withUTFString val $
\ valPtr ->
(\(HTMLInputElement arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_set_src argPtr1 arg2)
(toHTMLInputElement self)
valPtr)
getSrc ::
(MonadIO m, HTMLInputElementClass self, GlibString string) =>
self -> m string
getSrc self
= liftIO
(((\(HTMLInputElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_get_src argPtr1)
(toHTMLInputElement self))
>>=
readUTFString)
setStep ::
(MonadIO m, HTMLInputElementClass self, GlibString string) =>
self -> string -> m ()
setStep self val
= liftIO
(withUTFString val $
\ valPtr ->
(\(HTMLInputElement arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_set_step argPtr1 arg2)
(toHTMLInputElement self)
valPtr)
getStep ::
(MonadIO m, HTMLInputElementClass self, GlibString string) =>
self -> m string
getStep self
= liftIO
(((\(HTMLInputElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_get_step argPtr1)
(toHTMLInputElement self))
>>=
readUTFString)
setDefaultValue ::
(MonadIO m, HTMLInputElementClass self, GlibString string) =>
self -> (Maybe string) -> m ()
setDefaultValue self val
= liftIO
(maybeWith withUTFString val $
\ valPtr ->
(\(HTMLInputElement arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_set_default_value argPtr1 arg2)
(toHTMLInputElement self)
valPtr)
getDefaultValue ::
(MonadIO m, HTMLInputElementClass self, GlibString string) =>
self -> m (Maybe string)
getDefaultValue self
= liftIO
(((\(HTMLInputElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_get_default_value argPtr1)
(toHTMLInputElement self))
>>=
maybePeek readUTFString)
setValue ::
(MonadIO m, HTMLInputElementClass self, GlibString string) =>
self -> (Maybe string) -> m ()
setValue self val
= liftIO
(maybeWith withUTFString val $
\ valPtr ->
(\(HTMLInputElement arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_set_value argPtr1 arg2)
(toHTMLInputElement self)
valPtr)
getValue ::
(MonadIO m, HTMLInputElementClass self, GlibString string) =>
self -> m (Maybe string)
getValue self
= liftIO
(((\(HTMLInputElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_get_value argPtr1)
(toHTMLInputElement self))
>>=
maybePeek readUTFString)
setValueAsNumber ::
(MonadIO m, HTMLInputElementClass self) => self -> Double -> m ()
setValueAsNumber self val
= liftIO
(propagateGError $
\ errorPtr_ ->
(\(HTMLInputElement arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_set_value_as_number argPtr1 arg2 arg3)
(toHTMLInputElement self)
(realToFrac val)
errorPtr_)
getValueAsNumber ::
(MonadIO m, HTMLInputElementClass self) => self -> m Double
getValueAsNumber self
= liftIO
(realToFrac <$>
((\(HTMLInputElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_get_value_as_number argPtr1)
(toHTMLInputElement self)))
setWidth ::
(MonadIO m, HTMLInputElementClass self) => self -> Word -> m ()
setWidth self val
= liftIO
((\(HTMLInputElement arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_set_width argPtr1 arg2)
(toHTMLInputElement self)
(fromIntegral val))
getWidth ::
(MonadIO m, HTMLInputElementClass self) => self -> m Word
getWidth self
= liftIO
(fromIntegral <$>
((\(HTMLInputElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_get_width argPtr1)
(toHTMLInputElement self)))
getWillValidate ::
(MonadIO m, HTMLInputElementClass self) => self -> m Bool
getWillValidate self
= liftIO
(toBool <$>
((\(HTMLInputElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_get_will_validate argPtr1)
(toHTMLInputElement self)))
getValidity ::
(MonadIO m, HTMLInputElementClass self) =>
self -> m (Maybe ValidityState)
getValidity self
= liftIO
(maybeNull (makeNewGObject mkValidityState)
((\(HTMLInputElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_get_validity argPtr1)
(toHTMLInputElement self)))
getValidationMessage ::
(MonadIO m, HTMLInputElementClass self, GlibString string) =>
self -> m string
getValidationMessage self
= liftIO
(((\(HTMLInputElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_get_validation_message argPtr1)
(toHTMLInputElement self))
>>=
readUTFString)
getLabels ::
(MonadIO m, HTMLInputElementClass self) =>
self -> m (Maybe NodeList)
getLabels self
= liftIO
(maybeNull (makeNewGObject mkNodeList)
((\(HTMLInputElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_get_labels argPtr1)
(toHTMLInputElement self)))
setAlign ::
(MonadIO m, HTMLInputElementClass self, GlibString string) =>
self -> string -> m ()
setAlign self val
= liftIO
(withUTFString val $
\ valPtr ->
(\(HTMLInputElement arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_set_align argPtr1 arg2)
(toHTMLInputElement self)
valPtr)
getAlign ::
(MonadIO m, HTMLInputElementClass self, GlibString string) =>
self -> m string
getAlign self
= liftIO
(((\(HTMLInputElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_get_align argPtr1)
(toHTMLInputElement self))
>>=
readUTFString)
setUseMap ::
(MonadIO m, HTMLInputElementClass self, GlibString string) =>
self -> string -> m ()
setUseMap self val
= liftIO
(withUTFString val $
\ valPtr ->
(\(HTMLInputElement arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_set_use_map argPtr1 arg2)
(toHTMLInputElement self)
valPtr)
getUseMap ::
(MonadIO m, HTMLInputElementClass self, GlibString string) =>
self -> m string
getUseMap self
= liftIO
(((\(HTMLInputElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_get_use_map argPtr1)
(toHTMLInputElement self))
>>=
readUTFString)
setIncremental ::
(MonadIO m, HTMLInputElementClass self) => self -> Bool -> m ()
setIncremental self val
= liftIO
((\(HTMLInputElement arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_set_incremental argPtr1 arg2)
(toHTMLInputElement self)
(fromBool val))
getIncremental ::
(MonadIO m, HTMLInputElementClass self) => self -> m Bool
getIncremental self
= liftIO
(toBool <$>
((\(HTMLInputElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_get_incremental argPtr1)
(toHTMLInputElement self)))
setAutocorrect ::
(MonadIO m, HTMLInputElementClass self) => self -> Bool -> m ()
setAutocorrect self val
= liftIO
((\(HTMLInputElement arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_set_autocorrect argPtr1 arg2)
(toHTMLInputElement self)
(fromBool val))
getAutocorrect ::
(MonadIO m, HTMLInputElementClass self) => self -> m Bool
getAutocorrect self
= liftIO
(toBool <$>
((\(HTMLInputElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_get_autocorrect argPtr1)
(toHTMLInputElement self)))
setAutocapitalize ::
(MonadIO m, HTMLInputElementClass self, GlibString string) =>
self -> (Maybe string) -> m ()
setAutocapitalize self val
= liftIO
(maybeWith withUTFString val $
\ valPtr ->
(\(HTMLInputElement arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_set_autocapitalize argPtr1 arg2)
(toHTMLInputElement self)
valPtr)
getAutocapitalize ::
(MonadIO m, HTMLInputElementClass self, GlibString string) =>
self -> m (Maybe string)
getAutocapitalize self
= liftIO
(((\(HTMLInputElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_input_element_get_autocapitalize argPtr1)
(toHTMLInputElement self))
>>=
maybePeek readUTFString)
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_step_up"
webkit_dom_html_input_element_step_up :: ((Ptr HTMLInputElement) -> (CLong -> ((Ptr (Ptr ())) -> (IO ()))))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_step_down"
webkit_dom_html_input_element_step_down :: ((Ptr HTMLInputElement) -> (CLong -> ((Ptr (Ptr ())) -> (IO ()))))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_check_validity"
webkit_dom_html_input_element_check_validity :: ((Ptr HTMLInputElement) -> (IO CInt))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_set_custom_validity"
webkit_dom_html_input_element_set_custom_validity :: ((Ptr HTMLInputElement) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_select"
webkit_dom_html_input_element_select :: ((Ptr HTMLInputElement) -> (IO ()))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_set_range_text"
webkit_dom_html_input_element_set_range_text :: ((Ptr HTMLInputElement) -> ((Ptr CChar) -> (CULong -> (CULong -> ((Ptr CChar) -> ((Ptr (Ptr ())) -> (IO ())))))))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_set_value_for_user"
webkit_dom_html_input_element_set_value_for_user :: ((Ptr HTMLInputElement) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_set_accept"
webkit_dom_html_input_element_set_accept :: ((Ptr HTMLInputElement) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_get_accept"
webkit_dom_html_input_element_get_accept :: ((Ptr HTMLInputElement) -> (IO (Ptr CChar)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_set_alt"
webkit_dom_html_input_element_set_alt :: ((Ptr HTMLInputElement) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_get_alt"
webkit_dom_html_input_element_get_alt :: ((Ptr HTMLInputElement) -> (IO (Ptr CChar)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_set_autocomplete"
webkit_dom_html_input_element_set_autocomplete :: ((Ptr HTMLInputElement) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_get_autocomplete"
webkit_dom_html_input_element_get_autocomplete :: ((Ptr HTMLInputElement) -> (IO (Ptr CChar)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_set_autofocus"
webkit_dom_html_input_element_set_autofocus :: ((Ptr HTMLInputElement) -> (CInt -> (IO ())))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_get_autofocus"
webkit_dom_html_input_element_get_autofocus :: ((Ptr HTMLInputElement) -> (IO CInt))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_set_default_checked"
webkit_dom_html_input_element_set_default_checked :: ((Ptr HTMLInputElement) -> (CInt -> (IO ())))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_get_default_checked"
webkit_dom_html_input_element_get_default_checked :: ((Ptr HTMLInputElement) -> (IO CInt))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_set_checked"
webkit_dom_html_input_element_set_checked :: ((Ptr HTMLInputElement) -> (CInt -> (IO ())))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_get_checked"
webkit_dom_html_input_element_get_checked :: ((Ptr HTMLInputElement) -> (IO CInt))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_set_dir_name"
webkit_dom_html_input_element_set_dir_name :: ((Ptr HTMLInputElement) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_get_dir_name"
webkit_dom_html_input_element_get_dir_name :: ((Ptr HTMLInputElement) -> (IO (Ptr CChar)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_set_disabled"
webkit_dom_html_input_element_set_disabled :: ((Ptr HTMLInputElement) -> (CInt -> (IO ())))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_get_disabled"
webkit_dom_html_input_element_get_disabled :: ((Ptr HTMLInputElement) -> (IO CInt))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_get_form"
webkit_dom_html_input_element_get_form :: ((Ptr HTMLInputElement) -> (IO (Ptr HTMLFormElement)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_set_files"
webkit_dom_html_input_element_set_files :: ((Ptr HTMLInputElement) -> ((Ptr FileList) -> (IO ())))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_get_files"
webkit_dom_html_input_element_get_files :: ((Ptr HTMLInputElement) -> (IO (Ptr FileList)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_set_form_action"
webkit_dom_html_input_element_set_form_action :: ((Ptr HTMLInputElement) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_get_form_action"
webkit_dom_html_input_element_get_form_action :: ((Ptr HTMLInputElement) -> (IO (Ptr CChar)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_set_form_enctype"
webkit_dom_html_input_element_set_form_enctype :: ((Ptr HTMLInputElement) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_get_form_enctype"
webkit_dom_html_input_element_get_form_enctype :: ((Ptr HTMLInputElement) -> (IO (Ptr CChar)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_set_form_method"
webkit_dom_html_input_element_set_form_method :: ((Ptr HTMLInputElement) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_get_form_method"
webkit_dom_html_input_element_get_form_method :: ((Ptr HTMLInputElement) -> (IO (Ptr CChar)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_set_form_no_validate"
webkit_dom_html_input_element_set_form_no_validate :: ((Ptr HTMLInputElement) -> (CInt -> (IO ())))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_get_form_no_validate"
webkit_dom_html_input_element_get_form_no_validate :: ((Ptr HTMLInputElement) -> (IO CInt))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_set_form_target"
webkit_dom_html_input_element_set_form_target :: ((Ptr HTMLInputElement) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_get_form_target"
webkit_dom_html_input_element_get_form_target :: ((Ptr HTMLInputElement) -> (IO (Ptr CChar)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_set_height"
webkit_dom_html_input_element_set_height :: ((Ptr HTMLInputElement) -> (CULong -> (IO ())))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_get_height"
webkit_dom_html_input_element_get_height :: ((Ptr HTMLInputElement) -> (IO CULong))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_set_indeterminate"
webkit_dom_html_input_element_set_indeterminate :: ((Ptr HTMLInputElement) -> (CInt -> (IO ())))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_get_indeterminate"
webkit_dom_html_input_element_get_indeterminate :: ((Ptr HTMLInputElement) -> (IO CInt))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_get_list"
webkit_dom_html_input_element_get_list :: ((Ptr HTMLInputElement) -> (IO (Ptr HTMLElement)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_set_max"
webkit_dom_html_input_element_set_max :: ((Ptr HTMLInputElement) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_get_max"
webkit_dom_html_input_element_get_max :: ((Ptr HTMLInputElement) -> (IO (Ptr CChar)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_set_max_length"
webkit_dom_html_input_element_set_max_length :: ((Ptr HTMLInputElement) -> (CLong -> ((Ptr (Ptr ())) -> (IO ()))))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_get_max_length"
webkit_dom_html_input_element_get_max_length :: ((Ptr HTMLInputElement) -> (IO CLong))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_set_min"
webkit_dom_html_input_element_set_min :: ((Ptr HTMLInputElement) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_get_min"
webkit_dom_html_input_element_get_min :: ((Ptr HTMLInputElement) -> (IO (Ptr CChar)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_set_multiple"
webkit_dom_html_input_element_set_multiple :: ((Ptr HTMLInputElement) -> (CInt -> (IO ())))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_get_multiple"
webkit_dom_html_input_element_get_multiple :: ((Ptr HTMLInputElement) -> (IO CInt))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_set_name"
webkit_dom_html_input_element_set_name :: ((Ptr HTMLInputElement) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_get_name"
webkit_dom_html_input_element_get_name :: ((Ptr HTMLInputElement) -> (IO (Ptr CChar)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_set_pattern"
webkit_dom_html_input_element_set_pattern :: ((Ptr HTMLInputElement) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_get_pattern"
webkit_dom_html_input_element_get_pattern :: ((Ptr HTMLInputElement) -> (IO (Ptr CChar)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_set_placeholder"
webkit_dom_html_input_element_set_placeholder :: ((Ptr HTMLInputElement) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_get_placeholder"
webkit_dom_html_input_element_get_placeholder :: ((Ptr HTMLInputElement) -> (IO (Ptr CChar)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_set_read_only"
webkit_dom_html_input_element_set_read_only :: ((Ptr HTMLInputElement) -> (CInt -> (IO ())))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_get_read_only"
webkit_dom_html_input_element_get_read_only :: ((Ptr HTMLInputElement) -> (IO CInt))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_set_required"
webkit_dom_html_input_element_set_required :: ((Ptr HTMLInputElement) -> (CInt -> (IO ())))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_get_required"
webkit_dom_html_input_element_get_required :: ((Ptr HTMLInputElement) -> (IO CInt))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_set_size"
webkit_dom_html_input_element_set_size :: ((Ptr HTMLInputElement) -> (CULong -> ((Ptr (Ptr ())) -> (IO ()))))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_get_size"
webkit_dom_html_input_element_get_size :: ((Ptr HTMLInputElement) -> (IO CULong))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_set_src"
webkit_dom_html_input_element_set_src :: ((Ptr HTMLInputElement) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_get_src"
webkit_dom_html_input_element_get_src :: ((Ptr HTMLInputElement) -> (IO (Ptr CChar)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_set_step"
webkit_dom_html_input_element_set_step :: ((Ptr HTMLInputElement) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_get_step"
webkit_dom_html_input_element_get_step :: ((Ptr HTMLInputElement) -> (IO (Ptr CChar)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_set_default_value"
webkit_dom_html_input_element_set_default_value :: ((Ptr HTMLInputElement) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_get_default_value"
webkit_dom_html_input_element_get_default_value :: ((Ptr HTMLInputElement) -> (IO (Ptr CChar)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_set_value"
webkit_dom_html_input_element_set_value :: ((Ptr HTMLInputElement) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_get_value"
webkit_dom_html_input_element_get_value :: ((Ptr HTMLInputElement) -> (IO (Ptr CChar)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_set_value_as_number"
webkit_dom_html_input_element_set_value_as_number :: ((Ptr HTMLInputElement) -> (CDouble -> ((Ptr (Ptr ())) -> (IO ()))))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_get_value_as_number"
webkit_dom_html_input_element_get_value_as_number :: ((Ptr HTMLInputElement) -> (IO CDouble))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_set_width"
webkit_dom_html_input_element_set_width :: ((Ptr HTMLInputElement) -> (CULong -> (IO ())))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_get_width"
webkit_dom_html_input_element_get_width :: ((Ptr HTMLInputElement) -> (IO CULong))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_get_will_validate"
webkit_dom_html_input_element_get_will_validate :: ((Ptr HTMLInputElement) -> (IO CInt))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_get_validity"
webkit_dom_html_input_element_get_validity :: ((Ptr HTMLInputElement) -> (IO (Ptr ValidityState)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_get_validation_message"
webkit_dom_html_input_element_get_validation_message :: ((Ptr HTMLInputElement) -> (IO (Ptr CChar)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_get_labels"
webkit_dom_html_input_element_get_labels :: ((Ptr HTMLInputElement) -> (IO (Ptr NodeList)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_set_align"
webkit_dom_html_input_element_set_align :: ((Ptr HTMLInputElement) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_get_align"
webkit_dom_html_input_element_get_align :: ((Ptr HTMLInputElement) -> (IO (Ptr CChar)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_set_use_map"
webkit_dom_html_input_element_set_use_map :: ((Ptr HTMLInputElement) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_get_use_map"
webkit_dom_html_input_element_get_use_map :: ((Ptr HTMLInputElement) -> (IO (Ptr CChar)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_set_incremental"
webkit_dom_html_input_element_set_incremental :: ((Ptr HTMLInputElement) -> (CInt -> (IO ())))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_get_incremental"
webkit_dom_html_input_element_get_incremental :: ((Ptr HTMLInputElement) -> (IO CInt))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_set_autocorrect"
webkit_dom_html_input_element_set_autocorrect :: ((Ptr HTMLInputElement) -> (CInt -> (IO ())))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_get_autocorrect"
webkit_dom_html_input_element_get_autocorrect :: ((Ptr HTMLInputElement) -> (IO CInt))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_set_autocapitalize"
webkit_dom_html_input_element_set_autocapitalize :: ((Ptr HTMLInputElement) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/HTMLInputElement.h webkit_dom_html_input_element_get_autocapitalize"
webkit_dom_html_input_element_get_autocapitalize :: ((Ptr HTMLInputElement) -> (IO (Ptr CChar)))