{- |
Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
License    : LGPL-2.1
Maintainer : Iñaki García Etxebarria (garetxe@gmail.com)
-}

module GI.WebKit.Objects.DOMHTMLInputElement
    ( 

-- * Exported types
    DOMHTMLInputElement(..)                 ,
    DOMHTMLInputElementK                    ,
    toDOMHTMLInputElement                   ,
    noDOMHTMLInputElement                   ,


 -- * Methods
-- ** dOMHTMLInputElementCheckValidity
    dOMHTMLInputElementCheckValidity        ,


-- ** dOMHTMLInputElementGetAccept
    dOMHTMLInputElementGetAccept            ,


-- ** dOMHTMLInputElementGetAlign
    dOMHTMLInputElementGetAlign             ,


-- ** dOMHTMLInputElementGetAlt
    dOMHTMLInputElementGetAlt               ,


-- ** dOMHTMLInputElementGetAutocapitalize
    dOMHTMLInputElementGetAutocapitalize    ,


-- ** dOMHTMLInputElementGetAutocomplete
    dOMHTMLInputElementGetAutocomplete      ,


-- ** dOMHTMLInputElementGetAutocorrect
    dOMHTMLInputElementGetAutocorrect       ,


-- ** dOMHTMLInputElementGetAutofocus
    dOMHTMLInputElementGetAutofocus         ,


-- ** dOMHTMLInputElementGetCapture
    dOMHTMLInputElementGetCapture           ,


-- ** dOMHTMLInputElementGetChecked
    dOMHTMLInputElementGetChecked           ,


-- ** dOMHTMLInputElementGetDefaultChecked
    dOMHTMLInputElementGetDefaultChecked    ,


-- ** dOMHTMLInputElementGetDefaultValue
    dOMHTMLInputElementGetDefaultValue      ,


-- ** dOMHTMLInputElementGetDirName
    dOMHTMLInputElementGetDirName           ,


-- ** dOMHTMLInputElementGetDisabled
    dOMHTMLInputElementGetDisabled          ,


-- ** dOMHTMLInputElementGetFiles
    dOMHTMLInputElementGetFiles             ,


-- ** dOMHTMLInputElementGetForm
    dOMHTMLInputElementGetForm              ,


-- ** dOMHTMLInputElementGetFormAction
    dOMHTMLInputElementGetFormAction        ,


-- ** dOMHTMLInputElementGetFormEnctype
    dOMHTMLInputElementGetFormEnctype       ,


-- ** dOMHTMLInputElementGetFormMethod
    dOMHTMLInputElementGetFormMethod        ,


-- ** dOMHTMLInputElementGetFormNoValidate
    dOMHTMLInputElementGetFormNoValidate    ,


-- ** dOMHTMLInputElementGetFormTarget
    dOMHTMLInputElementGetFormTarget        ,


-- ** dOMHTMLInputElementGetHeight
    dOMHTMLInputElementGetHeight            ,


-- ** dOMHTMLInputElementGetIncremental
    dOMHTMLInputElementGetIncremental       ,


-- ** dOMHTMLInputElementGetIndeterminate
    dOMHTMLInputElementGetIndeterminate     ,


-- ** dOMHTMLInputElementGetLabels
    dOMHTMLInputElementGetLabels            ,


-- ** dOMHTMLInputElementGetList
    dOMHTMLInputElementGetList              ,


-- ** dOMHTMLInputElementGetMax
    dOMHTMLInputElementGetMax               ,


-- ** dOMHTMLInputElementGetMaxLength
    dOMHTMLInputElementGetMaxLength         ,


-- ** dOMHTMLInputElementGetMin
    dOMHTMLInputElementGetMin               ,


-- ** dOMHTMLInputElementGetMultiple
    dOMHTMLInputElementGetMultiple          ,


-- ** dOMHTMLInputElementGetName
    dOMHTMLInputElementGetName              ,


-- ** dOMHTMLInputElementGetPattern
    dOMHTMLInputElementGetPattern           ,


-- ** dOMHTMLInputElementGetPlaceholder
    dOMHTMLInputElementGetPlaceholder       ,


-- ** dOMHTMLInputElementGetReadOnly
    dOMHTMLInputElementGetReadOnly          ,


-- ** dOMHTMLInputElementGetRequired
    dOMHTMLInputElementGetRequired          ,


-- ** dOMHTMLInputElementGetSize
    dOMHTMLInputElementGetSize              ,


-- ** dOMHTMLInputElementGetSrc
    dOMHTMLInputElementGetSrc               ,


-- ** dOMHTMLInputElementGetStep
    dOMHTMLInputElementGetStep              ,


-- ** dOMHTMLInputElementGetUseMap
    dOMHTMLInputElementGetUseMap            ,


-- ** dOMHTMLInputElementGetValidationMessage
    dOMHTMLInputElementGetValidationMessage ,


-- ** dOMHTMLInputElementGetValidity
    dOMHTMLInputElementGetValidity          ,


-- ** dOMHTMLInputElementGetValue
    dOMHTMLInputElementGetValue             ,


-- ** dOMHTMLInputElementGetValueAsNumber
    dOMHTMLInputElementGetValueAsNumber     ,


-- ** dOMHTMLInputElementGetWebkitGrammar
    dOMHTMLInputElementGetWebkitGrammar     ,


-- ** dOMHTMLInputElementGetWebkitSpeech
    dOMHTMLInputElementGetWebkitSpeech      ,


-- ** dOMHTMLInputElementGetWebkitdirectory
    dOMHTMLInputElementGetWebkitdirectory   ,


-- ** dOMHTMLInputElementGetWidth
    dOMHTMLInputElementGetWidth             ,


-- ** dOMHTMLInputElementGetWillValidate
    dOMHTMLInputElementGetWillValidate      ,


-- ** dOMHTMLInputElementIsEdited
    dOMHTMLInputElementIsEdited             ,


-- ** dOMHTMLInputElementSelect
    dOMHTMLInputElementSelect               ,


-- ** dOMHTMLInputElementSetAccept
    dOMHTMLInputElementSetAccept            ,


-- ** dOMHTMLInputElementSetAlign
    dOMHTMLInputElementSetAlign             ,


-- ** dOMHTMLInputElementSetAlt
    dOMHTMLInputElementSetAlt               ,


-- ** dOMHTMLInputElementSetAutocapitalize
    dOMHTMLInputElementSetAutocapitalize    ,


-- ** dOMHTMLInputElementSetAutocomplete
    dOMHTMLInputElementSetAutocomplete      ,


-- ** dOMHTMLInputElementSetAutocorrect
    dOMHTMLInputElementSetAutocorrect       ,


-- ** dOMHTMLInputElementSetAutofocus
    dOMHTMLInputElementSetAutofocus         ,


-- ** dOMHTMLInputElementSetCapture
    dOMHTMLInputElementSetCapture           ,


-- ** dOMHTMLInputElementSetChecked
    dOMHTMLInputElementSetChecked           ,


-- ** dOMHTMLInputElementSetCustomValidity
    dOMHTMLInputElementSetCustomValidity    ,


-- ** dOMHTMLInputElementSetDefaultChecked
    dOMHTMLInputElementSetDefaultChecked    ,


-- ** dOMHTMLInputElementSetDefaultValue
    dOMHTMLInputElementSetDefaultValue      ,


-- ** dOMHTMLInputElementSetDirName
    dOMHTMLInputElementSetDirName           ,


-- ** dOMHTMLInputElementSetDisabled
    dOMHTMLInputElementSetDisabled          ,


-- ** dOMHTMLInputElementSetFiles
    dOMHTMLInputElementSetFiles             ,


-- ** dOMHTMLInputElementSetFormAction
    dOMHTMLInputElementSetFormAction        ,


-- ** dOMHTMLInputElementSetFormEnctype
    dOMHTMLInputElementSetFormEnctype       ,


-- ** dOMHTMLInputElementSetFormMethod
    dOMHTMLInputElementSetFormMethod        ,


-- ** dOMHTMLInputElementSetFormNoValidate
    dOMHTMLInputElementSetFormNoValidate    ,


-- ** dOMHTMLInputElementSetFormTarget
    dOMHTMLInputElementSetFormTarget        ,


-- ** dOMHTMLInputElementSetHeight
    dOMHTMLInputElementSetHeight            ,


-- ** dOMHTMLInputElementSetIncremental
    dOMHTMLInputElementSetIncremental       ,


-- ** dOMHTMLInputElementSetIndeterminate
    dOMHTMLInputElementSetIndeterminate     ,


-- ** dOMHTMLInputElementSetMax
    dOMHTMLInputElementSetMax               ,


-- ** dOMHTMLInputElementSetMaxLength
    dOMHTMLInputElementSetMaxLength         ,


-- ** dOMHTMLInputElementSetMin
    dOMHTMLInputElementSetMin               ,


-- ** dOMHTMLInputElementSetMultiple
    dOMHTMLInputElementSetMultiple          ,


-- ** dOMHTMLInputElementSetName
    dOMHTMLInputElementSetName              ,


-- ** dOMHTMLInputElementSetPattern
    dOMHTMLInputElementSetPattern           ,


-- ** dOMHTMLInputElementSetPlaceholder
    dOMHTMLInputElementSetPlaceholder       ,


-- ** dOMHTMLInputElementSetRangeText
    dOMHTMLInputElementSetRangeText         ,


-- ** dOMHTMLInputElementSetReadOnly
    dOMHTMLInputElementSetReadOnly          ,


-- ** dOMHTMLInputElementSetRequired
    dOMHTMLInputElementSetRequired          ,


-- ** dOMHTMLInputElementSetSize
    dOMHTMLInputElementSetSize              ,


-- ** dOMHTMLInputElementSetSrc
    dOMHTMLInputElementSetSrc               ,


-- ** dOMHTMLInputElementSetStep
    dOMHTMLInputElementSetStep              ,


-- ** dOMHTMLInputElementSetUseMap
    dOMHTMLInputElementSetUseMap            ,


-- ** dOMHTMLInputElementSetValue
    dOMHTMLInputElementSetValue             ,


-- ** dOMHTMLInputElementSetValueAsNumber
    dOMHTMLInputElementSetValueAsNumber     ,


-- ** dOMHTMLInputElementSetValueForUser
    dOMHTMLInputElementSetValueForUser      ,


-- ** dOMHTMLInputElementSetWebkitGrammar
    dOMHTMLInputElementSetWebkitGrammar     ,


-- ** dOMHTMLInputElementSetWebkitSpeech
    dOMHTMLInputElementSetWebkitSpeech      ,


-- ** dOMHTMLInputElementSetWebkitdirectory
    dOMHTMLInputElementSetWebkitdirectory   ,


-- ** dOMHTMLInputElementSetWidth
    dOMHTMLInputElementSetWidth             ,


-- ** dOMHTMLInputElementStepDown
    dOMHTMLInputElementStepDown             ,


-- ** dOMHTMLInputElementStepUp
    dOMHTMLInputElementStepUp               ,




 -- * Properties
-- ** Accept
    DOMHTMLInputElementAcceptPropertyInfo   ,
    constructDOMHTMLInputElementAccept      ,
    getDOMHTMLInputElementAccept            ,
    setDOMHTMLInputElementAccept            ,


-- ** Align
    DOMHTMLInputElementAlignPropertyInfo    ,
    constructDOMHTMLInputElementAlign       ,
    getDOMHTMLInputElementAlign             ,
    setDOMHTMLInputElementAlign             ,


-- ** Alt
    DOMHTMLInputElementAltPropertyInfo      ,
    constructDOMHTMLInputElementAlt         ,
    getDOMHTMLInputElementAlt               ,
    setDOMHTMLInputElementAlt               ,


-- ** Autocapitalize
    DOMHTMLInputElementAutocapitalizePropertyInfo,
    constructDOMHTMLInputElementAutocapitalize,
    getDOMHTMLInputElementAutocapitalize    ,
    setDOMHTMLInputElementAutocapitalize    ,


-- ** Autocomplete
    DOMHTMLInputElementAutocompletePropertyInfo,
    constructDOMHTMLInputElementAutocomplete,
    getDOMHTMLInputElementAutocomplete      ,
    setDOMHTMLInputElementAutocomplete      ,


-- ** Autocorrect
    DOMHTMLInputElementAutocorrectPropertyInfo,
    constructDOMHTMLInputElementAutocorrect ,
    getDOMHTMLInputElementAutocorrect       ,
    setDOMHTMLInputElementAutocorrect       ,


-- ** Autofocus
    DOMHTMLInputElementAutofocusPropertyInfo,
    constructDOMHTMLInputElementAutofocus   ,
    getDOMHTMLInputElementAutofocus         ,
    setDOMHTMLInputElementAutofocus         ,


-- ** Capture
    DOMHTMLInputElementCapturePropertyInfo  ,
    constructDOMHTMLInputElementCapture     ,
    getDOMHTMLInputElementCapture           ,
    setDOMHTMLInputElementCapture           ,


-- ** Checked
    DOMHTMLInputElementCheckedPropertyInfo  ,
    constructDOMHTMLInputElementChecked     ,
    getDOMHTMLInputElementChecked           ,
    setDOMHTMLInputElementChecked           ,


-- ** DefaultChecked
    DOMHTMLInputElementDefaultCheckedPropertyInfo,
    constructDOMHTMLInputElementDefaultChecked,
    getDOMHTMLInputElementDefaultChecked    ,
    setDOMHTMLInputElementDefaultChecked    ,


-- ** DefaultValue
    DOMHTMLInputElementDefaultValuePropertyInfo,
    constructDOMHTMLInputElementDefaultValue,
    getDOMHTMLInputElementDefaultValue      ,
    setDOMHTMLInputElementDefaultValue      ,


-- ** DirName
    DOMHTMLInputElementDirNamePropertyInfo  ,
    constructDOMHTMLInputElementDirName     ,
    getDOMHTMLInputElementDirName           ,
    setDOMHTMLInputElementDirName           ,


-- ** Disabled
    DOMHTMLInputElementDisabledPropertyInfo ,
    constructDOMHTMLInputElementDisabled    ,
    getDOMHTMLInputElementDisabled          ,
    setDOMHTMLInputElementDisabled          ,


-- ** Files
    DOMHTMLInputElementFilesPropertyInfo    ,
    getDOMHTMLInputElementFiles             ,


-- ** Form
    DOMHTMLInputElementFormPropertyInfo     ,
    getDOMHTMLInputElementForm              ,


-- ** FormAction
    DOMHTMLInputElementFormActionPropertyInfo,
    constructDOMHTMLInputElementFormAction  ,
    getDOMHTMLInputElementFormAction        ,
    setDOMHTMLInputElementFormAction        ,


-- ** FormEnctype
    DOMHTMLInputElementFormEnctypePropertyInfo,
    constructDOMHTMLInputElementFormEnctype ,
    getDOMHTMLInputElementFormEnctype       ,
    setDOMHTMLInputElementFormEnctype       ,


-- ** FormMethod
    DOMHTMLInputElementFormMethodPropertyInfo,
    constructDOMHTMLInputElementFormMethod  ,
    getDOMHTMLInputElementFormMethod        ,
    setDOMHTMLInputElementFormMethod        ,


-- ** FormNoValidate
    DOMHTMLInputElementFormNoValidatePropertyInfo,
    constructDOMHTMLInputElementFormNoValidate,
    getDOMHTMLInputElementFormNoValidate    ,
    setDOMHTMLInputElementFormNoValidate    ,


-- ** FormTarget
    DOMHTMLInputElementFormTargetPropertyInfo,
    constructDOMHTMLInputElementFormTarget  ,
    getDOMHTMLInputElementFormTarget        ,
    setDOMHTMLInputElementFormTarget        ,


-- ** Height
    DOMHTMLInputElementHeightPropertyInfo   ,
    constructDOMHTMLInputElementHeight      ,
    getDOMHTMLInputElementHeight            ,
    setDOMHTMLInputElementHeight            ,


-- ** Incremental
    DOMHTMLInputElementIncrementalPropertyInfo,
    constructDOMHTMLInputElementIncremental ,
    getDOMHTMLInputElementIncremental       ,
    setDOMHTMLInputElementIncremental       ,


-- ** Indeterminate
    DOMHTMLInputElementIndeterminatePropertyInfo,
    constructDOMHTMLInputElementIndeterminate,
    getDOMHTMLInputElementIndeterminate     ,
    setDOMHTMLInputElementIndeterminate     ,


-- ** Labels
    DOMHTMLInputElementLabelsPropertyInfo   ,
    getDOMHTMLInputElementLabels            ,


-- ** List
    DOMHTMLInputElementListPropertyInfo     ,
    getDOMHTMLInputElementList              ,


-- ** Max
    DOMHTMLInputElementMaxPropertyInfo      ,
    constructDOMHTMLInputElementMax         ,
    getDOMHTMLInputElementMax               ,
    setDOMHTMLInputElementMax               ,


-- ** MaxLength
    DOMHTMLInputElementMaxLengthPropertyInfo,
    constructDOMHTMLInputElementMaxLength   ,
    getDOMHTMLInputElementMaxLength         ,
    setDOMHTMLInputElementMaxLength         ,


-- ** Min
    DOMHTMLInputElementMinPropertyInfo      ,
    constructDOMHTMLInputElementMin         ,
    getDOMHTMLInputElementMin               ,
    setDOMHTMLInputElementMin               ,


-- ** Multiple
    DOMHTMLInputElementMultiplePropertyInfo ,
    constructDOMHTMLInputElementMultiple    ,
    getDOMHTMLInputElementMultiple          ,
    setDOMHTMLInputElementMultiple          ,


-- ** Name
    DOMHTMLInputElementNamePropertyInfo     ,
    constructDOMHTMLInputElementName        ,
    getDOMHTMLInputElementName              ,
    setDOMHTMLInputElementName              ,


-- ** Pattern
    DOMHTMLInputElementPatternPropertyInfo  ,
    constructDOMHTMLInputElementPattern     ,
    getDOMHTMLInputElementPattern           ,
    setDOMHTMLInputElementPattern           ,


-- ** Placeholder
    DOMHTMLInputElementPlaceholderPropertyInfo,
    constructDOMHTMLInputElementPlaceholder ,
    getDOMHTMLInputElementPlaceholder       ,
    setDOMHTMLInputElementPlaceholder       ,


-- ** ReadOnly
    DOMHTMLInputElementReadOnlyPropertyInfo ,
    constructDOMHTMLInputElementReadOnly    ,
    getDOMHTMLInputElementReadOnly          ,
    setDOMHTMLInputElementReadOnly          ,


-- ** Required
    DOMHTMLInputElementRequiredPropertyInfo ,
    constructDOMHTMLInputElementRequired    ,
    getDOMHTMLInputElementRequired          ,
    setDOMHTMLInputElementRequired          ,


-- ** Size
    DOMHTMLInputElementSizePropertyInfo     ,
    constructDOMHTMLInputElementSize        ,
    getDOMHTMLInputElementSize              ,
    setDOMHTMLInputElementSize              ,


-- ** Src
    DOMHTMLInputElementSrcPropertyInfo      ,
    constructDOMHTMLInputElementSrc         ,
    getDOMHTMLInputElementSrc               ,
    setDOMHTMLInputElementSrc               ,


-- ** Step
    DOMHTMLInputElementStepPropertyInfo     ,
    constructDOMHTMLInputElementStep        ,
    getDOMHTMLInputElementStep              ,
    setDOMHTMLInputElementStep              ,


-- ** Type
    DOMHTMLInputElementTypePropertyInfo     ,
    constructDOMHTMLInputElementType        ,
    getDOMHTMLInputElementType              ,
    setDOMHTMLInputElementType              ,


-- ** UseMap
    DOMHTMLInputElementUseMapPropertyInfo   ,
    constructDOMHTMLInputElementUseMap      ,
    getDOMHTMLInputElementUseMap            ,
    setDOMHTMLInputElementUseMap            ,


-- ** ValidationMessage
    DOMHTMLInputElementValidationMessagePropertyInfo,
    getDOMHTMLInputElementValidationMessage ,


-- ** Validity
    DOMHTMLInputElementValidityPropertyInfo ,
    getDOMHTMLInputElementValidity          ,


-- ** Value
    DOMHTMLInputElementValuePropertyInfo    ,
    constructDOMHTMLInputElementValue       ,
    getDOMHTMLInputElementValue             ,
    setDOMHTMLInputElementValue             ,


-- ** ValueAsNumber
    DOMHTMLInputElementValueAsNumberPropertyInfo,
    constructDOMHTMLInputElementValueAsNumber,
    getDOMHTMLInputElementValueAsNumber     ,
    setDOMHTMLInputElementValueAsNumber     ,


-- ** WebkitGrammar
    DOMHTMLInputElementWebkitGrammarPropertyInfo,
    constructDOMHTMLInputElementWebkitGrammar,
    getDOMHTMLInputElementWebkitGrammar     ,
    setDOMHTMLInputElementWebkitGrammar     ,


-- ** WebkitSpeech
    DOMHTMLInputElementWebkitSpeechPropertyInfo,
    constructDOMHTMLInputElementWebkitSpeech,
    getDOMHTMLInputElementWebkitSpeech      ,
    setDOMHTMLInputElementWebkitSpeech      ,


-- ** Webkitdirectory
    DOMHTMLInputElementWebkitdirectoryPropertyInfo,
    constructDOMHTMLInputElementWebkitdirectory,
    getDOMHTMLInputElementWebkitdirectory   ,
    setDOMHTMLInputElementWebkitdirectory   ,


-- ** Width
    DOMHTMLInputElementWidthPropertyInfo    ,
    constructDOMHTMLInputElementWidth       ,
    getDOMHTMLInputElementWidth             ,
    setDOMHTMLInputElementWidth             ,


-- ** WillValidate
    DOMHTMLInputElementWillValidatePropertyInfo,
    getDOMHTMLInputElementWillValidate      ,




    ) where

