module Graphics.UI.Gtk.WebKit.DOM.VideoTrackList(
item,
getTrackById,
getLength,
change,
addTrack,
removeTrack,
VideoTrackList,
castToVideoTrackList,
gTypeVideoTrackList,
VideoTrackListClass,
toVideoTrackList,
) where
import Prelude hiding (drop, error, print)
import Data.Typeable (Typeable)
import Foreign.Marshal (maybePeek, maybeWith)
import System.Glib.FFI (maybeNull, withForeignPtr, nullForeignPtr, Ptr, nullPtr, castPtr, Word, Int64, Word64, CChar(..), CInt(..), CUInt(..), CLong(..), CULong(..), CLLong(..), CULLong(..), CShort(..), CUShort(..), CFloat(..), CDouble(..), toBool, fromBool)
import System.Glib.UTFString (GlibString(..), readUTFString)
import Control.Applicative ((<$>))
import Control.Monad (void)
import Control.Monad.IO.Class (MonadIO(..))
import System.Glib.GError
import Graphics.UI.Gtk.WebKit.DOM.EventTargetClosures
import Graphics.UI.Gtk.WebKit.DOM.EventM
import Graphics.UI.Gtk.WebKit.Types
import Graphics.UI.Gtk.WebKit.DOM.Enums
item ::
(MonadIO m, VideoTrackListClass self) =>
self -> Word -> m (Maybe VideoTrack)
item self index
= liftIO
(maybeNull (makeNewGObject mkVideoTrack)
((\(VideoTrackList arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_video_track_list_item argPtr1 arg2)
(toVideoTrackList self)
(fromIntegral index)))
getTrackById ::
(MonadIO m, VideoTrackListClass self, GlibString string) =>
self -> string -> m (Maybe VideoTrack)
getTrackById self id
= liftIO
(maybeNull (makeNewGObject mkVideoTrack)
(withUTFString id $
\ idPtr ->
(\(VideoTrackList arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_video_track_list_get_track_by_id argPtr1 arg2)
(toVideoTrackList self)
idPtr))
getLength ::
(MonadIO m, VideoTrackListClass self) => self -> m Word
getLength self
= liftIO
(fromIntegral <$>
((\(VideoTrackList arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_video_track_list_get_length argPtr1)
(toVideoTrackList self)))
change :: (VideoTrackListClass self) => EventName self Event
change = EventName "change"
addTrack :: (VideoTrackListClass self) => EventName self Event
addTrack = EventName "addtrack"
removeTrack :: (VideoTrackListClass self) => EventName self Event
removeTrack = EventName "removetrack"
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/VideoTrackList.h webkit_dom_video_track_list_item"
webkit_dom_video_track_list_item :: ((Ptr VideoTrackList) -> (CULong -> (IO (Ptr VideoTrack))))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/VideoTrackList.h webkit_dom_video_track_list_get_track_by_id"
webkit_dom_video_track_list_get_track_by_id :: ((Ptr VideoTrackList) -> ((Ptr CChar) -> (IO (Ptr VideoTrack))))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/VideoTrackList.h webkit_dom_video_track_list_get_length"
webkit_dom_video_track_list_get_length :: ((Ptr VideoTrackList) -> (IO CULong))