{- |
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.DOMHTMLVideoElement
    ( 

-- * Exported types
    DOMHTMLVideoElement(..)                 ,
    DOMHTMLVideoElementK                    ,
    toDOMHTMLVideoElement                   ,
    noDOMHTMLVideoElement                   ,


 -- * Methods
-- ** dOMHTMLVideoElementGetHeight
    dOMHTMLVideoElementGetHeight            ,


-- ** dOMHTMLVideoElementGetPoster
    dOMHTMLVideoElementGetPoster            ,


-- ** dOMHTMLVideoElementGetVideoHeight
    dOMHTMLVideoElementGetVideoHeight       ,


-- ** dOMHTMLVideoElementGetVideoWidth
    dOMHTMLVideoElementGetVideoWidth        ,


-- ** dOMHTMLVideoElementGetWebkitDecodedFrameCount
    dOMHTMLVideoElementGetWebkitDecodedFrameCount,


-- ** dOMHTMLVideoElementGetWebkitDisplayingFullscreen
    dOMHTMLVideoElementGetWebkitDisplayingFullscreen,


-- ** dOMHTMLVideoElementGetWebkitDroppedFrameCount
    dOMHTMLVideoElementGetWebkitDroppedFrameCount,


-- ** dOMHTMLVideoElementGetWebkitSupportsFullscreen
    dOMHTMLVideoElementGetWebkitSupportsFullscreen,


-- ** dOMHTMLVideoElementGetWebkitWirelessVideoPlaybackDisabled
    dOMHTMLVideoElementGetWebkitWirelessVideoPlaybackDisabled,


-- ** dOMHTMLVideoElementGetWidth
    dOMHTMLVideoElementGetWidth             ,


-- ** dOMHTMLVideoElementSetHeight
    dOMHTMLVideoElementSetHeight            ,


-- ** dOMHTMLVideoElementSetPoster
    dOMHTMLVideoElementSetPoster            ,


-- ** dOMHTMLVideoElementSetWebkitWirelessVideoPlaybackDisabled
    dOMHTMLVideoElementSetWebkitWirelessVideoPlaybackDisabled,


-- ** dOMHTMLVideoElementSetWidth
    dOMHTMLVideoElementSetWidth             ,


-- ** dOMHTMLVideoElementWebkitEnterFullScreen
    dOMHTMLVideoElementWebkitEnterFullScreen,


-- ** dOMHTMLVideoElementWebkitEnterFullscreen
    dOMHTMLVideoElementWebkitEnterFullscreen,


-- ** dOMHTMLVideoElementWebkitExitFullScreen
    dOMHTMLVideoElementWebkitExitFullScreen ,


-- ** dOMHTMLVideoElementWebkitExitFullscreen
    dOMHTMLVideoElementWebkitExitFullscreen ,




 -- * Properties
-- ** Height
    DOMHTMLVideoElementHeightPropertyInfo   ,
    constructDOMHTMLVideoElementHeight      ,
    getDOMHTMLVideoElementHeight            ,
    setDOMHTMLVideoElementHeight            ,


-- ** Poster
    DOMHTMLVideoElementPosterPropertyInfo   ,
    constructDOMHTMLVideoElementPoster      ,
    getDOMHTMLVideoElementPoster            ,
    setDOMHTMLVideoElementPoster            ,


-- ** VideoHeight
    DOMHTMLVideoElementVideoHeightPropertyInfo,
    getDOMHTMLVideoElementVideoHeight       ,


-- ** VideoWidth
    DOMHTMLVideoElementVideoWidthPropertyInfo,
    getDOMHTMLVideoElementVideoWidth        ,


-- ** WebkitDecodedFrameCount
    DOMHTMLVideoElementWebkitDecodedFrameCountPropertyInfo,
    getDOMHTMLVideoElementWebkitDecodedFrameCount,


-- ** WebkitDisplayingFullscreen
    DOMHTMLVideoElementWebkitDisplayingFullscreenPropertyInfo,
    getDOMHTMLVideoElementWebkitDisplayingFullscreen,


-- ** WebkitDroppedFrameCount
    DOMHTMLVideoElementWebkitDroppedFrameCountPropertyInfo,
    getDOMHTMLVideoElementWebkitDroppedFrameCount,


-- ** WebkitSupportsFullscreen
    DOMHTMLVideoElementWebkitSupportsFullscreenPropertyInfo,
    getDOMHTMLVideoElementWebkitSupportsFullscreen,


-- ** WebkitWirelessVideoPlaybackDisabled
    DOMHTMLVideoElementWebkitWirelessVideoPlaybackDisabledPropertyInfo,
    constructDOMHTMLVideoElementWebkitWirelessVideoPlaybackDisabled,
    getDOMHTMLVideoElementWebkitWirelessVideoPlaybackDisabled,
    setDOMHTMLVideoElementWebkitWirelessVideoPlaybackDisabled,


-- ** Width
    DOMHTMLVideoElementWidthPropertyInfo    ,
    constructDOMHTMLVideoElementWidth       ,
    getDOMHTMLVideoElementWidth             ,
    setDOMHTMLVideoElementWidth             ,




    ) 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 DOMHTMLVideoElement = DOMHTMLVideoElement (ForeignPtr DOMHTMLVideoElement)
foreign import ccall "webkit_dom_html_video_element_get_type"
    c_webkit_dom_html_video_element_get_type :: IO GType

type instance ParentTypes DOMHTMLVideoElement = DOMHTMLVideoElementParentTypes
type DOMHTMLVideoElementParentTypes = '[DOMHTMLMediaElement, DOMHTMLElement, DOMElement, DOMNode, DOMObject, GObject.Object, DOMEventTarget]

instance GObject DOMHTMLVideoElement where
    gobjectIsInitiallyUnowned _ = False
    gobjectType _ = c_webkit_dom_html_video_element_get_type
    

class GObject o => DOMHTMLVideoElementK o
instance (GObject o, IsDescendantOf DOMHTMLVideoElement o) => DOMHTMLVideoElementK o

toDOMHTMLVideoElement :: DOMHTMLVideoElementK o => o -> IO DOMHTMLVideoElement
toDOMHTMLVideoElement = unsafeCastTo DOMHTMLVideoElement

noDOMHTMLVideoElement :: Maybe DOMHTMLVideoElement
noDOMHTMLVideoElement = Nothing

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

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

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

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

data DOMHTMLVideoElementHeightPropertyInfo
instance AttrInfo DOMHTMLVideoElementHeightPropertyInfo where
    type AttrAllowedOps DOMHTMLVideoElementHeightPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint DOMHTMLVideoElementHeightPropertyInfo = (~) Word64
    type AttrBaseTypeConstraint DOMHTMLVideoElementHeightPropertyInfo = DOMHTMLVideoElementK
    type AttrGetType DOMHTMLVideoElementHeightPropertyInfo = Word64
    type AttrLabel DOMHTMLVideoElementHeightPropertyInfo = "DOMHTMLVideoElement::height"
    attrGet _ = getDOMHTMLVideoElementHeight
    attrSet _ = setDOMHTMLVideoElementHeight
    attrConstruct _ = constructDOMHTMLVideoElementHeight

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

getDOMHTMLVideoElementPoster :: (MonadIO m, DOMHTMLVideoElementK o) => o -> m T.Text
getDOMHTMLVideoElementPoster obj = liftIO $ getObjectPropertyString obj "poster"

setDOMHTMLVideoElementPoster :: (MonadIO m, DOMHTMLVideoElementK o) => o -> T.Text -> m ()
setDOMHTMLVideoElementPoster obj val = liftIO $ setObjectPropertyString obj "poster" val

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

data DOMHTMLVideoElementPosterPropertyInfo
instance AttrInfo DOMHTMLVideoElementPosterPropertyInfo where
    type AttrAllowedOps DOMHTMLVideoElementPosterPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint DOMHTMLVideoElementPosterPropertyInfo = (~) T.Text
    type AttrBaseTypeConstraint DOMHTMLVideoElementPosterPropertyInfo = DOMHTMLVideoElementK
    type AttrGetType DOMHTMLVideoElementPosterPropertyInfo = T.Text
    type AttrLabel DOMHTMLVideoElementPosterPropertyInfo = "DOMHTMLVideoElement::poster"
    attrGet _ = getDOMHTMLVideoElementPoster
    attrSet _ = setDOMHTMLVideoElementPoster
    attrConstruct _ = constructDOMHTMLVideoElementPoster

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

getDOMHTMLVideoElementVideoHeight :: (MonadIO m, DOMHTMLVideoElementK o) => o -> m Word64
getDOMHTMLVideoElementVideoHeight obj = liftIO $ getObjectPropertyUInt64 obj "video-height"

data DOMHTMLVideoElementVideoHeightPropertyInfo
instance AttrInfo DOMHTMLVideoElementVideoHeightPropertyInfo where
    type AttrAllowedOps DOMHTMLVideoElementVideoHeightPropertyInfo = '[ 'AttrGet]
    type AttrSetTypeConstraint DOMHTMLVideoElementVideoHeightPropertyInfo = (~) ()
    type AttrBaseTypeConstraint DOMHTMLVideoElementVideoHeightPropertyInfo = DOMHTMLVideoElementK
    type AttrGetType DOMHTMLVideoElementVideoHeightPropertyInfo = Word64
    type AttrLabel DOMHTMLVideoElementVideoHeightPropertyInfo = "DOMHTMLVideoElement::video-height"
    attrGet _ = getDOMHTMLVideoElementVideoHeight
    attrSet _ = undefined
    attrConstruct _ = undefined

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