import Prelude ()
import Data.GI.Base.ShortPrelude

import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map

import GI.WebKit.Types
import GI.WebKit.Callbacks
import qualified GI.GObject as GObject

newtype DOMHTMLInputElement = DOMHTMLInputElement (ForeignPtr DOMHTMLInputElement)
foreign import ccall "webkit_dom_html_input_element_get_type"
    c_webkit_dom_html_input_element_get_type :: IO GType

type instance ParentTypes DOMHTMLInputElement = DOMHTMLInputElementParentTypes
type DOMHTMLInputElementParentTypes = '[DOMHTMLElement, DOMElement, DOMNode, DOMObject, GObject.Object, DOMEventTarget]

instance GObject DOMHTMLInputElement where
    gobjectIsInitiallyUnowned _ = False
    gobjectType _ = c_webkit_dom_html_input_element_get_type
    

class GObject o => DOMHTMLInputElementK o
instance (GObject o, IsDescendantOf DOMHTMLInputElement o) => DOMHTMLInputElementK o

toDOMHTMLInputElement :: DOMHTMLInputElementK o => o -> IO DOMHTMLInputElement
toDOMHTMLInputElement = unsafeCastTo DOMHTMLInputElement

noDOMHTMLInputElement :: Maybe DOMHTMLInputElement
noDOMHTMLInputElement = Nothing

-- VVV Prop "accept"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]

getDOMHTMLInputElementAccept :: (MonadIO m, DOMHTMLInputElementK o) => o -> m T.Text
getDOMHTMLInputElementAccept obj = liftIO $ getObjectPropertyString obj "accept"

setDOMHTMLInputElementAccept :: (MonadIO m, DOMHTMLInputElementK o) => o -> T.Text -> m ()
setDOMHTMLInputElementAccept obj val = liftIO $ setObjectPropertyString obj "accept" val

constructDOMHTMLInputElementAccept :: T.Text -> IO ([Char], GValue)
constructDOMHTMLInputElementAccept val = constructObjectPropertyString "accept" val

data DOMHTMLInputElementAcceptPropertyInfo
instance AttrInfo DOMHTMLInputElementAcceptPropertyInfo where
    type AttrAllowedOps DOMHTMLInputElementAcceptPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint DOMHTMLInputElementAcceptPropertyInfo = (~) T.Text
    type AttrBaseTypeConstraint DOMHTMLInputElementAcceptPropertyInfo = DOMHTMLInputElementK
    type AttrGetType DOMHTMLInputElementAcceptPropertyInfo = T.Text
    type AttrLabel DOMHTMLInputElementAcceptPropertyInfo = "DOMHTMLInputElement::accept"
    attrGet _ = getDOMHTMLInputElementAccept
    attrSet _ = setDOMHTMLInputElementAccept
    attrConstruct _ = constructDOMHTMLInputElementAccept

-- VVV Prop "align"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]

getDOMHTMLInputElementAlign :: (MonadIO m, DOMHTMLInputElementK o) => o -> m T.Text
getDOMHTMLInputElementAlign obj = liftIO $ getObjectPropertyString obj "align"

setDOMHTMLInputElementAlign :: (MonadIO m, DOMHTMLInputElementK o) => o -> T.Text -> m ()
setDOMHTMLInputElementAlign obj val = liftIO $ setObjectPropertyString obj "align" val

constructDOMHTMLInputElementAlign :: T.Text -> IO ([Char], GValue)
constructDOMHTMLInputElementAlign val = constructObjectPropertyString "align" val

data DOMHTMLInputElementAlignPropertyInfo
instance AttrInfo DOMHTMLInputElementAlignPropertyInfo where
    type AttrAllowedOps DOMHTMLInputElementAlignPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint DOMHTMLInputElementAlignPropertyInfo = (~) T.Text
    type AttrBaseTypeConstraint DOMHTMLInputElementAlignPropertyInfo = DOMHTMLInputElementK
    type AttrGetType DOMHTMLInputElementAlignPropertyInfo = T.Text
    type AttrLabel DOMHTMLInputElementAlignPropertyInfo = "DOMHTMLInputElement::align"
    attrGet _ = getDOMHTMLInputElementAlign
    attrSet _ = setDOMHTMLInputElementAlign
    attrConstruct _ = constructDOMHTMLInputElementAlign

-- VVV Prop "alt"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]

getDOMHTMLInputElementAlt :: (MonadIO m, DOMHTMLInputElementK o) => o -> m T.Text
getDOMHTMLInputElementAlt obj = liftIO $ getObjectPropertyString obj "alt"

setDOMHTMLInputElementAlt :: (MonadIO m, DOMHTMLInputElementK o) => o -> T.Text -> m ()
setDOMHTMLInputElementAlt obj val = liftIO $ setObjectPropertyString obj "alt" val

constructDOMHTMLInputElementAlt :: T.Text -> IO ([Char], GValue)
constructDOMHTMLInputElementAlt val = constructObjectPropertyString "alt" val

data DOMHTMLInputElementAltPropertyInfo
instance AttrInfo DOMHTMLInputElementAltPropertyInfo where
    type AttrAllowedOps DOMHTMLInputElementAltPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint DOMHTMLInputElementAltPropertyInfo = (~) T.Text
    type AttrBaseTypeConstraint DOMHTMLInputElementAltPropertyInfo = DOMHTMLInputElementK
    type AttrGetType DOMHTMLInputElementAltPropertyInfo = T.Text
    type AttrLabel DOMHTMLInputElementAltPropertyInfo = "DOMHTMLInputElement::alt"
    attrGet _ = getDOMHTMLInputElementAlt
    attrSet _ = setDOMHTMLInputElementAlt
    attrConstruct _ = constructDOMHTMLInputElementAlt

-- VVV Prop "autocapitalize"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]

getDOMHTMLInputElementAutocapitalize :: (MonadIO m, DOMHTMLInputElementK o) => o -> m T.Text
getDOMHTMLInputElementAutocapitalize obj = liftIO $ getObjectPropertyString obj "autocapitalize"

setDOMHTMLInputElementAutocapitalize :: (MonadIO m, DOMHTMLInputElementK o) => o -> T.Text -> m ()
setDOMHTMLInputElementAutocapitalize obj val = liftIO $ setObjectPropertyString obj "autocapitalize" val

constructDOMHTMLInputElementAutocapitalize :: T.Text -> IO ([Char], GValue)
constructDOMHTMLInputElementAutocapitalize val = constructObjectPropertyString "autocapitalize" val

data DOMHTMLInputElementAutocapitalizePropertyInfo
instance AttrInfo DOMHTMLInputElementAutocapitalizePropertyInfo where
    type AttrAllowedOps DOMHTMLInputElementAutocapitalizePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint DOMHTMLInputElementAutocapitalizePropertyInfo = (~) T.Text
    type AttrBaseTypeConstraint DOMHTMLInputElementAutocapitalizePropertyInfo = DOMHTMLInputElementK
    type AttrGetType DOMHTMLInputElementAutocapitalizePropertyInfo = T.Text
    type AttrLabel DOMHTMLInputElementAutocapitalizePropertyInfo = "DOMHTMLInputElement::autocapitalize"
    attrGet _ = getDOMHTMLInputElementAutocapitalize
    attrSet _ = setDOMHTMLInputElementAutocapitalize
    attrConstruct _ = constructDOMHTMLInputElementAutocapitalize

-- VVV Prop "autocomplete"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]

getDOMHTMLInputElementAutocomplete :: (MonadIO m, DOMHTMLInputElementK o) => o -> m T.Text
getDOMHTMLInputElementAutocomplete obj = liftIO $ getObjectPropertyString obj "autocomplete"

setDOMHTMLInputElementAutocomplete :: (MonadIO m, DOMHTMLInputElementK o) => o -> T.Text -> m ()
setDOMHTMLInputElementAutocomplete obj val = liftIO $ setObjectPropertyString obj "autocomplete" val

constructDOMHTMLInputElementAutocomplete :: T.Text -> IO ([Char], GValue)
constructDOMHTMLInputElementAutocomplete val = constructObjectPropertyString "autocomplete" val

data DOMHTMLInputElementAutocompletePropertyInfo
instance AttrInfo DOMHTMLInputElementAutocompletePropertyInfo where
    type AttrAllowedOps DOMHTMLInputElementAutocompletePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint DOMHTMLInputElementAutocompletePropertyInfo = (~) T.Text
    type AttrBaseTypeConstraint DOMHTMLInputElementAutocompletePropertyInfo = DOMHTMLInputElementK
    type AttrGetType DOMHTMLInputElementAutocompletePropertyInfo = T.Text
    type AttrLabel DOMHTMLInputElementAutocompletePropertyInfo = "DOMHTMLInputElement::autocomplete"
    attrGet _ = getDOMHTMLInputElementAutocomplete
    attrSet _ = setDOMHTMLInputElementAutocomplete
    attrConstruct _ = constructDOMHTMLInputElementAutocomplete

-- VVV Prop "autocorrect"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]

getDOMHTMLInputElementAutocorrect :: (MonadIO m, DOMHTMLInputElementK o) => o -> m Bool
getDOMHTMLInputElementAutocorrect obj = liftIO $ getObjectPropertyBool obj "autocorrect"

setDOMHTMLInputElementAutocorrect :: (MonadIO m, DOMHTMLInputElementK o) => o -> Bool -> m ()
setDOMHTMLInputElementAutocorrect obj val = liftIO $ setObjectPropertyBool obj "autocorrect" val

constructDOMHTMLInputElementAutocorrect :: Bool -> IO ([Char], GValue)
constructDOMHTMLInputElementAutocorrect val = constructObjectPropertyBool "autocorrect" val

data DOMHTMLInputElementAutocorrectPropertyInfo
instance AttrInfo DOMHTMLInputElementAutocorrectPropertyInfo where
    type AttrAllowedOps DOMHTMLInputElementAutocorrectPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint DOMHTMLInputElementAutocorrectPropertyInfo = (~) Bool
    type AttrBaseTypeConstraint DOMHTMLInputElementAutocorrectPropertyInfo = DOMHTMLInputElementK
    type AttrGetType DOMHTMLInputElementAutocorrectPropertyInfo = Bool
    type AttrLabel DOMHTMLInputElementAutocorrectPropertyInfo = "DOMHTMLInputElement::autocorrect"
    attrGet _ = getDOMHTMLInputElementAutocorrect
    attrSet _ = setDOMHTMLInputElementAutocorrect
    attrConstruct _ = constructDOMHTMLInputElementAutocorrect

-- VVV Prop "autofocus"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]

getDOMHTMLInputElementAutofocus :: (MonadIO m, DOMHTMLInputElementK o) => o -> m Bool
getDOMHTMLInputElementAutofocus obj = liftIO $ getObjectPropertyBool obj "autofocus"

setDOMHTMLInputElementAutofocus :: (MonadIO m, DOMHTMLInputElementK o) => o -> Bool -> m ()
setDOMHTMLInputElementAutofocus obj val = liftIO $ setObjectPropertyBool obj "autofocus" val

constructDOMHTMLInputElementAutofocus :: Bool -> IO ([Char], GValue)
constructDOMHTMLInputElementAutofocus val = constructObjectPropertyBool "autofocus" val

data DOMHTMLInputElementAutofocusPropertyInfo
instance AttrInfo DOMHTMLInputElementAutofocusPropertyInfo where
    type AttrAllowedOps DOMHTMLInputElementAutofocusPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint DOMHTMLInputElementAutofocusPropertyInfo = (~) Bool
    type AttrBaseTypeConstraint DOMHTMLInputElementAutofocusPropertyInfo = DOMHTMLInputElementK
    type AttrGetType DOMHTMLInputElementAutofocusPropertyInfo = Bool
    type AttrLabel DOMHTMLInputElementAutofocusPropertyInfo = "DOMHTMLInputElement::autofocus"
    attrGet _ = getDOMHTMLInputElementAutofocus
    attrSet _ = setDOMHTMLInputElementAutofocus
    attrConstruct _ = constructDOMHTMLInputElementAutofocus

-- VVV Prop "capture"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]

getDOMHTMLInputElementCapture :: (MonadIO m, DOMHTMLInputElementK o) => o -> m T.Text
getDOMHTMLInputElementCapture obj = liftIO $ getObjectPropertyString obj "capture"

setDOMHTMLInputElementCapture :: (MonadIO m, DOMHTMLInputElementK o) => o -> T.Text -> m ()
setDOMHTMLInputElementCapture obj val = liftIO $ setObjectPropertyString obj "capture" val

constructDOMHTMLInputElementCapture :: T.Text -> IO ([Char], GValue)
constructDOMHTMLInputElementCapture val = constructObjectPropertyString "capture" val

data DOMHTMLInputElementCapturePropertyInfo
instance AttrInfo DOMHTMLInputElementCapturePropertyInfo where
    type AttrAllowedOps DOMHTMLInputElementCapturePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint DOMHTMLInputElementCapturePropertyInfo = (~) T.Text
    type AttrBaseTypeConstraint DOMHTMLInputElementCapturePropertyInfo = DOMHTMLInputElementK
    type AttrGetType DOMHTMLInputElementCapturePropertyInfo = T.Text
    type AttrLabel DOMHTMLInputElementCapturePropertyInfo = "DOMHTMLInputElement::capture"
    attrGet _ = getDOMHTMLInputElementCapture
    attrSet _ = setDOMHTMLInputElementCapture
    attrConstruct _ = constructDOMHTMLInputElementCapture

-- VVV Prop "checked"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]

getDOMHTMLInputElementChecked :: (MonadIO m, DOMHTMLInputElementK o) => o -> m Bool
getDOMHTMLInputElementChecked obj = liftIO $ getObjectPropertyBool obj "checked"

setDOMHTMLInputElementChecked :: (MonadIO m, DOMHTMLInputElementK o) => o -> Bool -> m ()
setDOMHTMLInputElementChecked obj val = liftIO $ setObjectPropertyBool obj "checked" val

constructDOMHTMLInputElementChecked :: Bool -> IO ([Char], GValue)
constructDOMHTMLInputElementChecked val = constructObjectPropertyBool "checked" val

data DOMHTMLInputElementCheckedPropertyInfo
instance AttrInfo DOMHTMLInputElementCheckedPropertyInfo where
    type AttrAllowedOps DOMHTMLInputElementCheckedPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint DOMHTMLInputElementCheckedPropertyInfo = (~) Bool
    type AttrBaseTypeConstraint DOMHTMLInputElementCheckedPropertyInfo = DOMHTMLInputElementK
    type AttrGetType DOMHTMLInputElementCheckedPropertyInfo = Bool
    type AttrLabel DOMHTMLInputElementCheckedPropertyInfo = "DOMHTMLInputElement::checked"
    attrGet _ = getDOMHTMLInputElementChecked
    attrSet _ = setDOMHTMLInputElementChecked
    attrConstruct _ = constructDOMHTMLInputElementChecked

-- VVV Prop "default-checked"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]