getDOMHTMLVideoElementVideoWidth :: (MonadIO m, DOMHTMLVideoElementK o) => o -> m Word64
getDOMHTMLVideoElementVideoWidth obj = liftIO $ getObjectPropertyUInt64 obj "video-width"

data DOMHTMLVideoElementVideoWidthPropertyInfo
instance AttrInfo DOMHTMLVideoElementVideoWidthPropertyInfo where
    type AttrAllowedOps DOMHTMLVideoElementVideoWidthPropertyInfo = '[ 'AttrGet]
    type AttrSetTypeConstraint DOMHTMLVideoElementVideoWidthPropertyInfo = (~) ()
    type AttrBaseTypeConstraint DOMHTMLVideoElementVideoWidthPropertyInfo = DOMHTMLVideoElementK
    type AttrGetType DOMHTMLVideoElementVideoWidthPropertyInfo = Word64
    type AttrLabel DOMHTMLVideoElementVideoWidthPropertyInfo = "DOMHTMLVideoElement::video-width"
    attrGet _ = getDOMHTMLVideoElementVideoWidth
    attrSet _ = undefined
    attrConstruct _ = undefined

-- VVV Prop "webkit-decoded-frame-count"
   -- Type: TBasicType TUInt64
   -- Flags: [PropertyReadable]

getDOMHTMLVideoElementWebkitDecodedFrameCount :: (MonadIO m, DOMHTMLVideoElementK o) => o -> m Word64
getDOMHTMLVideoElementWebkitDecodedFrameCount obj = liftIO $ getObjectPropertyUInt64 obj "webkit-decoded-frame-count"

data DOMHTMLVideoElementWebkitDecodedFrameCountPropertyInfo
instance AttrInfo DOMHTMLVideoElementWebkitDecodedFrameCountPropertyInfo where
    type AttrAllowedOps DOMHTMLVideoElementWebkitDecodedFrameCountPropertyInfo = '[ 'AttrGet]
    type AttrSetTypeConstraint DOMHTMLVideoElementWebkitDecodedFrameCountPropertyInfo = (~) ()
    type AttrBaseTypeConstraint DOMHTMLVideoElementWebkitDecodedFrameCountPropertyInfo = DOMHTMLVideoElementK
    type AttrGetType DOMHTMLVideoElementWebkitDecodedFrameCountPropertyInfo = Word64
    type AttrLabel DOMHTMLVideoElementWebkitDecodedFrameCountPropertyInfo = "DOMHTMLVideoElement::webkit-decoded-frame-count"
    attrGet _ = getDOMHTMLVideoElementWebkitDecodedFrameCount
    attrSet _ = undefined
    attrConstruct _ = undefined

-- VVV Prop "webkit-displaying-fullscreen"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable]

getDOMHTMLVideoElementWebkitDisplayingFullscreen :: (MonadIO m, DOMHTMLVideoElementK o) => o -> m Bool
getDOMHTMLVideoElementWebkitDisplayingFullscreen obj = liftIO $ getObjectPropertyBool obj "webkit-displaying-fullscreen"

data DOMHTMLVideoElementWebkitDisplayingFullscreenPropertyInfo
instance AttrInfo DOMHTMLVideoElementWebkitDisplayingFullscreenPropertyInfo where
    type AttrAllowedOps DOMHTMLVideoElementWebkitDisplayingFullscreenPropertyInfo = '[ 'AttrGet]
    type AttrSetTypeConstraint DOMHTMLVideoElementWebkitDisplayingFullscreenPropertyInfo = (~) ()
    type AttrBaseTypeConstraint DOMHTMLVideoElementWebkitDisplayingFullscreenPropertyInfo = DOMHTMLVideoElementK
    type AttrGetType DOMHTMLVideoElementWebkitDisplayingFullscreenPropertyInfo = Bool
    type AttrLabel DOMHTMLVideoElementWebkitDisplayingFullscreenPropertyInfo = "DOMHTMLVideoElement::webkit-displaying-fullscreen"
    attrGet _ = getDOMHTMLVideoElementWebkitDisplayingFullscreen
    attrSet _ = undefined
    attrConstruct _ = undefined

-- VVV Prop "webkit-dropped-frame-count"
   -- Type: TBasicType TUInt64
   -- Flags: [PropertyReadable]

getDOMHTMLVideoElementWebkitDroppedFrameCount :: (MonadIO m, DOMHTMLVideoElementK o) => o -> m Word64
getDOMHTMLVideoElementWebkitDroppedFrameCount obj = liftIO $ getObjectPropertyUInt64 obj "webkit-dropped-frame-count"