getDOMHTMLInputElementDefaultChecked :: (MonadIO m, DOMHTMLInputElementK o) => o -> m Bool
getDOMHTMLInputElementDefaultChecked obj = liftIO $ getObjectPropertyBool obj "default-checked"

setDOMHTMLInputElementDefaultChecked :: (MonadIO m, DOMHTMLInputElementK o) => o -> Bool -> m ()
setDOMHTMLInputElementDefaultChecked obj val = liftIO $ setObjectPropertyBool obj "default-checked" val

constructDOMHTMLInputElementDefaultChecked :: Bool -> IO ([Char], GValue)
constructDOMHTMLInputElementDefaultChecked val = constructObjectPropertyBool "default-checked" val

data DOMHTMLInputElementDefaultCheckedPropertyInfo
instance AttrInfo DOMHTMLInputElementDefaultCheckedPropertyInfo where
    type AttrAllowedOps DOMHTMLInputElementDefaultCheckedPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint DOMHTMLInputElementDefaultCheckedPropertyInfo = (~) Bool
    type AttrBaseTypeConstraint DOMHTMLInputElementDefaultCheckedPropertyInfo = DOMHTMLInputElementK
    type AttrGetType DOMHTMLInputElementDefaultCheckedPropertyInfo = Bool
    type AttrLabel DOMHTMLInputElementDefaultCheckedPropertyInfo = "DOMHTMLInputElement::default-checked"
    attrGet _ = getDOMHTMLInputElementDefaultChecked
    attrSet _ = setDOMHTMLInputElementDefaultChecked
    attrConstruct _ = constructDOMHTMLInputElementDefaultChecked

-- VVV Prop "default-value"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]

getDOMHTMLInputElementDefaultValue :: (MonadIO m, DOMHTMLInputElementK o) => o -> m T.Text
getDOMHTMLInputElementDefaultValue obj = liftIO $ getObjectPropertyString obj "default-value"

setDOMHTMLInputElementDefaultValue :: (MonadIO m, DOMHTMLInputElementK o) => o -> T.Text -> m ()
setDOMHTMLInputElementDefaultValue obj val = liftIO $ setObjectPropertyString obj "default-value" val

constructDOMHTMLInputElementDefaultValue :: T.Text -> IO ([Char], GValue)
constructDOMHTMLInputElementDefaultValue val = constructObjectPropertyString "default-value" val

data DOMHTMLInputElementDefaultValuePropertyInfo
instance AttrInfo DOMHTMLInputElementDefaultValuePropertyInfo where
    type AttrAllowedOps DOMHTMLInputElementDefaultValuePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint DOMHTMLInputElementDefaultValuePropertyInfo = (~) T.Text
    type AttrBaseTypeConstraint DOMHTMLInputElementDefaultValuePropertyInfo = DOMHTMLInputElementK
    type AttrGetType DOMHTMLInputElementDefaultValuePropertyInfo = T.Text
    type AttrLabel DOMHTMLInputElementDefaultValuePropertyInfo = "DOMHTMLInputElement::default-value"
    attrGet _ = getDOMHTMLInputElementDefaultValue
    attrSet _ = setDOMHTMLInputElementDefaultValue
    attrConstruct _ = constructDOMHTMLInputElementDefaultValue

-- VVV Prop "dir-name"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]

getDOMHTMLInputElementDirName :: (MonadIO m, DOMHTMLInputElementK o) => o -> m T.Text
getDOMHTMLInputElementDirName obj = liftIO $ getObjectPropertyString obj "dir-name"

setDOMHTMLInputElementDirName :: (MonadIO m, DOMHTMLInputElementK o) => o -> T.Text -> m ()
setDOMHTMLInputElementDirName obj val = liftIO $ setObjectPropertyString obj "dir-name" val

constructDOMHTMLInputElementDirName :: T.Text -> IO ([Char], GValue)
constructDOMHTMLInputElementDirName val = constructObjectPropertyString "dir-name" val

data DOMHTMLInputElementDirNamePropertyInfo
instance AttrInfo DOMHTMLInputElementDirNamePropertyInfo where
    type AttrAllowedOps DOMHTMLInputElementDirNamePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint DOMHTMLInputElementDirNamePropertyInfo = (~) T.Text
    type AttrBaseTypeConstraint DOMHTMLInputElementDirNamePropertyInfo = DOMHTMLInputElementK
    type AttrGetType DOMHTMLInputElementDirNamePropertyInfo = T.Text
    type AttrLabel DOMHTMLInputElementDirNamePropertyInfo = "DOMHTMLInputElement::dir-name"
    attrGet _ = getDOMHTMLInputElementDirName
    attrSet _ = setDOMHTMLInputElementDirName
    attrConstruct _ = constructDOMHTMLInputElementDirName

-- VVV Prop "disabled"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]

getDOMHTMLInputElementDisabled :: (MonadIO m, DOMHTMLInputElementK o) => o -> m Bool
getDOMHTMLInputElementDisabled obj = liftIO $ getObjectPropertyBool obj "disabled"

setDOMHTMLInputElementDisabled :: (MonadIO m, DOMHTMLInputElementK o) => o -> Bool -> m ()
setDOMHTMLInputElementDisabled obj val = liftIO $ setObjectPropertyBool obj "disabled" val

constructDOMHTMLInputElementDisabled :: Bool -> IO ([Char], GValue)
constructDOMHTMLInputElementDisabled val = constructObjectPropertyBool "disabled" val

data DOMHTMLInputElementDisabledPropertyInfo
instance AttrInfo DOMHTMLInputElementDisabledPropertyInfo where
    type AttrAllowedOps DOMHTMLInputElementDisabledPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint DOMHTMLInputElementDisabledPropertyInfo = (~) Bool
    type AttrBaseTypeConstraint DOMHTMLInputElementDisabledPropertyInfo = DOMHTMLInputElementK
    type AttrGetType DOMHTMLInputElementDisabledPropertyInfo = Bool
    type AttrLabel DOMHTMLInputElementDisabledPropertyInfo = "DOMHTMLInputElement::disabled"
    attrGet _ = getDOMHTMLInputElementDisabled
    attrSet _ = setDOMHTMLInputElementDisabled
    attrConstruct _ = constructDOMHTMLInputElementDisabled

-- VVV Prop "files"
   -- Type: TInterface "WebKit" "DOMFileList"
   -- Flags: [PropertyReadable]

getDOMHTMLInputElementFiles :: (MonadIO m, DOMHTMLInputElementK o) => o -> m DOMFileList
getDOMHTMLInputElementFiles obj = liftIO $ getObjectPropertyObject obj "files" DOMFileList

data DOMHTMLInputElementFilesPropertyInfo
instance AttrInfo DOMHTMLInputElementFilesPropertyInfo where
    type AttrAllowedOps DOMHTMLInputElementFilesPropertyInfo = '[ 'AttrGet]
    type AttrSetTypeConstraint DOMHTMLInputElementFilesPropertyInfo = (~) ()
    type AttrBaseTypeConstraint DOMHTMLInputElementFilesPropertyInfo = DOMHTMLInputElementK
    type AttrGetType DOMHTMLInputElementFilesPropertyInfo = DOMFileList
    type AttrLabel DOMHTMLInputElementFilesPropertyInfo = "DOMHTMLInputElement::files"
    attrGet _ = getDOMHTMLInputElementFiles
    attrSet _ = undefined
    attrConstruct _ = undefined

-- VVV Prop "form"
   -- Type: TInterface "WebKit" "DOMHTMLFormElement"
   -- Flags: [PropertyReadable]

getDOMHTMLInputElementForm :: (MonadIO m, DOMHTMLInputElementK o) => o -> m DOMHTMLFormElement
getDOMHTMLInputElementForm obj = liftIO $ getObjectPropertyObject obj "form" DOMHTMLFormElement

data DOMHTMLInputElementFormPropertyInfo
instance AttrInfo DOMHTMLInputElementFormPropertyInfo where
    type AttrAllowedOps DOMHTMLInputElementFormPropertyInfo = '[ 'AttrGet]
    type AttrSetTypeConstraint DOMHTMLInputElementFormPropertyInfo = (~) ()
    type AttrBaseTypeConstraint DOMHTMLInputElementFormPropertyInfo = DOMHTMLInputElementK
    type AttrGetType DOMHTMLInputElementFormPropertyInfo = DOMHTMLFormElement
    type AttrLabel DOMHTMLInputElementFormPropertyInfo = "DOMHTMLInputElement::form"
    attrGet _ = getDOMHTMLInputElementForm
    attrSet _ = undefined
    attrConstruct _ = undefined

-- VVV Prop "form-action"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]

getDOMHTMLInputElementFormAction :: (MonadIO m, DOMHTMLInputElementK o) => o -> m T.Text
getDOMHTMLInputElementFormAction obj = liftIO $ getObjectPropertyString obj "form-action"

setDOMHTMLInputElementFormAction :: (MonadIO m, DOMHTMLInputElementK o) => o -> T.Text -> m ()
setDOMHTMLInputElementFormAction obj val = liftIO $ setObjectPropertyString obj "form-action" val

constructDOMHTMLInputElementFormAction :: T.Text -> IO ([Char], GValue)
constructDOMHTMLInputElementFormAction val = constructObjectPropertyString "form-action" val

data DOMHTMLInputElementFormActionPropertyInfo
instance AttrInfo DOMHTMLInputElementFormActionPropertyInfo where
    type AttrAllowedOps DOMHTMLInputElementFormActionPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint DOMHTMLInputElementFormActionPropertyInfo = (~) T.Text
    type AttrBaseTypeConstraint DOMHTMLInputElementFormActionPropertyInfo = DOMHTMLInputElementK
    type AttrGetType DOMHTMLInputElementFormActionPropertyInfo = T.Text
    type AttrLabel DOMHTMLInputElementFormActionPropertyInfo = "DOMHTMLInputElement::form-action"
    attrGet _ = getDOMHTMLInputElementFormAction
    attrSet _ = setDOMHTMLInputElementFormAction
    attrConstruct _ = constructDOMHTMLInputElementFormAction

-- VVV Prop "form-enctype"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]

getDOMHTMLInputElementFormEnctype :: (MonadIO m, DOMHTMLInputElementK o) => o -> m T.Text
getDOMHTMLInputElementFormEnctype obj = liftIO $ getObjectPropertyString obj "form-enctype"

setDOMHTMLInputElementFormEnctype :: (MonadIO m, DOMHTMLInputElementK o) => o -> T.Text -> m ()
setDOMHTMLInputElementFormEnctype obj val = liftIO $ setObjectPropertyString obj "form-enctype" val

constructDOMHTMLInputElementFormEnctype :: T.Text -> IO ([Char], GValue)
constructDOMHTMLInputElementFormEnctype val = constructObjectPropertyString "form-enctype" val

data DOMHTMLInputElementFormEnctypePropertyInfo
instance AttrInfo DOMHTMLInputElementFormEnctypePropertyInfo where
    type AttrAllowedOps DOMHTMLInputElementFormEnctypePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint DOMHTMLInputElementFormEnctypePropertyInfo = (~) T.Text
    type AttrBaseTypeConstraint DOMHTMLInputElementFormEnctypePropertyInfo = DOMHTMLInputElementK
    type AttrGetType DOMHTMLInputElementFormEnctypePropertyInfo = T.Text
    type AttrLabel DOMHTMLInputElementFormEnctypePropertyInfo = "DOMHTMLInputElement::form-enctype"
    attrGet _ = getDOMHTMLInputElementFormEnctype
    attrSet _ = setDOMHTMLInputElementFormEnctype
    attrConstruct _ = constructDOMHTMLInputElementFormEnctype

-- VVV Prop "form-method"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]

getDOMHTMLInputElementFormMethod :: (MonadIO m, DOMHTMLInputElementK o) => o -> m T.Text
getDOMHTMLInputElementFormMethod obj = liftIO $ getObjectPropertyString obj "form-method"

setDOMHTMLInputElementFormMethod :: (MonadIO m, DOMHTMLInputElementK o) => o -> T.Text -> m ()
setDOMHTMLInputElementFormMethod obj val = liftIO $ setObjectPropertyString obj "form-method" val

constructDOMHTMLInputElementFormMethod :: T.Text -> IO ([Char], GValue)
constructDOMHTMLInputElementFormMethod val = constructObjectPropertyString "form-method" val

data DOMHTMLInputElementFormMethodPropertyInfo
instance AttrInfo DOMHTMLInputElementFormMethodPropertyInfo where
    type AttrAllowedOps DOMHTMLInputElementFormMethodPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint DOMHTMLInputElementFormMethodPropertyInfo = (~) T.Text
    type AttrBaseTypeConstraint DOMHTMLInputElementFormMethodPropertyInfo = DOMHTMLInputElementK
    type AttrGetType DOMHTMLInputElementFormMethodPropertyInfo = T.Text
    type AttrLabel DOMHTMLInputElementFormMethodPropertyInfo = "DOMHTMLInputElement::form-method"
    attrGet _ = getDOMHTMLInputElementFormMethod
    attrSet _ = setDOMHTMLInputElementFormMethod
    attrConstruct _ = constructDOMHTMLInputElementFormMethod

-- VVV Prop "form-no-validate"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]

getDOMHTMLInputElementFormNoValidate :: (MonadIO m, DOMHTMLInputElementK o) => o -> m Bool
getDOMHTMLInputElementFormNoValidate obj = liftIO $ getObjectPropertyBool obj "form-no-validate"

setDOMHTMLInputElementFormNoValidate :: (MonadIO m, DOMHTMLInputElementK o) => o -> Bool -> m ()
setDOMHTMLInputElementFormNoValidate obj val = liftIO $ setObjectPropertyBool obj "form-no-validate" val

constructDOMHTMLInputElementFormNoValidate :: Bool -> IO ([Char], GValue)
constructDOMHTMLInputElementFormNoValidate val = constructObjectPropertyBool "form-no-validate" val

data DOMHTMLInputElementFormNoValidatePropertyInfo
instance AttrInfo DOMHTMLInputElementFormNoValidatePropertyInfo where
    type AttrAllowedOps DOMHTMLInputElementFormNoValidatePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint DOMHTMLInputElementFormNoValidatePropertyInfo = (~) Bool
    type AttrBaseTypeConstraint DOMHTMLInputElementFormNoValidatePropertyInfo = DOMHTMLInputElementK
    type AttrGetType DOMHTMLInputElementFormNoValidatePropertyInfo = Bool
    type AttrLabel DOMHTMLInputElementFormNoValidatePropertyInfo = "DOMHTMLInputElement::form-no-validate"
    attrGet _ = getDOMHTMLInputElementFormNoValidate
    attrSet _ = setDOMHTMLInputElementFormNoValidate
    attrConstruct _ = constructDOMHTMLInputElementFormNoValidate

-- VVV Prop "form-target"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]

getDOMHTMLInputElementFormTarget :: (MonadIO m, DOMHTMLInputElementK o) => o -> m T.Text
getDOMHTMLInputElementFormTarget obj = liftIO $ getObjectPropertyString obj "form-target"

setDOMHTMLInputElementFormTarget :: (MonadIO m, DOMHTMLInputElementK o) => o -> T.Text -> m ()
setDOMHTMLInputElementFormTarget obj val = liftIO $ setObjectPropertyString obj "form-target" val

constructDOMHTMLInputElementFormTarget :: T.Text -> IO ([Char], GValue)
constructDOMHTMLInputElementFormTarget val = constructObjectPropertyString "form-target" val

data DOMHTMLInputElementFormTargetPropertyInfo
instance AttrInfo DOMHTMLInputElementFormTargetPropertyInfo where
    type AttrAllowedOps DOMHTMLInputElementFormTargetPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint DOMHTMLInputElementFormTargetPropertyInfo = (~) T.Text
    type AttrBaseTypeConstraint DOMHTMLInputElementFormTargetPropertyInfo = DOMHTMLInputElementK
    type AttrGetType DOMHTMLInputElementFormTargetPropertyInfo = T.Text
    type AttrLabel DOMHTMLInputElementFormTargetPropertyInfo = "DOMHTMLInputElement::form-target"
    attrGet _ = getDOMHTMLInputElementFormTarget
    attrSet _ = setDOMHTMLInputElementFormTarget
    attrConstruct _ = constructDOMHTMLInputElementFormTarget

-- VVV Prop "height"
   -- Type: TBasicType TUInt64
   -- Flags: [PropertyReadable,PropertyWritable]

getDOMHTMLInputElementHeight :: (MonadIO m, DOMHTMLInputElementK o) => o -> m Word64
getDOMHTMLInputElementHeight obj = liftIO $ getObjectPropertyUInt64 obj "height"

setDOMHTMLInputElementHeight :: (MonadIO m, DOMHTMLInputElementK o) => o -> Word64 -> m ()
setDOMHTMLInputElementHeight obj val = liftIO $ setObjectPropertyUInt64 obj "height" val

constructDOMHTMLInputElementHeight :: Word64 -> IO ([Char], GValue)
constructDOMHTMLInputElementHeight val = constructObjectPropertyUInt64 "height" val

data DOMHTMLInputElementHeightPropertyInfo
instance AttrInfo DOMHTMLInputElementHeightPropertyInfo where
    type AttrAllowedOps DOMHTMLInputElementHeightPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint DOMHTMLInputElementHeightPropertyInfo = (~) Word64
    type AttrBaseTypeConstraint DOMHTMLInputElementHeightPropertyInfo = DOMHTMLInputElementK
    type AttrGetType DOMHTMLInputElementHeightPropertyInfo = Word64
    type AttrLabel DOMHTMLInputElementHeightPropertyInfo = "DOMHTMLInputElement::height"
    attrGet _ = getDOMHTMLInputElementHeight
    attrSet _ = setDOMHTMLInputElementHeight
    attrConstruct _ = constructDOMHTMLInputElementHeight

-- VVV Prop "incremental"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]

getDOMHTMLInputElementIncremental :: (MonadIO m, DOMHTMLInputElementK o) => o -> m Bool
getDOMHTMLInputElementIncremental obj = liftIO $ getObjectPropertyBool obj "incremental"

setDOMHTMLInputElementIncremental :: (MonadIO m, DOMHTMLInputElementK o) => o -> Bool -> m ()
setDOMHTMLInputElementIncremental obj val = liftIO $ setObjectPropertyBool obj "incremental" val

constructDOMHTMLInputElementIncremental :: Bool -> IO ([Char], GValue)
constructDOMHTMLInputElementIncremental val = constructObjectPropertyBool "incremental" val