data DOMHTMLVideoElementWebkitDroppedFrameCountPropertyInfo
instance AttrInfo DOMHTMLVideoElementWebkitDroppedFrameCountPropertyInfo where
    type AttrAllowedOps DOMHTMLVideoElementWebkitDroppedFrameCountPropertyInfo = '[ 'AttrGet]
    type AttrSetTypeConstraint DOMHTMLVideoElementWebkitDroppedFrameCountPropertyInfo = (~) ()
    type AttrBaseTypeConstraint DOMHTMLVideoElementWebkitDroppedFrameCountPropertyInfo = DOMHTMLVideoElementK
    type AttrGetType DOMHTMLVideoElementWebkitDroppedFrameCountPropertyInfo = Word64
    type AttrLabel DOMHTMLVideoElementWebkitDroppedFrameCountPropertyInfo = "DOMHTMLVideoElement::webkit-dropped-frame-count"
    attrGet _ = getDOMHTMLVideoElementWebkitDroppedFrameCount
    attrSet _ = undefined
    attrConstruct _ = undefined

-- VVV Prop "webkit-supports-fullscreen"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable]

getDOMHTMLVideoElementWebkitSupportsFullscreen :: (MonadIO m, DOMHTMLVideoElementK o) => o -> m Bool
getDOMHTMLVideoElementWebkitSupportsFullscreen obj = liftIO $ getObjectPropertyBool obj "webkit-supports-fullscreen"

data DOMHTMLVideoElementWebkitSupportsFullscreenPropertyInfo
instance AttrInfo DOMHTMLVideoElementWebkitSupportsFullscreenPropertyInfo where
    type AttrAllowedOps DOMHTMLVideoElementWebkitSupportsFullscreenPropertyInfo = '[ 'AttrGet]
    type AttrSetTypeConstraint DOMHTMLVideoElementWebkitSupportsFullscreenPropertyInfo = (~) ()
    type AttrBaseTypeConstraint DOMHTMLVideoElementWebkitSupportsFullscreenPropertyInfo = DOMHTMLVideoElementK
    type AttrGetType DOMHTMLVideoElementWebkitSupportsFullscreenPropertyInfo = Bool
    type AttrLabel DOMHTMLVideoElementWebkitSupportsFullscreenPropertyInfo = "DOMHTMLVideoElement::webkit-supports-fullscreen"
    attrGet _ = getDOMHTMLVideoElementWebkitSupportsFullscreen
    attrSet _ = undefined
    attrConstruct _ = undefined

-- VVV Prop "webkit-wireless-video-playback-disabled"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]

getDOMHTMLVideoElementWebkitWirelessVideoPlaybackDisabled :: (MonadIO m, DOMHTMLVideoElementK o) => o -> m Bool
getDOMHTMLVideoElementWebkitWirelessVideoPlaybackDisabled obj = liftIO $ getObjectPropertyBool obj "webkit-wireless-video-playback-disabled"

setDOMHTMLVideoElementWebkitWirelessVideoPlaybackDisabled :: (MonadIO m, DOMHTMLVideoElementK o) => o -> Bool -> m ()
setDOMHTMLVideoElementWebkitWirelessVideoPlaybackDisabled obj val = liftIO $ setObjectPropertyBool obj "webkit-wireless-video-playback-disabled" val

constructDOMHTMLVideoElementWebkitWirelessVideoPlaybackDisabled :: Bool -> IO ([Char], GValue)
constructDOMHTMLVideoElementWebkitWirelessVideoPlaybackDisabled val = constructObjectPropertyBool "webkit-wireless-video-playback-disabled" val

data DOMHTMLVideoElementWebkitWirelessVideoPlaybackDisabledPropertyInfo
instance AttrInfo DOMHTMLVideoElementWebkitWirelessVideoPlaybackDisabledPropertyInfo where
    type AttrAllowedOps DOMHTMLVideoElementWebkitWirelessVideoPlaybackDisabledPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint DOMHTMLVideoElementWebkitWirelessVideoPlaybackDisabledPropertyInfo = (~) Bool
    type AttrBaseTypeConstraint DOMHTMLVideoElementWebkitWirelessVideoPlaybackDisabledPropertyInfo = DOMHTMLVideoElementK
    type AttrGetType DOMHTMLVideoElementWebkitWirelessVideoPlaybackDisabledPropertyInfo = Bool
    type AttrLabel DOMHTMLVideoElementWebkitWirelessVideoPlaybackDisabledPropertyInfo = "DOMHTMLVideoElement::webkit-wireless-video-playback-disabled"
    attrGet _ = getDOMHTMLVideoElementWebkitWirelessVideoPlaybackDisabled
    attrSet _ = setDOMHTMLVideoElementWebkitWirelessVideoPlaybackDisabled
    attrConstruct _ = constructDOMHTMLVideoElementWebkitWirelessVideoPlaybackDisabled

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

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

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

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