data DOMHTMLInputElementIncrementalPropertyInfo
instance AttrInfo DOMHTMLInputElementIncrementalPropertyInfo where
    type AttrAllowedOps DOMHTMLInputElementIncrementalPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint DOMHTMLInputElementIncrementalPropertyInfo = (~) Bool
    type AttrBaseTypeConstraint DOMHTMLInputElementIncrementalPropertyInfo = DOMHTMLInputElementK
    type AttrGetType DOMHTMLInputElementIncrementalPropertyInfo = Bool
    type AttrLabel DOMHTMLInputElementIncrementalPropertyInfo = "DOMHTMLInputElement::incremental"
    attrGet _ = getDOMHTMLInputElementIncremental
    attrSet _ = setDOMHTMLInputElementIncremental
    attrConstruct _ = constructDOMHTMLInputElementIncremental

-- VVV Prop "indeterminate"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]

getDOMHTMLInputElementIndeterminate :: (MonadIO m, DOMHTMLInputElementK o) => o -> m Bool
getDOMHTMLInputElementIndeterminate obj = liftIO $ getObjectPropertyBool obj "indeterminate"

setDOMHTMLInputElementIndeterminate :: (MonadIO m, DOMHTMLInputElementK o) => o -> Bool -> m ()
setDOMHTMLInputElementIndeterminate obj val = liftIO $ setObjectPropertyBool obj "indeterminate" val

constructDOMHTMLInputElementIndeterminate :: Bool -> IO ([Char], GValue)
constructDOMHTMLInputElementIndeterminate val = constructObjectPropertyBool "indeterminate" val

data DOMHTMLInputElementIndeterminatePropertyInfo
instance AttrInfo DOMHTMLInputElementIndeterminatePropertyInfo where
    type AttrAllowedOps DOMHTMLInputElementIndeterminatePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint DOMHTMLInputElementIndeterminatePropertyInfo = (~) Bool
    type AttrBaseTypeConstraint DOMHTMLInputElementIndeterminatePropertyInfo = DOMHTMLInputElementK
    type AttrGetType DOMHTMLInputElementIndeterminatePropertyInfo = Bool
    type AttrLabel DOMHTMLInputElementIndeterminatePropertyInfo = "DOMHTMLInputElement::indeterminate"
    attrGet _ = getDOMHTMLInputElementIndeterminate
    attrSet _ = setDOMHTMLInputElementIndeterminate
    attrConstruct _ = constructDOMHTMLInputElementIndeterminate

-- VVV Prop "labels"
   -- Type: TInterface "WebKit" "DOMNodeList"
   -- Flags: [PropertyReadable]

getDOMHTMLInputElementLabels :: (MonadIO m, DOMHTMLInputElementK o) => o -> m DOMNodeList
getDOMHTMLInputElementLabels obj = liftIO $ getObjectPropertyObject obj "labels" DOMNodeList

data DOMHTMLInputElementLabelsPropertyInfo
instance AttrInfo DOMHTMLInputElementLabelsPropertyInfo where
    type AttrAllowedOps DOMHTMLInputElementLabelsPropertyInfo = '[ 'AttrGet]
    type AttrSetTypeConstraint DOMHTMLInputElementLabelsPropertyInfo = (~) ()
    type AttrBaseTypeConstraint DOMHTMLInputElementLabelsPropertyInfo = DOMHTMLInputElementK
    type AttrGetType DOMHTMLInputElementLabelsPropertyInfo = DOMNodeList
    type AttrLabel DOMHTMLInputElementLabelsPropertyInfo = "DOMHTMLInputElement::labels"
    attrGet _ = getDOMHTMLInputElementLabels
    attrSet _ = undefined
    attrConstruct _ = undefined

-- VVV Prop "list"
   -- Type: TInterface "WebKit" "DOMHTMLElement"
   -- Flags: [PropertyReadable]

getDOMHTMLInputElementList :: (MonadIO m, DOMHTMLInputElementK o) => o -> m DOMHTMLElement
getDOMHTMLInputElementList obj = liftIO $ getObjectPropertyObject obj "list" DOMHTMLElement

data DOMHTMLInputElementListPropertyInfo
instance AttrInfo DOMHTMLInputElementListPropertyInfo where
    type AttrAllowedOps DOMHTMLInputElementListPropertyInfo = '[ 'AttrGet]
    type AttrSetTypeConstraint DOMHTMLInputElementListPropertyInfo = (~) ()
    type AttrBaseTypeConstraint DOMHTMLInputElementListPropertyInfo = DOMHTMLInputElementK
    type AttrGetType DOMHTMLInputElementListPropertyInfo = DOMHTMLElement
    type AttrLabel DOMHTMLInputElementListPropertyInfo = "DOMHTMLInputElement::list"
    attrGet _ = getDOMHTMLInputElementList
    attrSet _ = undefined
    attrConstruct _ = undefined

-- VVV Prop "max"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]

getDOMHTMLInputElementMax :: (MonadIO m, DOMHTMLInputElementK o) => o -> m T.Text
getDOMHTMLInputElementMax obj = liftIO $ getObjectPropertyString obj "max"

setDOMHTMLInputElementMax :: (MonadIO m, DOMHTMLInputElementK o) => o -> T.Text -> m ()
setDOMHTMLInputElementMax obj val = liftIO $ setObjectPropertyString obj "max" val

constructDOMHTMLInputElementMax :: T.Text -> IO ([Char], GValue)
constructDOMHTMLInputElementMax val = constructObjectPropertyString "max" val

data DOMHTMLInputElementMaxPropertyInfo
instance AttrInfo DOMHTMLInputElementMaxPropertyInfo where
    type AttrAllowedOps DOMHTMLInputElementMaxPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint DOMHTMLInputElementMaxPropertyInfo = (~) T.Text
    type AttrBaseTypeConstraint DOMHTMLInputElementMaxPropertyInfo = DOMHTMLInputElementK
    type AttrGetType DOMHTMLInputElementMaxPropertyInfo = T.Text
    type AttrLabel DOMHTMLInputElementMaxPropertyInfo = "DOMHTMLInputElement::max"
    attrGet _ = getDOMHTMLInputElementMax
    attrSet _ = setDOMHTMLInputElementMax
    attrConstruct _ = constructDOMHTMLInputElementMax

-- VVV Prop "max-length"
   -- Type: TBasicType TInt64
   -- Flags: [PropertyReadable,PropertyWritable]

getDOMHTMLInputElementMaxLength :: (MonadIO m, DOMHTMLInputElementK o) => o -> m Int64
getDOMHTMLInputElementMaxLength obj = liftIO $ getObjectPropertyInt64 obj "max-length"

setDOMHTMLInputElementMaxLength :: (MonadIO m, DOMHTMLInputElementK o) => o -> Int64 -> m ()
setDOMHTMLInputElementMaxLength obj val = liftIO $ setObjectPropertyInt64 obj "max-length" val

constructDOMHTMLInputElementMaxLength :: Int64 -> IO ([Char], GValue)
constructDOMHTMLInputElementMaxLength val = constructObjectPropertyInt64 "max-length" val

data DOMHTMLInputElementMaxLengthPropertyInfo
instance AttrInfo DOMHTMLInputElementMaxLengthPropertyInfo where
    type AttrAllowedOps DOMHTMLInputElementMaxLengthPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint DOMHTMLInputElementMaxLengthPropertyInfo = (~) Int64
    type AttrBaseTypeConstraint DOMHTMLInputElementMaxLengthPropertyInfo = DOMHTMLInputElementK
    type AttrGetType DOMHTMLInputElementMaxLengthPropertyInfo = Int64
    type AttrLabel DOMHTMLInputElementMaxLengthPropertyInfo = "DOMHTMLInputElement::max-length"
    attrGet _ = getDOMHTMLInputElementMaxLength
    attrSet _ = setDOMHTMLInputElementMaxLength
    attrConstruct _ = constructDOMHTMLInputElementMaxLength

-- VVV Prop "min"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]

getDOMHTMLInputElementMin :: (MonadIO m, DOMHTMLInputElementK o) => o -> m T.Text
getDOMHTMLInputElementMin obj = liftIO $ getObjectPropertyString obj "min"

setDOMHTMLInputElementMin :: (MonadIO m, DOMHTMLInputElementK o) => o -> T.Text -> m ()
setDOMHTMLInputElementMin obj val = liftIO $ setObjectPropertyString obj "min" val

constructDOMHTMLInputElementMin :: T.Text -> IO ([Char], GValue)
constructDOMHTMLInputElementMin val = constructObjectPropertyString "min" val

data DOMHTMLInputElementMinPropertyInfo
instance AttrInfo DOMHTMLInputElementMinPropertyInfo where
    type AttrAllowedOps DOMHTMLInputElementMinPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint DOMHTMLInputElementMinPropertyInfo = (~) T.Text
    type AttrBaseTypeConstraint DOMHTMLInputElementMinPropertyInfo = DOMHTMLInputElementK
    type AttrGetType DOMHTMLInputElementMinPropertyInfo = T.Text
    type AttrLabel DOMHTMLInputElementMinPropertyInfo = "DOMHTMLInputElement::min"
    attrGet _ = getDOMHTMLInputElementMin
    attrSet _ = setDOMHTMLInputElementMin
    attrConstruct _ = constructDOMHTMLInputElementMin

-- VVV Prop "multiple"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]

getDOMHTMLInputElementMultiple :: (MonadIO m, DOMHTMLInputElementK o) => o -> m Bool
getDOMHTMLInputElementMultiple obj = liftIO $ getObjectPropertyBool obj "multiple"

setDOMHTMLInputElementMultiple :: (MonadIO m, DOMHTMLInputElementK o) => o -> Bool -> m ()
setDOMHTMLInputElementMultiple obj val = liftIO $ setObjectPropertyBool obj "multiple" val

constructDOMHTMLInputElementMultiple :: Bool -> IO ([Char], GValue)
constructDOMHTMLInputElementMultiple val = constructObjectPropertyBool "multiple" val

data DOMHTMLInputElementMultiplePropertyInfo
instance AttrInfo DOMHTMLInputElementMultiplePropertyInfo where
    type AttrAllowedOps DOMHTMLInputElementMultiplePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint DOMHTMLInputElementMultiplePropertyInfo = (~) Bool
    type AttrBaseTypeConstraint DOMHTMLInputElementMultiplePropertyInfo = DOMHTMLInputElementK
    type AttrGetType DOMHTMLInputElementMultiplePropertyInfo = Bool
    type AttrLabel DOMHTMLInputElementMultiplePropertyInfo = "DOMHTMLInputElement::multiple"
    attrGet _ = getDOMHTMLInputElementMultiple
    attrSet _ = setDOMHTMLInputElementMultiple
    attrConstruct _ = constructDOMHTMLInputElementMultiple

-- VVV Prop "name"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]

getDOMHTMLInputElementName :: (MonadIO m, DOMHTMLInputElementK o) => o -> m T.Text
getDOMHTMLInputElementName obj = liftIO $ getObjectPropertyString obj "name"

setDOMHTMLInputElementName :: (MonadIO m, DOMHTMLInputElementK o) => o -> T.Text -> m ()
setDOMHTMLInputElementName obj val = liftIO $ setObjectPropertyString obj "name" val

constructDOMHTMLInputElementName :: T.Text -> IO ([Char], GValue)
constructDOMHTMLInputElementName val = constructObjectPropertyString "name" val

data DOMHTMLInputElementNamePropertyInfo
instance AttrInfo DOMHTMLInputElementNamePropertyInfo where
    type AttrAllowedOps DOMHTMLInputElementNamePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint DOMHTMLInputElementNamePropertyInfo = (~) T.Text
    type AttrBaseTypeConstraint DOMHTMLInputElementNamePropertyInfo = DOMHTMLInputElementK
    type AttrGetType DOMHTMLInputElementNamePropertyInfo = T.Text
    type AttrLabel DOMHTMLInputElementNamePropertyInfo = "DOMHTMLInputElement::name"
    attrGet _ = getDOMHTMLInputElementName
    attrSet _ = setDOMHTMLInputElementName
    attrConstruct _ = constructDOMHTMLInputElementName

-- VVV Prop "pattern"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]

getDOMHTMLInputElementPattern :: (MonadIO m, DOMHTMLInputElementK o) => o -> m T.Text
getDOMHTMLInputElementPattern obj = liftIO $ getObjectPropertyString obj "pattern"

setDOMHTMLInputElementPattern :: (MonadIO m, DOMHTMLInputElementK o) => o -> T.Text -> m ()
setDOMHTMLInputElementPattern obj val = liftIO $ setObjectPropertyString obj "pattern" val

constructDOMHTMLInputElementPattern :: T.Text -> IO ([Char], GValue)
constructDOMHTMLInputElementPattern val = constructObjectPropertyString "pattern" val

data DOMHTMLInputElementPatternPropertyInfo
instance AttrInfo DOMHTMLInputElementPatternPropertyInfo where
    type AttrAllowedOps DOMHTMLInputElementPatternPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint DOMHTMLInputElementPatternPropertyInfo = (~) T.Text
    type AttrBaseTypeConstraint DOMHTMLInputElementPatternPropertyInfo = DOMHTMLInputElementK
    type AttrGetType DOMHTMLInputElementPatternPropertyInfo = T.Text
    type AttrLabel DOMHTMLInputElementPatternPropertyInfo = "DOMHTMLInputElement::pattern"
    attrGet _ = getDOMHTMLInputElementPattern
    attrSet _ = setDOMHTMLInputElementPattern
    attrConstruct _ = constructDOMHTMLInputElementPattern

-- VVV Prop "placeholder"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]

getDOMHTMLInputElementPlaceholder :: (MonadIO m, DOMHTMLInputElementK o) => o -> m T.Text
getDOMHTMLInputElementPlaceholder obj = liftIO $ getObjectPropertyString obj "placeholder"

setDOMHTMLInputElementPlaceholder :: (MonadIO m, DOMHTMLInputElementK o) => o -> T.Text -> m ()
setDOMHTMLInputElementPlaceholder obj val = liftIO $ setObjectPropertyString obj "placeholder" val

constructDOMHTMLInputElementPlaceholder :: T.Text -> IO ([Char], GValue)
constructDOMHTMLInputElementPlaceholder val = constructObjectPropertyString "placeholder" val

data DOMHTMLInputElementPlaceholderPropertyInfo
instance AttrInfo DOMHTMLInputElementPlaceholderPropertyInfo where
    type AttrAllowedOps DOMHTMLInputElementPlaceholderPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint DOMHTMLInputElementPlaceholderPropertyInfo = (~) T.Text
    type AttrBaseTypeConstraint DOMHTMLInputElementPlaceholderPropertyInfo = DOMHTMLInputElementK
    type AttrGetType DOMHTMLInputElementPlaceholderPropertyInfo = T.Text
    type AttrLabel DOMHTMLInputElementPlaceholderPropertyInfo = "DOMHTMLInputElement::placeholder"
    attrGet _ = getDOMHTMLInputElementPlaceholder
    attrSet _ = setDOMHTMLInputElementPlaceholder
    attrConstruct _ = constructDOMHTMLInputElementPlaceholder

-- VVV Prop "read-only"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]

getDOMHTMLInputElementReadOnly :: (MonadIO m, DOMHTMLInputElementK o) => o -> m Bool
getDOMHTMLInputElementReadOnly obj = liftIO $ getObjectPropertyBool obj "read-only"

setDOMHTMLInputElementReadOnly :: (MonadIO m, DOMHTMLInputElementK o) => o -> Bool -> m ()
setDOMHTMLInputElementReadOnly obj val = liftIO $ setObjectPropertyBool obj "read-only" val

constructDOMHTMLInputElementReadOnly :: Bool -> IO ([Char], GValue)
constructDOMHTMLInputElementReadOnly val = constructObjectPropertyBool "read-only" val

data DOMHTMLInputElementReadOnlyPropertyInfo
instance AttrInfo DOMHTMLInputElementReadOnlyPropertyInfo where
    type AttrAllowedOps DOMHTMLInputElementReadOnlyPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint DOMHTMLInputElementReadOnlyPropertyInfo = (~) Bool
    type AttrBaseTypeConstraint DOMHTMLInputElementReadOnlyPropertyInfo = DOMHTMLInputElementK
    type AttrGetType DOMHTMLInputElementReadOnlyPropertyInfo = Bool
    type AttrLabel DOMHTMLInputElementReadOnlyPropertyInfo = "DOMHTMLInputElement::read-only"
    attrGet _ = getDOMHTMLInputElementReadOnly
    attrSet _ = setDOMHTMLInputElementReadOnly
    attrConstruct _ = constructDOMHTMLInputElementReadOnly

-- VVV Prop "required"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]

getDOMHTMLInputElementRequired :: (MonadIO m, DOMHTMLInputElementK o) => o -> m Bool
getDOMHTMLInputElementRequired obj = liftIO $ getObjectPropertyBool obj "required"

setDOMHTMLInputElementRequired :: (MonadIO m, DOMHTMLInputElementK o) => o -> Bool -> m ()
setDOMHTMLInputElementRequired obj val = liftIO $ setObjectPropertyBool obj "required" val

constructDOMHTMLInputElementRequired :: Bool -> IO ([Char], GValue)
constructDOMHTMLInputElementRequired val = constructObjectPropertyBool "required" val

data DOMHTMLInputElementRequiredPropertyInfo
instance AttrInfo DOMHTMLInputElementRequiredPropertyInfo where
    type AttrAllowedOps DOMHTMLInputElementRequiredPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint DOMHTMLInputElementRequiredPropertyInfo = (~) Bool
    type AttrBaseTypeConstraint DOMHTMLInputElementRequiredPropertyInfo = DOMHTMLInputElementK
    type AttrGetType DOMHTMLInputElementRequiredPropertyInfo = Bool
    type AttrLabel DOMHTMLInputElementRequiredPropertyInfo = "DOMHTMLInputElement::required"
    attrGet _ = getDOMHTMLInputElementRequired
    attrSet _ = setDOMHTMLInputElementRequired
    attrConstruct _ = constructDOMHTMLInputElementRequired

-- VVV Prop "size"
   -- Type: TBasicType TUInt64
   -- Flags: [PropertyReadable,PropertyWritable]

getDOMHTMLInputElementSize :: (MonadIO m, DOMHTMLInputElementK o) => o -> m Word64
getDOMHTMLInputElementSize obj = liftIO $ getObjectPropertyUInt64 obj "size"