data DOMHTMLVideoElementWidthPropertyInfo
instance AttrInfo DOMHTMLVideoElementWidthPropertyInfo where
    type AttrAllowedOps DOMHTMLVideoElementWidthPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint DOMHTMLVideoElementWidthPropertyInfo = (~) Word64
    type AttrBaseTypeConstraint DOMHTMLVideoElementWidthPropertyInfo = DOMHTMLVideoElementK
    type AttrGetType DOMHTMLVideoElementWidthPropertyInfo = Word64
    type AttrLabel DOMHTMLVideoElementWidthPropertyInfo = "DOMHTMLVideoElement::width"
    attrGet _ = getDOMHTMLVideoElementWidth
    attrSet _ = setDOMHTMLVideoElementWidth
    attrConstruct _ = constructDOMHTMLVideoElementWidth

type instance AttributeList DOMHTMLVideoElement = DOMHTMLVideoElementAttributeList
type DOMHTMLVideoElementAttributeList = ('[ '("access-key", DOMHTMLElementAccessKeyPropertyInfo), '("attributes", DOMElementAttributesPropertyInfo), '("audio-tracks", DOMHTMLMediaElementAudioTracksPropertyInfo), '("autoplay", DOMHTMLMediaElementAutoplayPropertyInfo), '("base-uri", DOMNodeBaseUriPropertyInfo), '("buffered", DOMHTMLMediaElementBufferedPropertyInfo), '("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), '("controller", DOMHTMLMediaElementControllerPropertyInfo), '("controls", DOMHTMLMediaElementControlsPropertyInfo), '("core-object", DOMObjectCoreObjectPropertyInfo), '("current-src", DOMHTMLMediaElementCurrentSrcPropertyInfo), '("current-time", DOMHTMLMediaElementCurrentTimePropertyInfo), '("default-muted", DOMHTMLMediaElementDefaultMutedPropertyInfo), '("default-playback-rate", DOMHTMLMediaElementDefaultPlaybackRatePropertyInfo), '("dir", DOMHTMLElementDirPropertyInfo), '("draggable", DOMHTMLElementDraggablePropertyInfo), '("duration", DOMHTMLMediaElementDurationPropertyInfo), '("ended", DOMHTMLMediaElementEndedPropertyInfo), '("error", DOMHTMLMediaElementErrorPropertyInfo), '("first-child", DOMNodeFirstChildPropertyInfo), '("first-element-child", DOMElementFirstElementChildPropertyInfo), '("height", DOMHTMLVideoElementHeightPropertyInfo), '("hidden", DOMHTMLElementHiddenPropertyInfo), '("id", DOMElementIdPropertyInfo), '("inner-html", DOMHTMLElementInnerHtmlPropertyInfo), '("inner-text", DOMHTMLElementInnerTextPropertyInfo), '("is-content-editable", DOMHTMLElementIsContentEditablePropertyInfo), '("lang", DOMHTMLElementLangPropertyInfo), '("last-child", DOMNodeLastChildPropertyInfo), '("last-element-child", DOMElementLastElementChildPropertyInfo), '("local-name", DOMNodeLocalNamePropertyInfo), '("loop", DOMHTMLMediaElementLoopPropertyInfo), '("media-group", DOMHTMLMediaElementMediaGroupPropertyInfo), '("muted", DOMHTMLMediaElementMutedPropertyInfo), '("namespace-uri", DOMNodeNamespaceUriPropertyInfo), '("network-state", DOMHTMLMediaElementNetworkStatePropertyInfo), '("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), '("paused", DOMHTMLMediaElementPausedPropertyInfo), '("playback-rate", DOMHTMLMediaElementPlaybackRatePropertyInfo), '("played", DOMHTMLMediaElementPlayedPropertyInfo), '("poster", DOMHTMLVideoElementPosterPropertyInfo), '("prefix", DOMNodePrefixPropertyInfo), '("preload", DOMHTMLMediaElementPreloadPropertyInfo), '("previous-element-sibling", DOMElementPreviousElementSiblingPropertyInfo), '("previous-sibling", DOMNodePreviousSiblingPropertyInfo), '("ready-state", DOMHTMLMediaElementReadyStatePropertyInfo), '("scroll-height", DOMElementScrollHeightPropertyInfo), '("scroll-left", DOMElementScrollLeftPropertyInfo), '("scroll-top", DOMElementScrollTopPropertyInfo), '("scroll-width", DOMElementScrollWidthPropertyInfo), '("seekable", DOMHTMLMediaElementSeekablePropertyInfo), '("seeking", DOMHTMLMediaElementSeekingPropertyInfo), '("spellcheck", DOMHTMLElementSpellcheckPropertyInfo), '("src", DOMHTMLMediaElementSrcPropertyInfo), '("style", DOMElementStylePropertyInfo), '("tab-index", DOMHTMLElementTabIndexPropertyInfo), '("tag-name", DOMElementTagNamePropertyInfo), '("text-content", DOMNodeTextContentPropertyInfo), '("text-tracks", DOMHTMLMediaElementTextTracksPropertyInfo), '("title", DOMHTMLElementTitlePropertyInfo), '("translate", DOMHTMLElementTranslatePropertyInfo), '("video-height", DOMHTMLVideoElementVideoHeightPropertyInfo), '("video-tracks", DOMHTMLMediaElementVideoTracksPropertyInfo), '("video-width", DOMHTMLVideoElementVideoWidthPropertyInfo), '("volume", DOMHTMLMediaElementVolumePropertyInfo), '("webkit-audio-decoded-byte-count", DOMHTMLMediaElementWebkitAudioDecodedByteCountPropertyInfo), '("webkit-closed-captions-visible", DOMHTMLMediaElementWebkitClosedCaptionsVisiblePropertyInfo), '("webkit-current-playback-target-is-wireless", DOMHTMLMediaElementWebkitCurrentPlaybackTargetIsWirelessPropertyInfo), '("webkit-decoded-frame-count", DOMHTMLVideoElementWebkitDecodedFrameCountPropertyInfo), '("webkit-displaying-fullscreen", DOMHTMLVideoElementWebkitDisplayingFullscreenPropertyInfo), '("webkit-dropped-frame-count", DOMHTMLVideoElementWebkitDroppedFrameCountPropertyInfo), '("webkit-has-closed-captions", DOMHTMLMediaElementWebkitHasClosedCaptionsPropertyInfo), '("webkit-preserves-pitch", DOMHTMLMediaElementWebkitPreservesPitchPropertyInfo), '("webkit-region-overset", DOMElementWebkitRegionOversetPropertyInfo), '("webkit-supports-fullscreen", DOMHTMLVideoElementWebkitSupportsFullscreenPropertyInfo), '("webkit-video-decoded-byte-count", DOMHTMLMediaElementWebkitVideoDecodedByteCountPropertyInfo), '("webkit-wireless-video-playback-disabled", DOMHTMLVideoElementWebkitWirelessVideoPlaybackDisabledPropertyInfo), '("webkitdropzone", DOMHTMLElementWebkitdropzonePropertyInfo), '("width", DOMHTMLVideoElementWidthPropertyInfo)] :: [(Symbol, *)])

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

-- method DOMHTMLVideoElement::get_height
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLVideoElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLVideoElement", 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_video_element_get_height" webkit_dom_html_video_element_get_height :: 
    Ptr DOMHTMLVideoElement ->              -- _obj : TInterface "WebKit" "DOMHTMLVideoElement"
    IO Word64


dOMHTMLVideoElementGetHeight ::
    (MonadIO m, DOMHTMLVideoElementK a) =>
    a ->                                    -- _obj
    m Word64
dOMHTMLVideoElementGetHeight _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- webkit_dom_html_video_element_get_height _obj'
    touchManagedPtr _obj
    return result

-- method DOMHTMLVideoElement::get_poster
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLVideoElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLVideoElement", 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_video_element_get_poster" webkit_dom_html_video_element_get_poster :: 
    Ptr DOMHTMLVideoElement ->              -- _obj : TInterface "WebKit" "DOMHTMLVideoElement"
    IO CString


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

-- method DOMHTMLVideoElement::get_video_height
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLVideoElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLVideoElement", 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_video_element_get_video_height" webkit_dom_html_video_element_get_video_height :: 
    Ptr DOMHTMLVideoElement ->              -- _obj : TInterface "WebKit" "DOMHTMLVideoElement"
    IO Word64


dOMHTMLVideoElementGetVideoHeight ::
    (MonadIO m, DOMHTMLVideoElementK a) =>
    a ->                                    -- _obj
    m Word64
dOMHTMLVideoElementGetVideoHeight _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- webkit_dom_html_video_element_get_video_height _obj'
    touchManagedPtr _obj
    return result

-- method DOMHTMLVideoElement::get_video_width
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLVideoElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLVideoElement", 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_video_element_get_video_width" webkit_dom_html_video_element_get_video_width :: 
    Ptr DOMHTMLVideoElement ->              -- _obj : TInterface "WebKit" "DOMHTMLVideoElement"
    IO Word64