setDOMHTMLInputElementSize :: (MonadIO m, DOMHTMLInputElementK o) => o -> Word64 -> m ()
setDOMHTMLInputElementSize obj val = liftIO $ setObjectPropertyUInt64 obj "size" val

constructDOMHTMLInputElementSize :: Word64 -> IO ([Char], GValue)
constructDOMHTMLInputElementSize val = constructObjectPropertyUInt64 "size" val

data DOMHTMLInputElementSizePropertyInfo
instance AttrInfo DOMHTMLInputElementSizePropertyInfo where
    type AttrAllowedOps DOMHTMLInputElementSizePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint DOMHTMLInputElementSizePropertyInfo = (~) Word64
    type AttrBaseTypeConstraint DOMHTMLInputElementSizePropertyInfo = DOMHTMLInputElementK
    type AttrGetType DOMHTMLInputElementSizePropertyInfo = Word64
    type AttrLabel DOMHTMLInputElementSizePropertyInfo = "DOMHTMLInputElement::size"
    attrGet _ = getDOMHTMLInputElementSize
    attrSet _ = setDOMHTMLInputElementSize
    attrConstruct _ = constructDOMHTMLInputElementSize

-- VVV Prop "src"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]

getDOMHTMLInputElementSrc :: (MonadIO m, DOMHTMLInputElementK o) => o -> m T.Text
getDOMHTMLInputElementSrc obj = liftIO $ getObjectPropertyString obj "src"

setDOMHTMLInputElementSrc :: (MonadIO m, DOMHTMLInputElementK o) => o -> T.Text -> m ()
setDOMHTMLInputElementSrc obj val = liftIO $ setObjectPropertyString obj "src" val

constructDOMHTMLInputElementSrc :: T.Text -> IO ([Char], GValue)
constructDOMHTMLInputElementSrc val = constructObjectPropertyString "src" val

data DOMHTMLInputElementSrcPropertyInfo
instance AttrInfo DOMHTMLInputElementSrcPropertyInfo where
    type AttrAllowedOps DOMHTMLInputElementSrcPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint DOMHTMLInputElementSrcPropertyInfo = (~) T.Text
    type AttrBaseTypeConstraint DOMHTMLInputElementSrcPropertyInfo = DOMHTMLInputElementK
    type AttrGetType DOMHTMLInputElementSrcPropertyInfo = T.Text
    type AttrLabel DOMHTMLInputElementSrcPropertyInfo = "DOMHTMLInputElement::src"
    attrGet _ = getDOMHTMLInputElementSrc
    attrSet _ = setDOMHTMLInputElementSrc
    attrConstruct _ = constructDOMHTMLInputElementSrc

-- VVV Prop "step"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]

getDOMHTMLInputElementStep :: (MonadIO m, DOMHTMLInputElementK o) => o -> m T.Text
getDOMHTMLInputElementStep obj = liftIO $ getObjectPropertyString obj "step"

setDOMHTMLInputElementStep :: (MonadIO m, DOMHTMLInputElementK o) => o -> T.Text -> m ()
setDOMHTMLInputElementStep obj val = liftIO $ setObjectPropertyString obj "step" val

constructDOMHTMLInputElementStep :: T.Text -> IO ([Char], GValue)
constructDOMHTMLInputElementStep val = constructObjectPropertyString "step" val

data DOMHTMLInputElementStepPropertyInfo
instance AttrInfo DOMHTMLInputElementStepPropertyInfo where
    type AttrAllowedOps DOMHTMLInputElementStepPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint DOMHTMLInputElementStepPropertyInfo = (~) T.Text
    type AttrBaseTypeConstraint DOMHTMLInputElementStepPropertyInfo = DOMHTMLInputElementK
    type AttrGetType DOMHTMLInputElementStepPropertyInfo = T.Text
    type AttrLabel DOMHTMLInputElementStepPropertyInfo = "DOMHTMLInputElement::step"
    attrGet _ = getDOMHTMLInputElementStep
    attrSet _ = setDOMHTMLInputElementStep
    attrConstruct _ = constructDOMHTMLInputElementStep

-- VVV Prop "type"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]

getDOMHTMLInputElementType :: (MonadIO m, DOMHTMLInputElementK o) => o -> m T.Text
getDOMHTMLInputElementType obj = liftIO $ getObjectPropertyString obj "type"

setDOMHTMLInputElementType :: (MonadIO m, DOMHTMLInputElementK o) => o -> T.Text -> m ()
setDOMHTMLInputElementType obj val = liftIO $ setObjectPropertyString obj "type" val

constructDOMHTMLInputElementType :: T.Text -> IO ([Char], GValue)
constructDOMHTMLInputElementType val = constructObjectPropertyString "type" val

data DOMHTMLInputElementTypePropertyInfo
instance AttrInfo DOMHTMLInputElementTypePropertyInfo where
    type AttrAllowedOps DOMHTMLInputElementTypePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint DOMHTMLInputElementTypePropertyInfo = (~) T.Text
    type AttrBaseTypeConstraint DOMHTMLInputElementTypePropertyInfo = DOMHTMLInputElementK
    type AttrGetType DOMHTMLInputElementTypePropertyInfo = T.Text
    type AttrLabel DOMHTMLInputElementTypePropertyInfo = "DOMHTMLInputElement::type"
    attrGet _ = getDOMHTMLInputElementType
    attrSet _ = setDOMHTMLInputElementType
    attrConstruct _ = constructDOMHTMLInputElementType

-- VVV Prop "use-map"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]

getDOMHTMLInputElementUseMap :: (MonadIO m, DOMHTMLInputElementK o) => o -> m T.Text
getDOMHTMLInputElementUseMap obj = liftIO $ getObjectPropertyString obj "use-map"

setDOMHTMLInputElementUseMap :: (MonadIO m, DOMHTMLInputElementK o) => o -> T.Text -> m ()
setDOMHTMLInputElementUseMap obj val = liftIO $ setObjectPropertyString obj "use-map" val

constructDOMHTMLInputElementUseMap :: T.Text -> IO ([Char], GValue)
constructDOMHTMLInputElementUseMap val = constructObjectPropertyString "use-map" val

data DOMHTMLInputElementUseMapPropertyInfo
instance AttrInfo DOMHTMLInputElementUseMapPropertyInfo where
    type AttrAllowedOps DOMHTMLInputElementUseMapPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint DOMHTMLInputElementUseMapPropertyInfo = (~) T.Text
    type AttrBaseTypeConstraint DOMHTMLInputElementUseMapPropertyInfo = DOMHTMLInputElementK
    type AttrGetType DOMHTMLInputElementUseMapPropertyInfo = T.Text
    type AttrLabel DOMHTMLInputElementUseMapPropertyInfo = "DOMHTMLInputElement::use-map"
    attrGet _ = getDOMHTMLInputElementUseMap
    attrSet _ = setDOMHTMLInputElementUseMap
    attrConstruct _ = constructDOMHTMLInputElementUseMap

-- VVV Prop "validation-message"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable]

getDOMHTMLInputElementValidationMessage :: (MonadIO m, DOMHTMLInputElementK o) => o -> m T.Text
getDOMHTMLInputElementValidationMessage obj = liftIO $ getObjectPropertyString obj "validation-message"

data DOMHTMLInputElementValidationMessagePropertyInfo
instance AttrInfo DOMHTMLInputElementValidationMessagePropertyInfo where
    type AttrAllowedOps DOMHTMLInputElementValidationMessagePropertyInfo = '[ 'AttrGet]
    type AttrSetTypeConstraint DOMHTMLInputElementValidationMessagePropertyInfo = (~) ()
    type AttrBaseTypeConstraint DOMHTMLInputElementValidationMessagePropertyInfo = DOMHTMLInputElementK
    type AttrGetType DOMHTMLInputElementValidationMessagePropertyInfo = T.Text
    type AttrLabel DOMHTMLInputElementValidationMessagePropertyInfo = "DOMHTMLInputElement::validation-message"
    attrGet _ = getDOMHTMLInputElementValidationMessage
    attrSet _ = undefined
    attrConstruct _ = undefined

-- VVV Prop "validity"
   -- Type: TInterface "WebKit" "DOMValidityState"
   -- Flags: [PropertyReadable]

getDOMHTMLInputElementValidity :: (MonadIO m, DOMHTMLInputElementK o) => o -> m DOMValidityState
getDOMHTMLInputElementValidity obj = liftIO $ getObjectPropertyObject obj "validity" DOMValidityState

data DOMHTMLInputElementValidityPropertyInfo
instance AttrInfo DOMHTMLInputElementValidityPropertyInfo where
    type AttrAllowedOps DOMHTMLInputElementValidityPropertyInfo = '[ 'AttrGet]
    type AttrSetTypeConstraint DOMHTMLInputElementValidityPropertyInfo = (~) ()
    type AttrBaseTypeConstraint DOMHTMLInputElementValidityPropertyInfo = DOMHTMLInputElementK
    type AttrGetType DOMHTMLInputElementValidityPropertyInfo = DOMValidityState
    type AttrLabel DOMHTMLInputElementValidityPropertyInfo = "DOMHTMLInputElement::validity"
    attrGet _ = getDOMHTMLInputElementValidity
    attrSet _ = undefined
    attrConstruct _ = undefined

-- VVV Prop "value"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]

getDOMHTMLInputElementValue :: (MonadIO m, DOMHTMLInputElementK o) => o -> m T.Text
getDOMHTMLInputElementValue obj = liftIO $ getObjectPropertyString obj "value"

setDOMHTMLInputElementValue :: (MonadIO m, DOMHTMLInputElementK o) => o -> T.Text -> m ()
setDOMHTMLInputElementValue obj val = liftIO $ setObjectPropertyString obj "value" val

constructDOMHTMLInputElementValue :: T.Text -> IO ([Char], GValue)
constructDOMHTMLInputElementValue val = constructObjectPropertyString "value" val

data DOMHTMLInputElementValuePropertyInfo
instance AttrInfo DOMHTMLInputElementValuePropertyInfo where
    type AttrAllowedOps DOMHTMLInputElementValuePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint DOMHTMLInputElementValuePropertyInfo = (~) T.Text
    type AttrBaseTypeConstraint DOMHTMLInputElementValuePropertyInfo = DOMHTMLInputElementK
    type AttrGetType DOMHTMLInputElementValuePropertyInfo = T.Text
    type AttrLabel DOMHTMLInputElementValuePropertyInfo = "DOMHTMLInputElement::value"
    attrGet _ = getDOMHTMLInputElementValue
    attrSet _ = setDOMHTMLInputElementValue
    attrConstruct _ = constructDOMHTMLInputElementValue

-- VVV Prop "value-as-number"
   -- Type: TBasicType TDouble
   -- Flags: [PropertyReadable,PropertyWritable]

getDOMHTMLInputElementValueAsNumber :: (MonadIO m, DOMHTMLInputElementK o) => o -> m Double
getDOMHTMLInputElementValueAsNumber obj = liftIO $ getObjectPropertyDouble obj "value-as-number"

setDOMHTMLInputElementValueAsNumber :: (MonadIO m, DOMHTMLInputElementK o) => o -> Double -> m ()
setDOMHTMLInputElementValueAsNumber obj val = liftIO $ setObjectPropertyDouble obj "value-as-number" val

constructDOMHTMLInputElementValueAsNumber :: Double -> IO ([Char], GValue)
constructDOMHTMLInputElementValueAsNumber val = constructObjectPropertyDouble "value-as-number" val

data DOMHTMLInputElementValueAsNumberPropertyInfo
instance AttrInfo DOMHTMLInputElementValueAsNumberPropertyInfo where
    type AttrAllowedOps DOMHTMLInputElementValueAsNumberPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint DOMHTMLInputElementValueAsNumberPropertyInfo = (~) Double
    type AttrBaseTypeConstraint DOMHTMLInputElementValueAsNumberPropertyInfo = DOMHTMLInputElementK
    type AttrGetType DOMHTMLInputElementValueAsNumberPropertyInfo = Double
    type AttrLabel DOMHTMLInputElementValueAsNumberPropertyInfo = "DOMHTMLInputElement::value-as-number"
    attrGet _ = getDOMHTMLInputElementValueAsNumber
    attrSet _ = setDOMHTMLInputElementValueAsNumber
    attrConstruct _ = constructDOMHTMLInputElementValueAsNumber

-- VVV Prop "webkit-grammar"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]

getDOMHTMLInputElementWebkitGrammar :: (MonadIO m, DOMHTMLInputElementK o) => o -> m Bool
getDOMHTMLInputElementWebkitGrammar obj = liftIO $ getObjectPropertyBool obj "webkit-grammar"

setDOMHTMLInputElementWebkitGrammar :: (MonadIO m, DOMHTMLInputElementK o) => o -> Bool -> m ()
setDOMHTMLInputElementWebkitGrammar obj val = liftIO $ setObjectPropertyBool obj "webkit-grammar" val

constructDOMHTMLInputElementWebkitGrammar :: Bool -> IO ([Char], GValue)
constructDOMHTMLInputElementWebkitGrammar val = constructObjectPropertyBool "webkit-grammar" val

data DOMHTMLInputElementWebkitGrammarPropertyInfo
instance AttrInfo DOMHTMLInputElementWebkitGrammarPropertyInfo where
    type AttrAllowedOps DOMHTMLInputElementWebkitGrammarPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint DOMHTMLInputElementWebkitGrammarPropertyInfo = (~) Bool
    type AttrBaseTypeConstraint DOMHTMLInputElementWebkitGrammarPropertyInfo = DOMHTMLInputElementK
    type AttrGetType DOMHTMLInputElementWebkitGrammarPropertyInfo = Bool
    type AttrLabel DOMHTMLInputElementWebkitGrammarPropertyInfo = "DOMHTMLInputElement::webkit-grammar"
    attrGet _ = getDOMHTMLInputElementWebkitGrammar
    attrSet _ = setDOMHTMLInputElementWebkitGrammar
    attrConstruct _ = constructDOMHTMLInputElementWebkitGrammar

-- VVV Prop "webkit-speech"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]

getDOMHTMLInputElementWebkitSpeech :: (MonadIO m, DOMHTMLInputElementK o) => o -> m Bool
getDOMHTMLInputElementWebkitSpeech obj = liftIO $ getObjectPropertyBool obj "webkit-speech"

setDOMHTMLInputElementWebkitSpeech :: (MonadIO m, DOMHTMLInputElementK o) => o -> Bool -> m ()
setDOMHTMLInputElementWebkitSpeech obj val = liftIO $ setObjectPropertyBool obj "webkit-speech" val

constructDOMHTMLInputElementWebkitSpeech :: Bool -> IO ([Char], GValue)
constructDOMHTMLInputElementWebkitSpeech val = constructObjectPropertyBool "webkit-speech" val

data DOMHTMLInputElementWebkitSpeechPropertyInfo
instance AttrInfo DOMHTMLInputElementWebkitSpeechPropertyInfo where
    type AttrAllowedOps DOMHTMLInputElementWebkitSpeechPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint DOMHTMLInputElementWebkitSpeechPropertyInfo = (~) Bool
    type AttrBaseTypeConstraint DOMHTMLInputElementWebkitSpeechPropertyInfo = DOMHTMLInputElementK
    type AttrGetType DOMHTMLInputElementWebkitSpeechPropertyInfo = Bool
    type AttrLabel DOMHTMLInputElementWebkitSpeechPropertyInfo = "DOMHTMLInputElement::webkit-speech"
    attrGet _ = getDOMHTMLInputElementWebkitSpeech
    attrSet _ = setDOMHTMLInputElementWebkitSpeech
    attrConstruct _ = constructDOMHTMLInputElementWebkitSpeech

-- VVV Prop "webkitdirectory"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]

getDOMHTMLInputElementWebkitdirectory :: (MonadIO m, DOMHTMLInputElementK o) => o -> m Bool
getDOMHTMLInputElementWebkitdirectory obj = liftIO $ getObjectPropertyBool obj "webkitdirectory"

setDOMHTMLInputElementWebkitdirectory :: (MonadIO m, DOMHTMLInputElementK o) => o -> Bool -> m ()
setDOMHTMLInputElementWebkitdirectory obj val = liftIO $ setObjectPropertyBool obj "webkitdirectory" val

constructDOMHTMLInputElementWebkitdirectory :: Bool -> IO ([Char], GValue)
constructDOMHTMLInputElementWebkitdirectory val = constructObjectPropertyBool "webkitdirectory" val

data DOMHTMLInputElementWebkitdirectoryPropertyInfo
instance AttrInfo DOMHTMLInputElementWebkitdirectoryPropertyInfo where
    type AttrAllowedOps DOMHTMLInputElementWebkitdirectoryPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint DOMHTMLInputElementWebkitdirectoryPropertyInfo = (~) Bool
    type AttrBaseTypeConstraint DOMHTMLInputElementWebkitdirectoryPropertyInfo = DOMHTMLInputElementK
    type AttrGetType DOMHTMLInputElementWebkitdirectoryPropertyInfo = Bool
    type AttrLabel DOMHTMLInputElementWebkitdirectoryPropertyInfo = "DOMHTMLInputElement::webkitdirectory"
    attrGet _ = getDOMHTMLInputElementWebkitdirectory
    attrSet _ = setDOMHTMLInputElementWebkitdirectory
    attrConstruct _ = constructDOMHTMLInputElementWebkitdirectory

-- VVV Prop "width"
   -- Type: TBasicType TUInt64
   -- Flags: [PropertyReadable,PropertyWritable]

getDOMHTMLInputElementWidth :: (MonadIO m, DOMHTMLInputElementK o) => o -> m Word64
getDOMHTMLInputElementWidth obj = liftIO $ getObjectPropertyUInt64 obj "width"

setDOMHTMLInputElementWidth :: (MonadIO m, DOMHTMLInputElementK o) => o -> Word64 -> m ()
setDOMHTMLInputElementWidth obj val = liftIO $ setObjectPropertyUInt64 obj "width" val

constructDOMHTMLInputElementWidth :: Word64 -> IO ([Char], GValue)
constructDOMHTMLInputElementWidth val = constructObjectPropertyUInt64 "width" val