dOMHTMLVideoElementGetVideoWidth ::
    (MonadIO m, DOMHTMLVideoElementK a) =>
    a ->                                    -- _obj
    m Word64
dOMHTMLVideoElementGetVideoWidth _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- webkit_dom_html_video_element_get_video_width _obj'
    touchManagedPtr _obj
    return result

-- method DOMHTMLVideoElement::get_webkit_decoded_frame_count
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLVideoElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLVideoElement", 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_video_element_get_webkit_decoded_frame_count" webkit_dom_html_video_element_get_webkit_decoded_frame_count :: 
    Ptr DOMHTMLVideoElement ->              -- _obj : TInterface "WebKit" "DOMHTMLVideoElement"
    IO Word64


dOMHTMLVideoElementGetWebkitDecodedFrameCount ::
    (MonadIO m, DOMHTMLVideoElementK a) =>
    a ->                                    -- _obj
    m Word64
dOMHTMLVideoElementGetWebkitDecodedFrameCount _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- webkit_dom_html_video_element_get_webkit_decoded_frame_count _obj'
    touchManagedPtr _obj
    return result

-- method DOMHTMLVideoElement::get_webkit_displaying_fullscreen
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLVideoElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLVideoElement", 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_video_element_get_webkit_displaying_fullscreen" webkit_dom_html_video_element_get_webkit_displaying_fullscreen :: 
    Ptr DOMHTMLVideoElement ->              -- _obj : TInterface "WebKit" "DOMHTMLVideoElement"
    IO CInt


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

-- method DOMHTMLVideoElement::get_webkit_dropped_frame_count
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLVideoElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLVideoElement", 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_video_element_get_webkit_dropped_frame_count" webkit_dom_html_video_element_get_webkit_dropped_frame_count :: 
    Ptr DOMHTMLVideoElement ->              -- _obj : TInterface "WebKit" "DOMHTMLVideoElement"
    IO Word64


dOMHTMLVideoElementGetWebkitDroppedFrameCount ::
    (MonadIO m, DOMHTMLVideoElementK a) =>
    a ->                                    -- _obj
    m Word64
dOMHTMLVideoElementGetWebkitDroppedFrameCount _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- webkit_dom_html_video_element_get_webkit_dropped_frame_count _obj'
    touchManagedPtr _obj
    return result

-- method DOMHTMLVideoElement::get_webkit_supports_fullscreen
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLVideoElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLVideoElement", 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_video_element_get_webkit_supports_fullscreen" webkit_dom_html_video_element_get_webkit_supports_fullscreen :: 
    Ptr DOMHTMLVideoElement ->              -- _obj : TInterface "WebKit" "DOMHTMLVideoElement"
    IO CInt


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

-- method DOMHTMLVideoElement::get_webkit_wireless_video_playback_disabled
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLVideoElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLVideoElement", 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_video_element_get_webkit_wireless_video_playback_disabled" webkit_dom_html_video_element_get_webkit_wireless_video_playback_disabled :: 
    Ptr DOMHTMLVideoElement ->              -- _obj : TInterface "WebKit" "DOMHTMLVideoElement"
    IO CInt


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

-- method DOMHTMLVideoElement::get_width
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLVideoElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLVideoElement", 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_video_element_get_width" webkit_dom_html_video_element_get_width :: 
    Ptr DOMHTMLVideoElement ->              -- _obj : TInterface "WebKit" "DOMHTMLVideoElement"
    IO Word64


dOMHTMLVideoElementGetWidth ::
    (MonadIO m, DOMHTMLVideoElementK a) =>
    a ->                                    -- _obj
    m Word64
dOMHTMLVideoElementGetWidth _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- webkit_dom_html_video_element_get_width _obj'
    touchManagedPtr _obj
    return result

-- method DOMHTMLVideoElement::set_height
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLVideoElement", 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" "DOMHTMLVideoElement", 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_video_element_set_height" webkit_dom_html_video_element_set_height :: 
    Ptr DOMHTMLVideoElement ->              -- _obj : TInterface "WebKit" "DOMHTMLVideoElement"
    Word64 ->                               -- value : TBasicType TUInt64
    IO ()


dOMHTMLVideoElementSetHeight ::
    (MonadIO m, DOMHTMLVideoElementK a) =>
    a ->                                    -- _obj
    Word64 ->                               -- value
    m ()
dOMHTMLVideoElementSetHeight _obj value = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    webkit_dom_html_video_element_set_height _obj' value
    touchManagedPtr _obj
    return ()

-- method DOMHTMLVideoElement::set_poster
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLVideoElement", 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" "DOMHTMLVideoElement", 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_video_element_set_poster" webkit_dom_html_video_element_set_poster :: 
    Ptr DOMHTMLVideoElement ->              -- _obj : TInterface "WebKit" "DOMHTMLVideoElement"
    CString ->                              -- value : TBasicType TUTF8
    IO ()


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

-- method DOMHTMLVideoElement::set_webkit_wireless_video_playback_disabled
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLVideoElement", 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" "DOMHTMLVideoElement", 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_video_element_set_webkit_wireless_video_playback_disabled" webkit_dom_html_video_element_set_webkit_wireless_video_playback_disabled :: 
    Ptr DOMHTMLVideoElement ->              -- _obj : TInterface "WebKit" "DOMHTMLVideoElement"
    CInt ->                                 -- value : TBasicType TBoolean
    IO ()


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

-- method DOMHTMLVideoElement::set_width
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLVideoElement", 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" "DOMHTMLVideoElement", 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_video_element_set_width" webkit_dom_html_video_element_set_width :: 
    Ptr DOMHTMLVideoElement ->              -- _obj : TInterface "WebKit" "DOMHTMLVideoElement"
    Word64 ->                               -- value : TBasicType TUInt64
    IO ()


dOMHTMLVideoElementSetWidth ::
    (MonadIO m, DOMHTMLVideoElementK a) =>
    a ->                                    -- _obj
    Word64 ->                               -- value
    m ()
dOMHTMLVideoElementSetWidth _obj value = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    webkit_dom_html_video_element_set_width _obj' value
    touchManagedPtr _obj
    return ()

-- method DOMHTMLVideoElement::webkit_enter_full_screen
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLVideoElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLVideoElement", 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_video_element_webkit_enter_full_screen" webkit_dom_html_video_element_webkit_enter_full_screen :: 
    Ptr DOMHTMLVideoElement ->              -- _obj : TInterface "WebKit" "DOMHTMLVideoElement"
    Ptr (Ptr GError) ->                     -- error
    IO ()


dOMHTMLVideoElementWebkitEnterFullScreen ::
    (MonadIO m, DOMHTMLVideoElementK a) =>
    a ->                                    -- _obj
    m ()
dOMHTMLVideoElementWebkitEnterFullScreen _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    onException (do
        propagateGError $ webkit_dom_html_video_element_webkit_enter_full_screen _obj'
        touchManagedPtr _obj
        return ()
     ) (do
        return ()
     )

-- method DOMHTMLVideoElement::webkit_enter_fullscreen
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLVideoElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLVideoElement", 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_video_element_webkit_enter_fullscreen" webkit_dom_html_video_element_webkit_enter_fullscreen :: 
    Ptr DOMHTMLVideoElement ->              -- _obj : TInterface "WebKit" "DOMHTMLVideoElement"
    Ptr (Ptr GError) ->                     -- error
    IO ()


dOMHTMLVideoElementWebkitEnterFullscreen ::
    (MonadIO m, DOMHTMLVideoElementK a) =>
    a ->                                    -- _obj
    m ()
dOMHTMLVideoElementWebkitEnterFullscreen _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    onException (do
        propagateGError $ webkit_dom_html_video_element_webkit_enter_fullscreen _obj'
        touchManagedPtr _obj
        return ()
     ) (do
        return ()
     )

-- method DOMHTMLVideoElement::webkit_exit_full_screen
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLVideoElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLVideoElement", 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_video_element_webkit_exit_full_screen" webkit_dom_html_video_element_webkit_exit_full_screen :: 
    Ptr DOMHTMLVideoElement ->              -- _obj : TInterface "WebKit" "DOMHTMLVideoElement"
    IO ()


dOMHTMLVideoElementWebkitExitFullScreen ::
    (MonadIO m, DOMHTMLVideoElementK a) =>
    a ->                                    -- _obj
    m ()
dOMHTMLVideoElementWebkitExitFullScreen _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    webkit_dom_html_video_element_webkit_exit_full_screen _obj'
    touchManagedPtr _obj
    return ()

-- method DOMHTMLVideoElement::webkit_exit_fullscreen
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLVideoElement", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHTMLVideoElement", 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_video_element_webkit_exit_fullscreen" webkit_dom_html_video_element_webkit_exit_fullscreen :: 
    Ptr DOMHTMLVideoElement ->              -- _obj : TInterface "WebKit" "DOMHTMLVideoElement"
    IO ()


dOMHTMLVideoElementWebkitExitFullscreen ::
    (MonadIO m, DOMHTMLVideoElementK a) =>
    a ->                                    -- _obj
    m ()
dOMHTMLVideoElementWebkitExitFullscreen _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    webkit_dom_html_video_element_webkit_exit_fullscreen _obj'
    touchManagedPtr _obj
    return ()