data DOMHTMLInputElementWidthPropertyInfo
instance AttrInfo DOMHTMLInputElementWidthPropertyInfo where
    type AttrAllowedOps DOMHTMLInputElementWidthPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint DOMHTMLInputElementWidthPropertyInfo = (~) Word64
    type AttrBaseTypeConstraint DOMHTMLInputElementWidthPropertyInfo = DOMHTMLInputElementK
    type AttrGetType DOMHTMLInputElementWidthPropertyInfo = Word64
    type AttrLabel DOMHTMLInputElementWidthPropertyInfo = "DOMHTMLInputElement::width"
    attrGet _ = getDOMHTMLInputElementWidth
    attrSet _ = setDOMHTMLInputElementWidth
    attrConstruct _ = constructDOMHTMLInputElementWidth

-- VVV Prop "will-validate"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable]

getDOMHTMLInputElementWillValidate :: (MonadIO m, DOMHTMLInputElementK o) => o -> m Bool
getDOMHTMLInputElementWillValidate obj = liftIO $ getObjectPropertyBool obj "will-validate"

data DOMHTMLInputElementWillValidatePropertyInfo
instance AttrInfo DOMHTMLInputElementWillValidatePropertyInfo where
    type AttrAllowedOps DOMHTMLInputElementWillValidatePropertyInfo = '[ 'AttrGet]
    type AttrSetTypeConstraint DOMHTMLInputElementWillValidatePropertyInfo = (~) ()
    type AttrBaseTypeConstraint DOMHTMLInputElementWillValidatePropertyInfo = DOMHTMLInputElementK
    type AttrGetType DOMHTMLInputElementWillValidatePropertyInfo = Bool
    type AttrLabel DOMHTMLInputElementWillValidatePropertyInfo = "DOMHTMLInputElement::will-validate"
    attrGet _ = getDOMHTMLInputElementWillValidate
    attrSet _ = undefined
    attrConstruct _ = undefined

type instance AttributeList DOMHTMLInputElement = DOMHTMLInputElementAttributeList
type DOMHTMLInputElementAttributeList = ('[ '("accept", DOMHTMLInputElementAcceptPropertyInfo), '("access-key", DOMHTMLElementAccessKeyPropertyInfo), '("align", DOMHTMLInputElementAlignPropertyInfo), '("alt", DOMHTMLInputElementAltPropertyInfo), '("attributes", DOMElementAttributesPropertyInfo), '("autocapitalize", DOMHTMLInputElementAutocapitalizePropertyInfo), '("autocomplete", DOMHTMLInputElementAutocompletePropertyInfo), '("autocorrect", DOMHTMLInputElementAutocorrectPropertyInfo), '("autofocus", DOMHTMLInputElementAutofocusPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("capture", DOMHTMLInputElementCapturePropertyInfo), '("checked", DOMHTMLInputElementCheckedPropertyInfo), '("child-element-count", DOMElementChildElementCountPropertyInfo), '("child-nodes", DOMNodeChildNodesPropertyInfo), '("children", DOMHTMLElementChildrenPropertyInfo), '("class-list", DOMElementClassListPropertyInfo), '("class-name", DOMElementClassNamePropertyInfo), '("client-height", DOMElementClientHeightPropertyInfo), '("client-left", DOMElementClientLeftPropertyInfo), '("client-top", DOMElementClientTopPropertyInfo), '("client-width", DOMElementClientWidthPropertyInfo), '("content-editable", DOMHTMLElementContentEditablePropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("default-checked", DOMHTMLInputElementDefaultCheckedPropertyInfo), '("default-value", DOMHTMLInputElementDefaultValuePropertyInfo), '("dir", DOMHTMLElementDirPropertyInfo), '("dir-name", DOMHTMLInputElementDirNamePropertyInfo), '("disabled", DOMHTMLInputElementDisabledPropertyInfo), '("draggable", DOMHTMLElementDraggablePropertyInfo), '("files", DOMHTMLInputElementFilesPropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("first-element-child", DOMElementFirstElementChildPropertyInfo), '("form", DOMHTMLInputElementFormPropertyInfo), '("form-action", DOMHTMLInputElementFormActionPropertyInfo), '("form-enctype", DOMHTMLInputElementFormEnctypePropertyInfo), '("form-method", DOMHTMLInputElementFormMethodPropertyInfo), '("form-no-validate", DOMHTMLInputElementFormNoValidatePropertyInfo), '("form-target", DOMHTMLInputElementFormTargetPropertyInfo), '("height", DOMHTMLInputElementHeightPropertyInfo), '("hidden", DOMHTMLElementHiddenPropertyInfo), '("id", DOMElementIdPropertyInfo), '("incremental", DOMHTMLInputElementIncrementalPropertyInfo), '("indeterminate", DOMHTMLInputElementIndeterminatePropertyInfo), '("inner-html", DOMHTMLElementInnerHtmlPropertyInfo), '("inner-text", DOMHTMLElementInnerTextPropertyInfo), '("is-content-editable", DOMHTMLElementIsContentEditablePropertyInfo), '("labels", DOMHTMLInputElementLabelsPropertyInfo), '("lang", DOMHTMLElementLangPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-element-child", DOMElementLastElementChildPropertyInfo), '("list", DOMHTMLInputElementListPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("max", DOMHTMLInputElementMaxPropertyInfo), '("max-length", DOMHTMLInputElementMaxLengthPropertyInfo), '("min", DOMHTMLInputElementMinPropertyInfo), '("multiple", DOMHTMLInputElementMultiplePropertyInfo), '("name", DOMHTMLInputElementNamePropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("next-element-sibling", DOMElementNextElementSiblingPropertyInfo), '("next-sibling", DOMNodeNextSiblingPropertyInfo), '("node-name", DOMNodeNodeNamePropertyInfo), '("node-type", DOMNodeNodeTypePropertyInfo), '("node-value", DOMNodeNodeValuePropertyInfo), '("offset-height", DOMElementOffsetHeightPropertyInfo), '("offset-left", DOMElementOffsetLeftPropertyInfo), '("offset-parent", DOMElementOffsetParentPropertyInfo), '("offset-top", DOMElementOffsetTopPropertyInfo), '("offset-width", DOMElementOffsetWidthPropertyInfo), '("outer-html", DOMHTMLElementOuterHtmlPropertyInfo), '("outer-text", DOMHTMLElementOuterTextPropertyInfo), '("owner-document", DOMNodeOwnerDocumentPropertyInfo), '("parent-element", DOMNodeParentElementPropertyInfo), '("parent-node", DOMNodeParentNodePropertyInfo), '("pattern", DOMHTMLInputElementPatternPropertyInfo), '("placeholder", DOMHTMLInputElementPlaceholderPropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("previous-element-sibling", DOMElementPreviousElementSiblingPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("read-only", DOMHTMLInputElementReadOnlyPropertyInfo), '("required", DOMHTMLInputElementRequiredPropertyInfo), '("scroll-height", DOMElementScrollHeightPropertyInfo), '("scroll-left", DOMElementScrollLeftPropertyInfo), '("scroll-top", DOMElementScrollTopPropertyInfo), '("scroll-width", DOMElementScrollWidthPropertyInfo), '("size", DOMHTMLInputElementSizePropertyInfo), '("spellcheck", DOMHTMLElementSpellcheckPropertyInfo), '("src", DOMHTMLInputElementSrcPropertyInfo), '("step", DOMHTMLInputElementStepPropertyInfo), '("style", DOMElementStylePropertyInfo), '("tab-index", DOMHTMLElementTabIndexPropertyInfo), '("tag-name", DOMElementTagNamePropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("title", DOMHTMLElementTitlePropertyInfo), '("translate", DOMHTMLElementTranslatePropertyInfo), '("type", DOMHTMLInputElementTypePropertyInfo), '("use-map", DOMHTMLInputElementUseMapPropertyInfo), '("validation-message", DOMHTMLInputElementValidationMessagePropertyInfo), '("validity", DOMHTMLInputElementValidityPropertyInfo), '("value", DOMHTMLInputElementValuePropertyInfo), '("value-as-number", DOMHTMLInputElementValueAsNumberPropertyInfo), '("webkit-grammar", DOMHTMLInputElementWebkitGrammarPropertyInfo), '("webkit-region-overset", DOMElementWebkitRegionOversetPropertyInfo), '("webkit-speech", DOMHTMLInputElementWebkitSpeechPropertyInfo), '("webkitdirectory", DOMHTMLInputElementWebkitdirectoryPropertyInfo), '("webkitdropzone", DOMHTMLElementWebkitdropzonePropertyInfo), '("width", DOMHTMLInputElementWidthPropertyInfo), '("will-validate", DOMHTMLInputElementWillValidatePropertyInfo)] :: [(Symbol, *)])

type instance SignalList DOMHTMLInputElement = DOMHTMLInputElementSignalList
type DOMHTMLInputElementSignalList = ('[ '("notify", GObject.ObjectNotifySignalInfo), '("notify::[property]", GObjectNotifySignalInfo)] :: [(Symbol, *)])

-- method DOMHTMLInputElement::check_validity
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_check_validity" webkit_dom_html_input_element_check_validity :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    IO CInt


dOMHTMLInputElementCheckValidity ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    m Bool
dOMHTMLInputElementCheckValidity _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- webkit_dom_html_input_element_check_validity _obj'
    let result' = (/= 0) result
    touchManagedPtr _obj
    return result'

-- method DOMHTMLInputElement::get_accept
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_get_accept" webkit_dom_html_input_element_get_accept :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    IO CString


dOMHTMLInputElementGetAccept ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    m T.Text
dOMHTMLInputElementGetAccept _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- webkit_dom_html_input_element_get_accept _obj'
    checkUnexpectedReturnNULL "webkit_dom_html_input_element_get_accept" result
    result' <- cstringToText result
    freeMem result
    touchManagedPtr _obj
    return result'

-- method DOMHTMLInputElement::get_align
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_get_align" webkit_dom_html_input_element_get_align :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    IO CString


dOMHTMLInputElementGetAlign ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    m T.Text
dOMHTMLInputElementGetAlign _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- webkit_dom_html_input_element_get_align _obj'
    checkUnexpectedReturnNULL "webkit_dom_html_input_element_get_align" result
    result' <- cstringToText result
    freeMem result
    touchManagedPtr _obj
    return result'

-- method DOMHTMLInputElement::get_alt
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_get_alt" webkit_dom_html_input_element_get_alt :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    IO CString


dOMHTMLInputElementGetAlt ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    m T.Text
dOMHTMLInputElementGetAlt _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- webkit_dom_html_input_element_get_alt _obj'
    checkUnexpectedReturnNULL "webkit_dom_html_input_element_get_alt" result
    result' <- cstringToText result
    freeMem result
    touchManagedPtr _obj
    return result'

-- method DOMHTMLInputElement::get_autocapitalize
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_get_autocapitalize" webkit_dom_html_input_element_get_autocapitalize :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    IO CString


dOMHTMLInputElementGetAutocapitalize ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    m T.Text
dOMHTMLInputElementGetAutocapitalize _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- webkit_dom_html_input_element_get_autocapitalize _obj'
    checkUnexpectedReturnNULL "webkit_dom_html_input_element_get_autocapitalize" result
    result' <- cstringToText result
    freeMem result
    touchManagedPtr _obj
    return result'

-- method DOMHTMLInputElement::get_autocomplete
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_get_autocomplete" webkit_dom_html_input_element_get_autocomplete :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    IO CString


dOMHTMLInputElementGetAutocomplete ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    m T.Text
dOMHTMLInputElementGetAutocomplete _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- webkit_dom_html_input_element_get_autocomplete _obj'
    checkUnexpectedReturnNULL "webkit_dom_html_input_element_get_autocomplete" result
    result' <- cstringToText result
    freeMem result
    touchManagedPtr _obj
    return result'

-- method DOMHTMLInputElement::get_autocorrect
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_get_autocorrect" webkit_dom_html_input_element_get_autocorrect :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    IO CInt


dOMHTMLInputElementGetAutocorrect ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    m Bool
dOMHTMLInputElementGetAutocorrect _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- webkit_dom_html_input_element_get_autocorrect _obj'
    let result' = (/= 0) result
    touchManagedPtr _obj
    return result'

-- method DOMHTMLInputElement::get_autofocus
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_get_autofocus" webkit_dom_html_input_element_get_autofocus :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    IO CInt


dOMHTMLInputElementGetAutofocus ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    m Bool
dOMHTMLInputElementGetAutofocus _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- webkit_dom_html_input_element_get_autofocus _obj'
    let result' = (/= 0) result
    touchManagedPtr _obj
    return result'

-- method DOMHTMLInputElement::get_capture
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_get_capture" webkit_dom_html_input_element_get_capture :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    IO CString


dOMHTMLInputElementGetCapture ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    m T.Text
dOMHTMLInputElementGetCapture _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- webkit_dom_html_input_element_get_capture _obj'
    checkUnexpectedReturnNULL "webkit_dom_html_input_element_get_capture" result
    result' <- cstringToText result
    freeMem result
    touchManagedPtr _obj
    return result'

-- method DOMHTMLInputElement::get_checked
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_get_checked" webkit_dom_html_input_element_get_checked :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    IO CInt


dOMHTMLInputElementGetChecked ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    m Bool
dOMHTMLInputElementGetChecked _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- webkit_dom_html_input_element_get_checked _obj'
    let result' = (/= 0) result
    touchManagedPtr _obj
    return result'

-- method DOMHTMLInputElement::get_default_checked
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_get_default_checked" webkit_dom_html_input_element_get_default_checked :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    IO CInt


dOMHTMLInputElementGetDefaultChecked ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    m Bool
dOMHTMLInputElementGetDefaultChecked _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- webkit_dom_html_input_element_get_default_checked _obj'
    let result' = (/= 0) result
    touchManagedPtr _obj
    return result'

-- method DOMHTMLInputElement::get_default_value
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_get_default_value" webkit_dom_html_input_element_get_default_value :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    IO CString


dOMHTMLInputElementGetDefaultValue ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    m T.Text
dOMHTMLInputElementGetDefaultValue _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- webkit_dom_html_input_element_get_default_value _obj'
    checkUnexpectedReturnNULL "webkit_dom_html_input_element_get_default_value" result
    result' <- cstringToText result
    freeMem result
    touchManagedPtr _obj
    return result'

-- method DOMHTMLInputElement::get_dir_name
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_get_dir_name" webkit_dom_html_input_element_get_dir_name :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    IO CString


dOMHTMLInputElementGetDirName ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    m T.Text
dOMHTMLInputElementGetDirName _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- webkit_dom_html_input_element_get_dir_name _obj'
    checkUnexpectedReturnNULL "webkit_dom_html_input_element_get_dir_name" result
    result' <- cstringToText result
    freeMem result
    touchManagedPtr _obj
    return result'

-- method DOMHTMLInputElement::get_disabled
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_get_disabled" webkit_dom_html_input_element_get_disabled :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    IO CInt


dOMHTMLInputElementGetDisabled ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    m Bool
dOMHTMLInputElementGetDisabled _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- webkit_dom_html_input_element_get_disabled _obj'
    let result' = (/= 0) result
    touchManagedPtr _obj
    return result'

-- method DOMHTMLInputElement::get_files
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "WebKit" "DOMFileList"
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_get_files" webkit_dom_html_input_element_get_files :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    IO (Ptr DOMFileList)


dOMHTMLInputElementGetFiles ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    m DOMFileList
dOMHTMLInputElementGetFiles _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- webkit_dom_html_input_element_get_files _obj'
    checkUnexpectedReturnNULL "webkit_dom_html_input_element_get_files" result
    result' <- (wrapObject DOMFileList) result
    touchManagedPtr _obj
    return result'

-- method DOMHTMLInputElement::get_form
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "WebKit" "DOMHTMLFormElement"
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_get_form" webkit_dom_html_input_element_get_form :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    IO (Ptr DOMHTMLFormElement)


dOMHTMLInputElementGetForm ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    m DOMHTMLFormElement
dOMHTMLInputElementGetForm _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- webkit_dom_html_input_element_get_form _obj'
    checkUnexpectedReturnNULL "webkit_dom_html_input_element_get_form" result
    result' <- (newObject DOMHTMLFormElement) result
    touchManagedPtr _obj
    return result'

-- method DOMHTMLInputElement::get_form_action
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_get_form_action" webkit_dom_html_input_element_get_form_action :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    IO CString


dOMHTMLInputElementGetFormAction ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    m T.Text
dOMHTMLInputElementGetFormAction _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- webkit_dom_html_input_element_get_form_action _obj'
    checkUnexpectedReturnNULL "webkit_dom_html_input_element_get_form_action" result
    result' <- cstringToText result
    freeMem result
    touchManagedPtr _obj
    return result'

-- method DOMHTMLInputElement::get_form_enctype
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_get_form_enctype" webkit_dom_html_input_element_get_form_enctype :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    IO CString


dOMHTMLInputElementGetFormEnctype ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    m T.Text
dOMHTMLInputElementGetFormEnctype _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- webkit_dom_html_input_element_get_form_enctype _obj'
    checkUnexpectedReturnNULL "webkit_dom_html_input_element_get_form_enctype" result
    result' <- cstringToText result
    freeMem result
    touchManagedPtr _obj
    return result'

-- method DOMHTMLInputElement::get_form_method
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_get_form_method" webkit_dom_html_input_element_get_form_method :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    IO CString


dOMHTMLInputElementGetFormMethod ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    m T.Text
dOMHTMLInputElementGetFormMethod _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- webkit_dom_html_input_element_get_form_method _obj'
    checkUnexpectedReturnNULL "webkit_dom_html_input_element_get_form_method" result
    result' <- cstringToText result
    freeMem result
    touchManagedPtr _obj
    return result'

-- method DOMHTMLInputElement::get_form_no_validate
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_get_form_no_validate" webkit_dom_html_input_element_get_form_no_validate :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    IO CInt


dOMHTMLInputElementGetFormNoValidate ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    m Bool
dOMHTMLInputElementGetFormNoValidate _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- webkit_dom_html_input_element_get_form_no_validate _obj'
    let result' = (/= 0) result
    touchManagedPtr _obj
    return result'

-- method DOMHTMLInputElement::get_form_target
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_get_form_target" webkit_dom_html_input_element_get_form_target :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    IO CString


dOMHTMLInputElementGetFormTarget ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    m T.Text
dOMHTMLInputElementGetFormTarget _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- webkit_dom_html_input_element_get_form_target _obj'
    checkUnexpectedReturnNULL "webkit_dom_html_input_element_get_form_target" result
    result' <- cstringToText result
    freeMem result
    touchManagedPtr _obj
    return result'

-- method DOMHTMLInputElement::get_height
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUInt64
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_get_height" webkit_dom_html_input_element_get_height :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    IO Word64


dOMHTMLInputElementGetHeight ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    m Word64
dOMHTMLInputElementGetHeight _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- webkit_dom_html_input_element_get_height _obj'
    touchManagedPtr _obj
    return result

-- method DOMHTMLInputElement::get_incremental
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_get_incremental" webkit_dom_html_input_element_get_incremental :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    IO CInt


dOMHTMLInputElementGetIncremental ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    m Bool
dOMHTMLInputElementGetIncremental _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- webkit_dom_html_input_element_get_incremental _obj'
    let result' = (/= 0) result
    touchManagedPtr _obj
    return result'

-- method DOMHTMLInputElement::get_indeterminate
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_get_indeterminate" webkit_dom_html_input_element_get_indeterminate :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    IO CInt


dOMHTMLInputElementGetIndeterminate ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    m Bool
dOMHTMLInputElementGetIndeterminate _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- webkit_dom_html_input_element_get_indeterminate _obj'
    let result' = (/= 0) result
    touchManagedPtr _obj
    return result'

-- method DOMHTMLInputElement::get_labels
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "WebKit" "DOMNodeList"
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_get_labels" webkit_dom_html_input_element_get_labels :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    IO (Ptr DOMNodeList)


dOMHTMLInputElementGetLabels ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    m DOMNodeList
dOMHTMLInputElementGetLabels _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- webkit_dom_html_input_element_get_labels _obj'
    checkUnexpectedReturnNULL "webkit_dom_html_input_element_get_labels" result
    result' <- (wrapObject DOMNodeList) result
    touchManagedPtr _obj
    return result'

-- method DOMHTMLInputElement::get_list
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "WebKit" "DOMHTMLElement"
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_get_list" webkit_dom_html_input_element_get_list :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    IO (Ptr DOMHTMLElement)


dOMHTMLInputElementGetList ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    m DOMHTMLElement
dOMHTMLInputElementGetList _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- webkit_dom_html_input_element_get_list _obj'
    checkUnexpectedReturnNULL "webkit_dom_html_input_element_get_list" result
    result' <- (newObject DOMHTMLElement) result
    touchManagedPtr _obj
    return result'

-- method DOMHTMLInputElement::get_max
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_get_max" webkit_dom_html_input_element_get_max :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    IO CString


dOMHTMLInputElementGetMax ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    m T.Text
dOMHTMLInputElementGetMax _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- webkit_dom_html_input_element_get_max _obj'
    checkUnexpectedReturnNULL "webkit_dom_html_input_element_get_max" result
    result' <- cstringToText result
    freeMem result
    touchManagedPtr _obj
    return result'

-- method DOMHTMLInputElement::get_max_length
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TInt64
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_get_max_length" webkit_dom_html_input_element_get_max_length :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    IO Int64


dOMHTMLInputElementGetMaxLength ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    m Int64
dOMHTMLInputElementGetMaxLength _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- webkit_dom_html_input_element_get_max_length _obj'
    touchManagedPtr _obj
    return result

-- method DOMHTMLInputElement::get_min
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_get_min" webkit_dom_html_input_element_get_min :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    IO CString


dOMHTMLInputElementGetMin ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    m T.Text
dOMHTMLInputElementGetMin _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- webkit_dom_html_input_element_get_min _obj'
    checkUnexpectedReturnNULL "webkit_dom_html_input_element_get_min" result
    result' <- cstringToText result
    freeMem result
    touchManagedPtr _obj
    return result'

-- method DOMHTMLInputElement::get_multiple
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_get_multiple" webkit_dom_html_input_element_get_multiple :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    IO CInt


dOMHTMLInputElementGetMultiple ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    m Bool
dOMHTMLInputElementGetMultiple _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- webkit_dom_html_input_element_get_multiple _obj'
    let result' = (/= 0) result
    touchManagedPtr _obj
    return result'

-- method DOMHTMLInputElement::get_name
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_get_name" webkit_dom_html_input_element_get_name :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    IO CString


dOMHTMLInputElementGetName ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    m T.Text
dOMHTMLInputElementGetName _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- webkit_dom_html_input_element_get_name _obj'
    checkUnexpectedReturnNULL "webkit_dom_html_input_element_get_name" result
    result' <- cstringToText result
    freeMem result
    touchManagedPtr _obj
    return result'

-- method DOMHTMLInputElement::get_pattern
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_get_pattern" webkit_dom_html_input_element_get_pattern :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    IO CString


dOMHTMLInputElementGetPattern ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    m T.Text
dOMHTMLInputElementGetPattern _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- webkit_dom_html_input_element_get_pattern _obj'
    checkUnexpectedReturnNULL "webkit_dom_html_input_element_get_pattern" result
    result' <- cstringToText result
    freeMem result
    touchManagedPtr _obj
    return result'

-- method DOMHTMLInputElement::get_placeholder
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_get_placeholder" webkit_dom_html_input_element_get_placeholder :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    IO CString


dOMHTMLInputElementGetPlaceholder ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    m T.Text
dOMHTMLInputElementGetPlaceholder _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- webkit_dom_html_input_element_get_placeholder _obj'
    checkUnexpectedReturnNULL "webkit_dom_html_input_element_get_placeholder" result
    result' <- cstringToText result
    freeMem result
    touchManagedPtr _obj
    return result'

-- method DOMHTMLInputElement::get_read_only
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_get_read_only" webkit_dom_html_input_element_get_read_only :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    IO CInt


dOMHTMLInputElementGetReadOnly ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    m Bool
dOMHTMLInputElementGetReadOnly _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- webkit_dom_html_input_element_get_read_only _obj'
    let result' = (/= 0) result
    touchManagedPtr _obj
    return result'

-- method DOMHTMLInputElement::get_required
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_get_required" webkit_dom_html_input_element_get_required :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    IO CInt


dOMHTMLInputElementGetRequired ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    m Bool
dOMHTMLInputElementGetRequired _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- webkit_dom_html_input_element_get_required _obj'
    let result' = (/= 0) result
    touchManagedPtr _obj
    return result'

-- method DOMHTMLInputElement::get_size
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUInt64
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_get_size" webkit_dom_html_input_element_get_size :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    IO Word64


dOMHTMLInputElementGetSize ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    m Word64
dOMHTMLInputElementGetSize _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- webkit_dom_html_input_element_get_size _obj'
    touchManagedPtr _obj
    return result

-- method DOMHTMLInputElement::get_src
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_get_src" webkit_dom_html_input_element_get_src :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    IO CString


dOMHTMLInputElementGetSrc ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    m T.Text
dOMHTMLInputElementGetSrc _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- webkit_dom_html_input_element_get_src _obj'
    checkUnexpectedReturnNULL "webkit_dom_html_input_element_get_src" result
    result' <- cstringToText result
    freeMem result
    touchManagedPtr _obj
    return result'

-- method DOMHTMLInputElement::get_step
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_get_step" webkit_dom_html_input_element_get_step :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    IO CString


dOMHTMLInputElementGetStep ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    m T.Text
dOMHTMLInputElementGetStep _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- webkit_dom_html_input_element_get_step _obj'
    checkUnexpectedReturnNULL "webkit_dom_html_input_element_get_step" result
    result' <- cstringToText result
    freeMem result
    touchManagedPtr _obj
    return result'

-- method DOMHTMLInputElement::get_use_map
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_get_use_map" webkit_dom_html_input_element_get_use_map :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    IO CString


dOMHTMLInputElementGetUseMap ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    m T.Text
dOMHTMLInputElementGetUseMap _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- webkit_dom_html_input_element_get_use_map _obj'
    checkUnexpectedReturnNULL "webkit_dom_html_input_element_get_use_map" result
    result' <- cstringToText result
    freeMem result
    touchManagedPtr _obj
    return result'

-- method DOMHTMLInputElement::get_validation_message
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_get_validation_message" webkit_dom_html_input_element_get_validation_message :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    IO CString


dOMHTMLInputElementGetValidationMessage ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    m T.Text
dOMHTMLInputElementGetValidationMessage _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- webkit_dom_html_input_element_get_validation_message _obj'
    checkUnexpectedReturnNULL "webkit_dom_html_input_element_get_validation_message" result
    result' <- cstringToText result
    freeMem result
    touchManagedPtr _obj
    return result'

-- method DOMHTMLInputElement::get_validity
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "WebKit" "DOMValidityState"
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_get_validity" webkit_dom_html_input_element_get_validity :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    IO (Ptr DOMValidityState)


dOMHTMLInputElementGetValidity ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    m DOMValidityState
dOMHTMLInputElementGetValidity _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- webkit_dom_html_input_element_get_validity _obj'
    checkUnexpectedReturnNULL "webkit_dom_html_input_element_get_validity" result
    result' <- (wrapObject DOMValidityState) result
    touchManagedPtr _obj
    return result'

-- method DOMHTMLInputElement::get_value
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_get_value" webkit_dom_html_input_element_get_value :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    IO CString


dOMHTMLInputElementGetValue ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    m T.Text
dOMHTMLInputElementGetValue _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- webkit_dom_html_input_element_get_value _obj'
    checkUnexpectedReturnNULL "webkit_dom_html_input_element_get_value" result
    result' <- cstringToText result
    freeMem result
    touchManagedPtr _obj
    return result'

-- method DOMHTMLInputElement::get_value_as_number
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TDouble
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_get_value_as_number" webkit_dom_html_input_element_get_value_as_number :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    IO CDouble


dOMHTMLInputElementGetValueAsNumber ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    m Double
dOMHTMLInputElementGetValueAsNumber _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- webkit_dom_html_input_element_get_value_as_number _obj'
    let result' = realToFrac result
    touchManagedPtr _obj
    return result'

-- method DOMHTMLInputElement::get_webkit_grammar
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_get_webkit_grammar" webkit_dom_html_input_element_get_webkit_grammar :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    IO CInt


dOMHTMLInputElementGetWebkitGrammar ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    m Bool
dOMHTMLInputElementGetWebkitGrammar _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- webkit_dom_html_input_element_get_webkit_grammar _obj'
    let result' = (/= 0) result
    touchManagedPtr _obj
    return result'

-- method DOMHTMLInputElement::get_webkit_speech
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_get_webkit_speech" webkit_dom_html_input_element_get_webkit_speech :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    IO CInt


dOMHTMLInputElementGetWebkitSpeech ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    m Bool
dOMHTMLInputElementGetWebkitSpeech _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- webkit_dom_html_input_element_get_webkit_speech _obj'
    let result' = (/= 0) result
    touchManagedPtr _obj
    return result'

-- method DOMHTMLInputElement::get_webkitdirectory
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_get_webkitdirectory" webkit_dom_html_input_element_get_webkitdirectory :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    IO CInt


dOMHTMLInputElementGetWebkitdirectory ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    m Bool
dOMHTMLInputElementGetWebkitdirectory _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- webkit_dom_html_input_element_get_webkitdirectory _obj'
    let result' = (/= 0) result
    touchManagedPtr _obj
    return result'

-- method DOMHTMLInputElement::get_width
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUInt64
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_get_width" webkit_dom_html_input_element_get_width :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    IO Word64


dOMHTMLInputElementGetWidth ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    m Word64
dOMHTMLInputElementGetWidth _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- webkit_dom_html_input_element_get_width _obj'
    touchManagedPtr _obj
    return result

-- method DOMHTMLInputElement::get_will_validate
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_get_will_validate" webkit_dom_html_input_element_get_will_validate :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    IO CInt


dOMHTMLInputElementGetWillValidate ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    m Bool
dOMHTMLInputElementGetWillValidate _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- webkit_dom_html_input_element_get_will_validate _obj'
    let result' = (/= 0) result
    touchManagedPtr _obj
    return result'

-- method DOMHTMLInputElement::is_edited
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_is_edited" webkit_dom_html_input_element_is_edited :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    IO CInt


dOMHTMLInputElementIsEdited ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    m Bool
dOMHTMLInputElementIsEdited _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- webkit_dom_html_input_element_is_edited _obj'
    let result' = (/= 0) result
    touchManagedPtr _obj
    return result'

-- method DOMHTMLInputElement::select
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_select" webkit_dom_html_input_element_select :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    IO ()


dOMHTMLInputElementSelect ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    m ()
dOMHTMLInputElementSelect _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    webkit_dom_html_input_element_select _obj'
    touchManagedPtr _obj
    return ()

-- method DOMHTMLInputElement::set_accept
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_set_accept" webkit_dom_html_input_element_set_accept :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    CString ->                              -- value : TBasicType TUTF8
    IO ()


dOMHTMLInputElementSetAccept ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    T.Text ->                               -- value
    m ()
dOMHTMLInputElementSetAccept _obj value = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    value' <- textToCString value
    webkit_dom_html_input_element_set_accept _obj' value'
    touchManagedPtr _obj
    freeMem value'
    return ()

-- method DOMHTMLInputElement::set_align
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_set_align" webkit_dom_html_input_element_set_align :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    CString ->                              -- value : TBasicType TUTF8
    IO ()


dOMHTMLInputElementSetAlign ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    T.Text ->                               -- value
    m ()
dOMHTMLInputElementSetAlign _obj value = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    value' <- textToCString value
    webkit_dom_html_input_element_set_align _obj' value'
    touchManagedPtr _obj
    freeMem value'
    return ()

-- method DOMHTMLInputElement::set_alt
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_set_alt" webkit_dom_html_input_element_set_alt :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    CString ->                              -- value : TBasicType TUTF8
    IO ()


dOMHTMLInputElementSetAlt ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    T.Text ->                               -- value
    m ()
dOMHTMLInputElementSetAlt _obj value = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    value' <- textToCString value
    webkit_dom_html_input_element_set_alt _obj' value'
    touchManagedPtr _obj
    freeMem value'
    return ()

-- method DOMHTMLInputElement::set_autocapitalize
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_set_autocapitalize" webkit_dom_html_input_element_set_autocapitalize :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    CString ->                              -- value : TBasicType TUTF8
    IO ()


dOMHTMLInputElementSetAutocapitalize ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    T.Text ->                               -- value
    m ()
dOMHTMLInputElementSetAutocapitalize _obj value = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    value' <- textToCString value
    webkit_dom_html_input_element_set_autocapitalize _obj' value'
    touchManagedPtr _obj
    freeMem value'
    return ()

-- method DOMHTMLInputElement::set_autocomplete
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_set_autocomplete" webkit_dom_html_input_element_set_autocomplete :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    CString ->                              -- value : TBasicType TUTF8
    IO ()


dOMHTMLInputElementSetAutocomplete ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    T.Text ->                               -- value
    m ()
dOMHTMLInputElementSetAutocomplete _obj value = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    value' <- textToCString value
    webkit_dom_html_input_element_set_autocomplete _obj' value'
    touchManagedPtr _obj
    freeMem value'
    return ()

-- method DOMHTMLInputElement::set_autocorrect
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_set_autocorrect" webkit_dom_html_input_element_set_autocorrect :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    CInt ->                                 -- value : TBasicType TBoolean
    IO ()


dOMHTMLInputElementSetAutocorrect ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    Bool ->                                 -- value
    m ()
dOMHTMLInputElementSetAutocorrect _obj value = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let value' = (fromIntegral . fromEnum) value
    webkit_dom_html_input_element_set_autocorrect _obj' value'
    touchManagedPtr _obj
    return ()

-- method DOMHTMLInputElement::set_autofocus
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_set_autofocus" webkit_dom_html_input_element_set_autofocus :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    CInt ->                                 -- value : TBasicType TBoolean
    IO ()


dOMHTMLInputElementSetAutofocus ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    Bool ->                                 -- value
    m ()
dOMHTMLInputElementSetAutofocus _obj value = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let value' = (fromIntegral . fromEnum) value
    webkit_dom_html_input_element_set_autofocus _obj' value'
    touchManagedPtr _obj
    return ()

-- method DOMHTMLInputElement::set_capture
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_set_capture" webkit_dom_html_input_element_set_capture :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    CString ->                              -- value : TBasicType TUTF8
    IO ()


dOMHTMLInputElementSetCapture ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    T.Text ->                               -- value
    m ()
dOMHTMLInputElementSetCapture _obj value = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    value' <- textToCString value
    webkit_dom_html_input_element_set_capture _obj' value'
    touchManagedPtr _obj
    freeMem value'
    return ()

-- method DOMHTMLInputElement::set_checked
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_set_checked" webkit_dom_html_input_element_set_checked :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    CInt ->                                 -- value : TBasicType TBoolean
    IO ()


dOMHTMLInputElementSetChecked ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    Bool ->                                 -- value
    m ()
dOMHTMLInputElementSetChecked _obj value = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let value' = (fromIntegral . fromEnum) value
    webkit_dom_html_input_element_set_checked _obj' value'
    touchManagedPtr _obj
    return ()

-- method DOMHTMLInputElement::set_custom_validity
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "error", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "error", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_set_custom_validity" webkit_dom_html_input_element_set_custom_validity :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    CString ->                              -- error : TBasicType TUTF8
    IO ()


dOMHTMLInputElementSetCustomValidity ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    T.Text ->                               -- error
    m ()
dOMHTMLInputElementSetCustomValidity _obj error_ = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    error_' <- textToCString error_
    webkit_dom_html_input_element_set_custom_validity _obj' error_'
    touchManagedPtr _obj
    freeMem error_'
    return ()

-- method DOMHTMLInputElement::set_default_checked
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_set_default_checked" webkit_dom_html_input_element_set_default_checked :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    CInt ->                                 -- value : TBasicType TBoolean
    IO ()


dOMHTMLInputElementSetDefaultChecked ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    Bool ->                                 -- value
    m ()
dOMHTMLInputElementSetDefaultChecked _obj value = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let value' = (fromIntegral . fromEnum) value
    webkit_dom_html_input_element_set_default_checked _obj' value'
    touchManagedPtr _obj
    return ()

-- method DOMHTMLInputElement::set_default_value
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_set_default_value" webkit_dom_html_input_element_set_default_value :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    CString ->                              -- value : TBasicType TUTF8
    IO ()


dOMHTMLInputElementSetDefaultValue ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    T.Text ->                               -- value
    m ()
dOMHTMLInputElementSetDefaultValue _obj value = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    value' <- textToCString value
    webkit_dom_html_input_element_set_default_value _obj' value'
    touchManagedPtr _obj
    freeMem value'
    return ()

-- method DOMHTMLInputElement::set_dir_name
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_set_dir_name" webkit_dom_html_input_element_set_dir_name :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    CString ->                              -- value : TBasicType TUTF8
    IO ()


dOMHTMLInputElementSetDirName ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    T.Text ->                               -- value
    m ()
dOMHTMLInputElementSetDirName _obj value = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    value' <- textToCString value
    webkit_dom_html_input_element_set_dir_name _obj' value'
    touchManagedPtr _obj
    freeMem value'
    return ()

-- method DOMHTMLInputElement::set_disabled
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_set_disabled" webkit_dom_html_input_element_set_disabled :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    CInt ->                                 -- value : TBasicType TBoolean
    IO ()


dOMHTMLInputElementSetDisabled ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    Bool ->                                 -- value
    m ()
dOMHTMLInputElementSetDisabled _obj value = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let value' = (fromIntegral . fromEnum) value
    webkit_dom_html_input_element_set_disabled _obj' value'
    touchManagedPtr _obj
    return ()

-- method DOMHTMLInputElement::set_files
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TInterface "WebKit" "DOMFileList", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TInterface "WebKit" "DOMFileList", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_set_files" webkit_dom_html_input_element_set_files :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    Ptr DOMFileList ->                      -- value : TInterface "WebKit" "DOMFileList"
    IO ()


dOMHTMLInputElementSetFiles ::
    (MonadIO m, DOMHTMLInputElementK a, DOMFileListK b) =>
    a ->                                    -- _obj
    b ->                                    -- value
    m ()
dOMHTMLInputElementSetFiles _obj value = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let value' = unsafeManagedPtrCastPtr value
    webkit_dom_html_input_element_set_files _obj' value'
    touchManagedPtr _obj
    touchManagedPtr value
    return ()

-- method DOMHTMLInputElement::set_form_action
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_set_form_action" webkit_dom_html_input_element_set_form_action :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    CString ->                              -- value : TBasicType TUTF8
    IO ()


dOMHTMLInputElementSetFormAction ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    T.Text ->                               -- value
    m ()
dOMHTMLInputElementSetFormAction _obj value = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    value' <- textToCString value
    webkit_dom_html_input_element_set_form_action _obj' value'
    touchManagedPtr _obj
    freeMem value'
    return ()

-- method DOMHTMLInputElement::set_form_enctype
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_set_form_enctype" webkit_dom_html_input_element_set_form_enctype :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    CString ->                              -- value : TBasicType TUTF8
    IO ()


dOMHTMLInputElementSetFormEnctype ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    T.Text ->                               -- value
    m ()
dOMHTMLInputElementSetFormEnctype _obj value = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    value' <- textToCString value
    webkit_dom_html_input_element_set_form_enctype _obj' value'
    touchManagedPtr _obj
    freeMem value'
    return ()

-- method DOMHTMLInputElement::set_form_method
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_set_form_method" webkit_dom_html_input_element_set_form_method :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    CString ->                              -- value : TBasicType TUTF8
    IO ()


dOMHTMLInputElementSetFormMethod ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    T.Text ->                               -- value
    m ()
dOMHTMLInputElementSetFormMethod _obj value = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    value' <- textToCString value
    webkit_dom_html_input_element_set_form_method _obj' value'
    touchManagedPtr _obj
    freeMem value'
    return ()

-- method DOMHTMLInputElement::set_form_no_validate
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_set_form_no_validate" webkit_dom_html_input_element_set_form_no_validate :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    CInt ->                                 -- value : TBasicType TBoolean
    IO ()


dOMHTMLInputElementSetFormNoValidate ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    Bool ->                                 -- value
    m ()
dOMHTMLInputElementSetFormNoValidate _obj value = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let value' = (fromIntegral . fromEnum) value
    webkit_dom_html_input_element_set_form_no_validate _obj' value'
    touchManagedPtr _obj
    return ()

-- method DOMHTMLInputElement::set_form_target
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_set_form_target" webkit_dom_html_input_element_set_form_target :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    CString ->                              -- value : TBasicType TUTF8
    IO ()


dOMHTMLInputElementSetFormTarget ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    T.Text ->                               -- value
    m ()
dOMHTMLInputElementSetFormTarget _obj value = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    value' <- textToCString value
    webkit_dom_html_input_element_set_form_target _obj' value'
    touchManagedPtr _obj
    freeMem value'
    return ()

-- method DOMHTMLInputElement::set_height
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_set_height" webkit_dom_html_input_element_set_height :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    Word64 ->                               -- value : TBasicType TUInt64
    IO ()


dOMHTMLInputElementSetHeight ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    Word64 ->                               -- value
    m ()
dOMHTMLInputElementSetHeight _obj value = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    webkit_dom_html_input_element_set_height _obj' value
    touchManagedPtr _obj
    return ()

-- method DOMHTMLInputElement::set_incremental
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_set_incremental" webkit_dom_html_input_element_set_incremental :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    CInt ->                                 -- value : TBasicType TBoolean
    IO ()


dOMHTMLInputElementSetIncremental ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    Bool ->                                 -- value
    m ()
dOMHTMLInputElementSetIncremental _obj value = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let value' = (fromIntegral . fromEnum) value
    webkit_dom_html_input_element_set_incremental _obj' value'
    touchManagedPtr _obj
    return ()

-- method DOMHTMLInputElement::set_indeterminate
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_set_indeterminate" webkit_dom_html_input_element_set_indeterminate :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    CInt ->                                 -- value : TBasicType TBoolean
    IO ()


dOMHTMLInputElementSetIndeterminate ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    Bool ->                                 -- value
    m ()
dOMHTMLInputElementSetIndeterminate _obj value = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let value' = (fromIntegral . fromEnum) value
    webkit_dom_html_input_element_set_indeterminate _obj' value'
    touchManagedPtr _obj
    return ()

-- method DOMHTMLInputElement::set_max
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_set_max" webkit_dom_html_input_element_set_max :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    CString ->                              -- value : TBasicType TUTF8
    IO ()


dOMHTMLInputElementSetMax ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    T.Text ->                               -- value
    m ()
dOMHTMLInputElementSetMax _obj value = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    value' <- textToCString value
    webkit_dom_html_input_element_set_max _obj' value'
    touchManagedPtr _obj
    freeMem value'
    return ()

-- method DOMHTMLInputElement::set_max_length
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : True
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_set_max_length" webkit_dom_html_input_element_set_max_length :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    Int64 ->                                -- value : TBasicType TInt64
    Ptr (Ptr GError) ->                     -- error
    IO ()


dOMHTMLInputElementSetMaxLength ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    Int64 ->                                -- value
    m ()
dOMHTMLInputElementSetMaxLength _obj value = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    onException (do
        propagateGError $ webkit_dom_html_input_element_set_max_length _obj' value
        touchManagedPtr _obj
        return ()
     ) (do
        return ()
     )

-- method DOMHTMLInputElement::set_min
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_set_min" webkit_dom_html_input_element_set_min :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    CString ->                              -- value : TBasicType TUTF8
    IO ()


dOMHTMLInputElementSetMin ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    T.Text ->                               -- value
    m ()
dOMHTMLInputElementSetMin _obj value = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    value' <- textToCString value
    webkit_dom_html_input_element_set_min _obj' value'
    touchManagedPtr _obj
    freeMem value'
    return ()

-- method DOMHTMLInputElement::set_multiple
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_set_multiple" webkit_dom_html_input_element_set_multiple :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    CInt ->                                 -- value : TBasicType TBoolean
    IO ()


dOMHTMLInputElementSetMultiple ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    Bool ->                                 -- value
    m ()
dOMHTMLInputElementSetMultiple _obj value = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let value' = (fromIntegral . fromEnum) value
    webkit_dom_html_input_element_set_multiple _obj' value'
    touchManagedPtr _obj
    return ()

-- method DOMHTMLInputElement::set_name
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_set_name" webkit_dom_html_input_element_set_name :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    CString ->                              -- value : TBasicType TUTF8
    IO ()


dOMHTMLInputElementSetName ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    T.Text ->                               -- value
    m ()
dOMHTMLInputElementSetName _obj value = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    value' <- textToCString value
    webkit_dom_html_input_element_set_name _obj' value'
    touchManagedPtr _obj
    freeMem value'
    return ()

-- method DOMHTMLInputElement::set_pattern
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_set_pattern" webkit_dom_html_input_element_set_pattern :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    CString ->                              -- value : TBasicType TUTF8
    IO ()


dOMHTMLInputElementSetPattern ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    T.Text ->                               -- value
    m ()
dOMHTMLInputElementSetPattern _obj value = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    value' <- textToCString value
    webkit_dom_html_input_element_set_pattern _obj' value'
    touchManagedPtr _obj
    freeMem value'
    return ()

-- method DOMHTMLInputElement::set_placeholder
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_set_placeholder" webkit_dom_html_input_element_set_placeholder :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    CString ->                              -- value : TBasicType TUTF8
    IO ()


dOMHTMLInputElementSetPlaceholder ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    T.Text ->                               -- value
    m ()
dOMHTMLInputElementSetPlaceholder _obj value = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    value' <- textToCString value
    webkit_dom_html_input_element_set_placeholder _obj' value'
    touchManagedPtr _obj
    freeMem value'
    return ()

-- method DOMHTMLInputElement::set_range_text
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "replacement", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "start", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "end", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "selectionMode", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "replacement", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "start", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "end", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "selectionMode", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : True
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_set_range_text" webkit_dom_html_input_element_set_range_text :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    CString ->                              -- replacement : TBasicType TUTF8
    Word64 ->                               -- start : TBasicType TUInt64
    Word64 ->                               -- end : TBasicType TUInt64
    CString ->                              -- selectionMode : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO ()


dOMHTMLInputElementSetRangeText ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    T.Text ->                               -- replacement
    Word64 ->                               -- start
    Word64 ->                               -- end
    T.Text ->                               -- selectionMode
    m ()
dOMHTMLInputElementSetRangeText _obj replacement start end selectionMode = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    replacement' <- textToCString replacement
    selectionMode' <- textToCString selectionMode
    onException (do
        propagateGError $ webkit_dom_html_input_element_set_range_text _obj' replacement' start end selectionMode'
        touchManagedPtr _obj
        freeMem replacement'
        freeMem selectionMode'
        return ()
     ) (do
        freeMem replacement'
        freeMem selectionMode'
     )

-- method DOMHTMLInputElement::set_read_only
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_set_read_only" webkit_dom_html_input_element_set_read_only :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    CInt ->                                 -- value : TBasicType TBoolean
    IO ()


dOMHTMLInputElementSetReadOnly ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    Bool ->                                 -- value
    m ()
dOMHTMLInputElementSetReadOnly _obj value = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let value' = (fromIntegral . fromEnum) value
    webkit_dom_html_input_element_set_read_only _obj' value'
    touchManagedPtr _obj
    return ()

-- method DOMHTMLInputElement::set_required
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_set_required" webkit_dom_html_input_element_set_required :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    CInt ->                                 -- value : TBasicType TBoolean
    IO ()


dOMHTMLInputElementSetRequired ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    Bool ->                                 -- value
    m ()
dOMHTMLInputElementSetRequired _obj value = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let value' = (fromIntegral . fromEnum) value
    webkit_dom_html_input_element_set_required _obj' value'
    touchManagedPtr _obj
    return ()

-- method DOMHTMLInputElement::set_size
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : True
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_set_size" webkit_dom_html_input_element_set_size :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    Word64 ->                               -- value : TBasicType TUInt64
    Ptr (Ptr GError) ->                     -- error
    IO ()


dOMHTMLInputElementSetSize ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    Word64 ->                               -- value
    m ()
dOMHTMLInputElementSetSize _obj value = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    onException (do
        propagateGError $ webkit_dom_html_input_element_set_size _obj' value
        touchManagedPtr _obj
        return ()
     ) (do
        return ()
     )

-- method DOMHTMLInputElement::set_src
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_set_src" webkit_dom_html_input_element_set_src :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    CString ->                              -- value : TBasicType TUTF8
    IO ()


dOMHTMLInputElementSetSrc ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    T.Text ->                               -- value
    m ()
dOMHTMLInputElementSetSrc _obj value = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    value' <- textToCString value
    webkit_dom_html_input_element_set_src _obj' value'
    touchManagedPtr _obj
    freeMem value'
    return ()

-- method DOMHTMLInputElement::set_step
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_set_step" webkit_dom_html_input_element_set_step :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    CString ->                              -- value : TBasicType TUTF8
    IO ()


dOMHTMLInputElementSetStep ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    T.Text ->                               -- value
    m ()
dOMHTMLInputElementSetStep _obj value = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    value' <- textToCString value
    webkit_dom_html_input_element_set_step _obj' value'
    touchManagedPtr _obj
    freeMem value'
    return ()

-- method DOMHTMLInputElement::set_use_map
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_set_use_map" webkit_dom_html_input_element_set_use_map :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    CString ->                              -- value : TBasicType TUTF8
    IO ()


dOMHTMLInputElementSetUseMap ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    T.Text ->                               -- value
    m ()
dOMHTMLInputElementSetUseMap _obj value = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    value' <- textToCString value
    webkit_dom_html_input_element_set_use_map _obj' value'
    touchManagedPtr _obj
    freeMem value'
    return ()

-- method DOMHTMLInputElement::set_value
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_set_value" webkit_dom_html_input_element_set_value :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    CString ->                              -- value : TBasicType TUTF8
    IO ()


dOMHTMLInputElementSetValue ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    T.Text ->                               -- value
    m ()
dOMHTMLInputElementSetValue _obj value = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    value' <- textToCString value
    webkit_dom_html_input_element_set_value _obj' value'
    touchManagedPtr _obj
    freeMem value'
    return ()

-- method DOMHTMLInputElement::set_value_as_number
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TDouble, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TDouble, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : True
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_set_value_as_number" webkit_dom_html_input_element_set_value_as_number :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    CDouble ->                              -- value : TBasicType TDouble
    Ptr (Ptr GError) ->                     -- error
    IO ()


dOMHTMLInputElementSetValueAsNumber ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    Double ->                               -- value
    m ()
dOMHTMLInputElementSetValueAsNumber _obj value = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let value' = realToFrac value
    onException (do
        propagateGError $ webkit_dom_html_input_element_set_value_as_number _obj' value'
        touchManagedPtr _obj
        return ()
     ) (do
        return ()
     )

-- method DOMHTMLInputElement::set_value_for_user
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_set_value_for_user" webkit_dom_html_input_element_set_value_for_user :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    CString ->                              -- value : TBasicType TUTF8
    IO ()


dOMHTMLInputElementSetValueForUser ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    T.Text ->                               -- value
    m ()
dOMHTMLInputElementSetValueForUser _obj value = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    value' <- textToCString value
    webkit_dom_html_input_element_set_value_for_user _obj' value'
    touchManagedPtr _obj
    freeMem value'
    return ()

-- method DOMHTMLInputElement::set_webkit_grammar
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_set_webkit_grammar" webkit_dom_html_input_element_set_webkit_grammar :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    CInt ->                                 -- value : TBasicType TBoolean
    IO ()


dOMHTMLInputElementSetWebkitGrammar ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    Bool ->                                 -- value
    m ()
dOMHTMLInputElementSetWebkitGrammar _obj value = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let value' = (fromIntegral . fromEnum) value
    webkit_dom_html_input_element_set_webkit_grammar _obj' value'
    touchManagedPtr _obj
    return ()

-- method DOMHTMLInputElement::set_webkit_speech
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_set_webkit_speech" webkit_dom_html_input_element_set_webkit_speech :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    CInt ->                                 -- value : TBasicType TBoolean
    IO ()


dOMHTMLInputElementSetWebkitSpeech ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    Bool ->                                 -- value
    m ()
dOMHTMLInputElementSetWebkitSpeech _obj value = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let value' = (fromIntegral . fromEnum) value
    webkit_dom_html_input_element_set_webkit_speech _obj' value'
    touchManagedPtr _obj
    return ()

-- method DOMHTMLInputElement::set_webkitdirectory
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_set_webkitdirectory" webkit_dom_html_input_element_set_webkitdirectory :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    CInt ->                                 -- value : TBasicType TBoolean
    IO ()


dOMHTMLInputElementSetWebkitdirectory ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    Bool ->                                 -- value
    m ()
dOMHTMLInputElementSetWebkitdirectory _obj value = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let value' = (fromIntegral . fromEnum) value
    webkit_dom_html_input_element_set_webkitdirectory _obj' value'
    touchManagedPtr _obj
    return ()

-- method DOMHTMLInputElement::set_width
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_set_width" webkit_dom_html_input_element_set_width :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    Word64 ->                               -- value : TBasicType TUInt64
    IO ()


dOMHTMLInputElementSetWidth ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    Word64 ->                               -- value
    m ()
dOMHTMLInputElementSetWidth _obj value = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    webkit_dom_html_input_element_set_width _obj' value
    touchManagedPtr _obj
    return ()

-- method DOMHTMLInputElement::step_down
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "n", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "n", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : True
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_step_down" webkit_dom_html_input_element_step_down :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    Int64 ->                                -- n : TBasicType TInt64
    Ptr (Ptr GError) ->                     -- error
    IO ()


dOMHTMLInputElementStepDown ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    Int64 ->                                -- n
    m ()
dOMHTMLInputElementStepDown _obj n = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    onException (do
        propagateGError $ webkit_dom_html_input_element_step_down _obj' n
        touchManagedPtr _obj
        return ()
     ) (do
        return ()
     )

-- method DOMHTMLInputElement::step_up
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "n", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLInputElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "n", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : True
-- Skip return : False

foreign import ccall "webkit_dom_html_input_element_step_up" webkit_dom_html_input_element_step_up :: 
    Ptr DOMHTMLInputElement ->              -- _obj : TInterface "WebKit" "DOMHTMLInputElement"
    Int64 ->                                -- n : TBasicType TInt64
    Ptr (Ptr GError) ->                     -- error
    IO ()


dOMHTMLInputElementStepUp ::
    (MonadIO m, DOMHTMLInputElementK a) =>
    a ->                                    -- _obj
    Int64 ->                                -- n
    m ()
dOMHTMLInputElementStepUp _obj n = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    onException (do
        propagateGError $ webkit_dom_html_input_element_step_up _obj' n
        touchManagedPtr _obj
        return ()
     ) (do
        return ()
     )