{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- @GtkVideo@ is a widget to show a @GtkMediaStream@ with media controls.
-- 
-- <<https://docs.gtk.org/gtk4/video.png An example GtkVideo>>
-- 
-- The controls are available separately as t'GI.Gtk.Objects.MediaControls.MediaControls'.
-- If you just want to display a video without controls, you can treat it
-- like any other paintable and for example put it into a t'GI.Gtk.Objects.Picture.Picture'.
-- 
-- @GtkVideo@ aims to cover use cases such as previews, embedded animations,
-- etc. It supports autoplay, looping, and simple media controls. It does
-- not have support for video overlays, multichannel audio, device
-- selection, or input. If you are writing a full-fledged video player,
-- you may want to use the t'GI.Gdk.Interfaces.Paintable.Paintable' API and a media framework
-- such as Gstreamer directly.

#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif

module GI.Gtk.Objects.Video
    ( 

-- * Exported types
    Video(..)                               ,
    IsVideo                                 ,
    toVideo                                 ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [actionSetEnabled]("GI.Gtk.Objects.Widget#g:method:actionSetEnabled"), [activate]("GI.Gtk.Objects.Widget#g:method:activate"), [activateAction]("GI.Gtk.Objects.Widget#g:method:activateAction"), [activateDefault]("GI.Gtk.Objects.Widget#g:method:activateDefault"), [addController]("GI.Gtk.Objects.Widget#g:method:addController"), [addCssClass]("GI.Gtk.Objects.Widget#g:method:addCssClass"), [addMnemonicLabel]("GI.Gtk.Objects.Widget#g:method:addMnemonicLabel"), [addTickCallback]("GI.Gtk.Objects.Widget#g:method:addTickCallback"), [allocate]("GI.Gtk.Objects.Widget#g:method:allocate"), [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [childFocus]("GI.Gtk.Objects.Widget#g:method:childFocus"), [computeBounds]("GI.Gtk.Objects.Widget#g:method:computeBounds"), [computeExpand]("GI.Gtk.Objects.Widget#g:method:computeExpand"), [computePoint]("GI.Gtk.Objects.Widget#g:method:computePoint"), [computeTransform]("GI.Gtk.Objects.Widget#g:method:computeTransform"), [contains]("GI.Gtk.Objects.Widget#g:method:contains"), [createPangoContext]("GI.Gtk.Objects.Widget#g:method:createPangoContext"), [createPangoLayout]("GI.Gtk.Objects.Widget#g:method:createPangoLayout"), [disposeTemplate]("GI.Gtk.Objects.Widget#g:method:disposeTemplate"), [dragCheckThreshold]("GI.Gtk.Objects.Widget#g:method:dragCheckThreshold"), [errorBell]("GI.Gtk.Objects.Widget#g:method:errorBell"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [grabFocus]("GI.Gtk.Objects.Widget#g:method:grabFocus"), [hasCssClass]("GI.Gtk.Objects.Widget#g:method:hasCssClass"), [hasDefault]("GI.Gtk.Objects.Widget#g:method:hasDefault"), [hasFocus]("GI.Gtk.Objects.Widget#g:method:hasFocus"), [hasVisibleFocus]("GI.Gtk.Objects.Widget#g:method:hasVisibleFocus"), [hide]("GI.Gtk.Objects.Widget#g:method:hide"), [inDestruction]("GI.Gtk.Objects.Widget#g:method:inDestruction"), [initTemplate]("GI.Gtk.Objects.Widget#g:method:initTemplate"), [insertActionGroup]("GI.Gtk.Objects.Widget#g:method:insertActionGroup"), [insertAfter]("GI.Gtk.Objects.Widget#g:method:insertAfter"), [insertBefore]("GI.Gtk.Objects.Widget#g:method:insertBefore"), [isAncestor]("GI.Gtk.Objects.Widget#g:method:isAncestor"), [isDrawable]("GI.Gtk.Objects.Widget#g:method:isDrawable"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [isFocus]("GI.Gtk.Objects.Widget#g:method:isFocus"), [isSensitive]("GI.Gtk.Objects.Widget#g:method:isSensitive"), [isVisible]("GI.Gtk.Objects.Widget#g:method:isVisible"), [keynavFailed]("GI.Gtk.Objects.Widget#g:method:keynavFailed"), [listMnemonicLabels]("GI.Gtk.Objects.Widget#g:method:listMnemonicLabels"), [map]("GI.Gtk.Objects.Widget#g:method:map"), [measure]("GI.Gtk.Objects.Widget#g:method:measure"), [mnemonicActivate]("GI.Gtk.Objects.Widget#g:method:mnemonicActivate"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [observeChildren]("GI.Gtk.Objects.Widget#g:method:observeChildren"), [observeControllers]("GI.Gtk.Objects.Widget#g:method:observeControllers"), [pick]("GI.Gtk.Objects.Widget#g:method:pick"), [queueAllocate]("GI.Gtk.Objects.Widget#g:method:queueAllocate"), [queueDraw]("GI.Gtk.Objects.Widget#g:method:queueDraw"), [queueResize]("GI.Gtk.Objects.Widget#g:method:queueResize"), [realize]("GI.Gtk.Objects.Widget#g:method:realize"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [removeController]("GI.Gtk.Objects.Widget#g:method:removeController"), [removeCssClass]("GI.Gtk.Objects.Widget#g:method:removeCssClass"), [removeMnemonicLabel]("GI.Gtk.Objects.Widget#g:method:removeMnemonicLabel"), [removeTickCallback]("GI.Gtk.Objects.Widget#g:method:removeTickCallback"), [resetProperty]("GI.Gtk.Interfaces.Accessible#g:method:resetProperty"), [resetRelation]("GI.Gtk.Interfaces.Accessible#g:method:resetRelation"), [resetState]("GI.Gtk.Interfaces.Accessible#g:method:resetState"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [shouldLayout]("GI.Gtk.Objects.Widget#g:method:shouldLayout"), [show]("GI.Gtk.Objects.Widget#g:method:show"), [sizeAllocate]("GI.Gtk.Objects.Widget#g:method:sizeAllocate"), [snapshotChild]("GI.Gtk.Objects.Widget#g:method:snapshotChild"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [translateCoordinates]("GI.Gtk.Objects.Widget#g:method:translateCoordinates"), [triggerTooltipQuery]("GI.Gtk.Objects.Widget#g:method:triggerTooltipQuery"), [unmap]("GI.Gtk.Objects.Widget#g:method:unmap"), [unparent]("GI.Gtk.Objects.Widget#g:method:unparent"), [unrealize]("GI.Gtk.Objects.Widget#g:method:unrealize"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [unsetStateFlags]("GI.Gtk.Objects.Widget#g:method:unsetStateFlags"), [updateProperty]("GI.Gtk.Interfaces.Accessible#g:method:updateProperty"), [updateRelation]("GI.Gtk.Interfaces.Accessible#g:method:updateRelation"), [updateState]("GI.Gtk.Interfaces.Accessible#g:method:updateState"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getAccessibleRole]("GI.Gtk.Interfaces.Accessible#g:method:getAccessibleRole"), [getAllocatedBaseline]("GI.Gtk.Objects.Widget#g:method:getAllocatedBaseline"), [getAllocatedHeight]("GI.Gtk.Objects.Widget#g:method:getAllocatedHeight"), [getAllocatedWidth]("GI.Gtk.Objects.Widget#g:method:getAllocatedWidth"), [getAllocation]("GI.Gtk.Objects.Widget#g:method:getAllocation"), [getAncestor]("GI.Gtk.Objects.Widget#g:method:getAncestor"), [getAutoplay]("GI.Gtk.Objects.Video#g:method:getAutoplay"), [getBuildableId]("GI.Gtk.Interfaces.Buildable#g:method:getBuildableId"), [getCanFocus]("GI.Gtk.Objects.Widget#g:method:getCanFocus"), [getCanTarget]("GI.Gtk.Objects.Widget#g:method:getCanTarget"), [getChildVisible]("GI.Gtk.Objects.Widget#g:method:getChildVisible"), [getClipboard]("GI.Gtk.Objects.Widget#g:method:getClipboard"), [getCssClasses]("GI.Gtk.Objects.Widget#g:method:getCssClasses"), [getCssName]("GI.Gtk.Objects.Widget#g:method:getCssName"), [getCursor]("GI.Gtk.Objects.Widget#g:method:getCursor"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getDirection]("GI.Gtk.Objects.Widget#g:method:getDirection"), [getDisplay]("GI.Gtk.Objects.Widget#g:method:getDisplay"), [getFile]("GI.Gtk.Objects.Video#g:method:getFile"), [getFirstChild]("GI.Gtk.Objects.Widget#g:method:getFirstChild"), [getFocusChild]("GI.Gtk.Objects.Widget#g:method:getFocusChild"), [getFocusOnClick]("GI.Gtk.Objects.Widget#g:method:getFocusOnClick"), [getFocusable]("GI.Gtk.Objects.Widget#g:method:getFocusable"), [getFontMap]("GI.Gtk.Objects.Widget#g:method:getFontMap"), [getFontOptions]("GI.Gtk.Objects.Widget#g:method:getFontOptions"), [getFrameClock]("GI.Gtk.Objects.Widget#g:method:getFrameClock"), [getHalign]("GI.Gtk.Objects.Widget#g:method:getHalign"), [getHasTooltip]("GI.Gtk.Objects.Widget#g:method:getHasTooltip"), [getHeight]("GI.Gtk.Objects.Widget#g:method:getHeight"), [getHexpand]("GI.Gtk.Objects.Widget#g:method:getHexpand"), [getHexpandSet]("GI.Gtk.Objects.Widget#g:method:getHexpandSet"), [getLastChild]("GI.Gtk.Objects.Widget#g:method:getLastChild"), [getLayoutManager]("GI.Gtk.Objects.Widget#g:method:getLayoutManager"), [getLoop]("GI.Gtk.Objects.Video#g:method:getLoop"), [getMapped]("GI.Gtk.Objects.Widget#g:method:getMapped"), [getMarginBottom]("GI.Gtk.Objects.Widget#g:method:getMarginBottom"), [getMarginEnd]("GI.Gtk.Objects.Widget#g:method:getMarginEnd"), [getMarginStart]("GI.Gtk.Objects.Widget#g:method:getMarginStart"), [getMarginTop]("GI.Gtk.Objects.Widget#g:method:getMarginTop"), [getMediaStream]("GI.Gtk.Objects.Video#g:method:getMediaStream"), [getName]("GI.Gtk.Objects.Widget#g:method:getName"), [getNative]("GI.Gtk.Objects.Widget#g:method:getNative"), [getNextSibling]("GI.Gtk.Objects.Widget#g:method:getNextSibling"), [getOpacity]("GI.Gtk.Objects.Widget#g:method:getOpacity"), [getOverflow]("GI.Gtk.Objects.Widget#g:method:getOverflow"), [getPangoContext]("GI.Gtk.Objects.Widget#g:method:getPangoContext"), [getParent]("GI.Gtk.Objects.Widget#g:method:getParent"), [getPreferredSize]("GI.Gtk.Objects.Widget#g:method:getPreferredSize"), [getPrevSibling]("GI.Gtk.Objects.Widget#g:method:getPrevSibling"), [getPrimaryClipboard]("GI.Gtk.Objects.Widget#g:method:getPrimaryClipboard"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getRealized]("GI.Gtk.Objects.Widget#g:method:getRealized"), [getReceivesDefault]("GI.Gtk.Objects.Widget#g:method:getReceivesDefault"), [getRequestMode]("GI.Gtk.Objects.Widget#g:method:getRequestMode"), [getRoot]("GI.Gtk.Objects.Widget#g:method:getRoot"), [getScaleFactor]("GI.Gtk.Objects.Widget#g:method:getScaleFactor"), [getSensitive]("GI.Gtk.Objects.Widget#g:method:getSensitive"), [getSettings]("GI.Gtk.Objects.Widget#g:method:getSettings"), [getSize]("GI.Gtk.Objects.Widget#g:method:getSize"), [getSizeRequest]("GI.Gtk.Objects.Widget#g:method:getSizeRequest"), [getStateFlags]("GI.Gtk.Objects.Widget#g:method:getStateFlags"), [getStyleContext]("GI.Gtk.Objects.Widget#g:method:getStyleContext"), [getTemplateChild]("GI.Gtk.Objects.Widget#g:method:getTemplateChild"), [getTooltipMarkup]("GI.Gtk.Objects.Widget#g:method:getTooltipMarkup"), [getTooltipText]("GI.Gtk.Objects.Widget#g:method:getTooltipText"), [getValign]("GI.Gtk.Objects.Widget#g:method:getValign"), [getVexpand]("GI.Gtk.Objects.Widget#g:method:getVexpand"), [getVexpandSet]("GI.Gtk.Objects.Widget#g:method:getVexpandSet"), [getVisible]("GI.Gtk.Objects.Widget#g:method:getVisible"), [getWidth]("GI.Gtk.Objects.Widget#g:method:getWidth").
-- 
-- ==== Setters
-- [setAutoplay]("GI.Gtk.Objects.Video#g:method:setAutoplay"), [setCanFocus]("GI.Gtk.Objects.Widget#g:method:setCanFocus"), [setCanTarget]("GI.Gtk.Objects.Widget#g:method:setCanTarget"), [setChildVisible]("GI.Gtk.Objects.Widget#g:method:setChildVisible"), [setCssClasses]("GI.Gtk.Objects.Widget#g:method:setCssClasses"), [setCursor]("GI.Gtk.Objects.Widget#g:method:setCursor"), [setCursorFromName]("GI.Gtk.Objects.Widget#g:method:setCursorFromName"), [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setDirection]("GI.Gtk.Objects.Widget#g:method:setDirection"), [setFile]("GI.Gtk.Objects.Video#g:method:setFile"), [setFilename]("GI.Gtk.Objects.Video#g:method:setFilename"), [setFocusChild]("GI.Gtk.Objects.Widget#g:method:setFocusChild"), [setFocusOnClick]("GI.Gtk.Objects.Widget#g:method:setFocusOnClick"), [setFocusable]("GI.Gtk.Objects.Widget#g:method:setFocusable"), [setFontMap]("GI.Gtk.Objects.Widget#g:method:setFontMap"), [setFontOptions]("GI.Gtk.Objects.Widget#g:method:setFontOptions"), [setHalign]("GI.Gtk.Objects.Widget#g:method:setHalign"), [setHasTooltip]("GI.Gtk.Objects.Widget#g:method:setHasTooltip"), [setHexpand]("GI.Gtk.Objects.Widget#g:method:setHexpand"), [setHexpandSet]("GI.Gtk.Objects.Widget#g:method:setHexpandSet"), [setLayoutManager]("GI.Gtk.Objects.Widget#g:method:setLayoutManager"), [setLoop]("GI.Gtk.Objects.Video#g:method:setLoop"), [setMarginBottom]("GI.Gtk.Objects.Widget#g:method:setMarginBottom"), [setMarginEnd]("GI.Gtk.Objects.Widget#g:method:setMarginEnd"), [setMarginStart]("GI.Gtk.Objects.Widget#g:method:setMarginStart"), [setMarginTop]("GI.Gtk.Objects.Widget#g:method:setMarginTop"), [setMediaStream]("GI.Gtk.Objects.Video#g:method:setMediaStream"), [setName]("GI.Gtk.Objects.Widget#g:method:setName"), [setOpacity]("GI.Gtk.Objects.Widget#g:method:setOpacity"), [setOverflow]("GI.Gtk.Objects.Widget#g:method:setOverflow"), [setParent]("GI.Gtk.Objects.Widget#g:method:setParent"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setReceivesDefault]("GI.Gtk.Objects.Widget#g:method:setReceivesDefault"), [setResource]("GI.Gtk.Objects.Video#g:method:setResource"), [setSensitive]("GI.Gtk.Objects.Widget#g:method:setSensitive"), [setSizeRequest]("GI.Gtk.Objects.Widget#g:method:setSizeRequest"), [setStateFlags]("GI.Gtk.Objects.Widget#g:method:setStateFlags"), [setTooltipMarkup]("GI.Gtk.Objects.Widget#g:method:setTooltipMarkup"), [setTooltipText]("GI.Gtk.Objects.Widget#g:method:setTooltipText"), [setValign]("GI.Gtk.Objects.Widget#g:method:setValign"), [setVexpand]("GI.Gtk.Objects.Widget#g:method:setVexpand"), [setVexpandSet]("GI.Gtk.Objects.Widget#g:method:setVexpandSet"), [setVisible]("GI.Gtk.Objects.Widget#g:method:setVisible").

#if defined(ENABLE_OVERLOADING)
    ResolveVideoMethod                      ,
#endif

-- ** getAutoplay #method:getAutoplay#

#if defined(ENABLE_OVERLOADING)
    VideoGetAutoplayMethodInfo              ,
#endif
    videoGetAutoplay                        ,


-- ** getFile #method:getFile#

#if defined(ENABLE_OVERLOADING)
    VideoGetFileMethodInfo                  ,
#endif
    videoGetFile                            ,


-- ** getLoop #method:getLoop#

#if defined(ENABLE_OVERLOADING)
    VideoGetLoopMethodInfo                  ,
#endif
    videoGetLoop                            ,


-- ** getMediaStream #method:getMediaStream#

#if defined(ENABLE_OVERLOADING)
    VideoGetMediaStreamMethodInfo           ,
#endif
    videoGetMediaStream                     ,


-- ** new #method:new#

    videoNew                                ,


-- ** newForFile #method:newForFile#

    videoNewForFile                         ,


-- ** newForFilename #method:newForFilename#

    videoNewForFilename                     ,


-- ** newForMediaStream #method:newForMediaStream#

    videoNewForMediaStream                  ,


-- ** newForResource #method:newForResource#

    videoNewForResource                     ,


-- ** setAutoplay #method:setAutoplay#

#if defined(ENABLE_OVERLOADING)
    VideoSetAutoplayMethodInfo              ,
#endif
    videoSetAutoplay                        ,


-- ** setFile #method:setFile#

#if defined(ENABLE_OVERLOADING)
    VideoSetFileMethodInfo                  ,
#endif
    videoSetFile                            ,


-- ** setFilename #method:setFilename#

#if defined(ENABLE_OVERLOADING)
    VideoSetFilenameMethodInfo              ,
#endif
    videoSetFilename                        ,


-- ** setLoop #method:setLoop#

#if defined(ENABLE_OVERLOADING)
    VideoSetLoopMethodInfo                  ,
#endif
    videoSetLoop                            ,


-- ** setMediaStream #method:setMediaStream#

#if defined(ENABLE_OVERLOADING)
    VideoSetMediaStreamMethodInfo           ,
#endif
    videoSetMediaStream                     ,


-- ** setResource #method:setResource#

#if defined(ENABLE_OVERLOADING)
    VideoSetResourceMethodInfo              ,
#endif
    videoSetResource                        ,




 -- * Properties


-- ** autoplay #attr:autoplay#
-- | If the video should automatically begin playing.

#if defined(ENABLE_OVERLOADING)
    VideoAutoplayPropertyInfo               ,
#endif
    constructVideoAutoplay                  ,
    getVideoAutoplay                        ,
    setVideoAutoplay                        ,
#if defined(ENABLE_OVERLOADING)
    videoAutoplay                           ,
#endif


-- ** file #attr:file#
-- | The file played by this video if the video is playing a file.

#if defined(ENABLE_OVERLOADING)
    VideoFilePropertyInfo                   ,
#endif
    clearVideoFile                          ,
    constructVideoFile                      ,
    getVideoFile                            ,
    setVideoFile                            ,
#if defined(ENABLE_OVERLOADING)
    videoFile                               ,
#endif


-- ** loop #attr:loop#
-- | If new media files should be set to loop.

#if defined(ENABLE_OVERLOADING)
    VideoLoopPropertyInfo                   ,
#endif
    constructVideoLoop                      ,
    getVideoLoop                            ,
    setVideoLoop                            ,
#if defined(ENABLE_OVERLOADING)
    videoLoop                               ,
#endif


-- ** mediaStream #attr:mediaStream#
-- | The media-stream played

#if defined(ENABLE_OVERLOADING)
    VideoMediaStreamPropertyInfo            ,
#endif
    clearVideoMediaStream                   ,
    constructVideoMediaStream               ,
    getVideoMediaStream                     ,
    setVideoMediaStream                     ,
#if defined(ENABLE_OVERLOADING)
    videoMediaStream                        ,
#endif




    ) where

import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R

import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gio.Interfaces.File as Gio.File
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Accessible as Gtk.Accessible
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.ConstraintTarget as Gtk.ConstraintTarget
import {-# SOURCE #-} qualified GI.Gtk.Objects.MediaStream as Gtk.MediaStream
import {-# SOURCE #-} qualified GI.Gtk.Objects.Widget as Gtk.Widget

-- | Memory-managed wrapper type.
newtype Video = Video (SP.ManagedPtr Video)
    deriving (Video -> Video -> Bool
(Video -> Video -> Bool) -> (Video -> Video -> Bool) -> Eq Video
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Video -> Video -> Bool
== :: Video -> Video -> Bool
$c/= :: Video -> Video -> Bool
/= :: Video -> Video -> Bool
Eq)

instance SP.ManagedPtrNewtype Video where
    toManagedPtr :: Video -> ManagedPtr Video
toManagedPtr (Video ManagedPtr Video
p) = ManagedPtr Video
p

foreign import ccall "gtk_video_get_type"
    c_gtk_video_get_type :: IO B.Types.GType

instance B.Types.TypedObject Video where
    glibType :: IO GType
glibType = IO GType
c_gtk_video_get_type

instance B.Types.GObject Video

-- | Type class for types which can be safely cast to `Video`, for instance with `toVideo`.
class (SP.GObject o, O.IsDescendantOf Video o) => IsVideo o
instance (SP.GObject o, O.IsDescendantOf Video o) => IsVideo o

instance O.HasParentTypes Video
type instance O.ParentTypes Video = '[Gtk.Widget.Widget, GObject.Object.Object, Gtk.Accessible.Accessible, Gtk.Buildable.Buildable, Gtk.ConstraintTarget.ConstraintTarget]

-- | Cast to `Video`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toVideo :: (MIO.MonadIO m, IsVideo o) => o -> m Video
toVideo :: forall (m :: * -> *) o. (MonadIO m, IsVideo o) => o -> m Video
toVideo = IO Video -> m Video
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Video -> m Video) -> (o -> IO Video) -> o -> m Video
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr Video -> Video) -> o -> IO Video
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr Video -> Video
Video

-- | Convert 'Video' to and from 'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue (Maybe Video) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gtk_video_get_type
    gvalueSet_ :: Ptr GValue -> Maybe Video -> IO ()
gvalueSet_ Ptr GValue
gv Maybe Video
P.Nothing = Ptr GValue -> Ptr Video -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr Video
forall a. Ptr a
FP.nullPtr :: FP.Ptr Video)
    gvalueSet_ Ptr GValue
gv (P.Just Video
obj) = Video -> (Ptr Video -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Video
obj (Ptr GValue -> Ptr Video -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe Video)
gvalueGet_ Ptr GValue
gv = do
        Ptr Video
ptr <- Ptr GValue -> IO (Ptr Video)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr Video)
        if Ptr Video
ptr Ptr Video -> Ptr Video -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr Video
forall a. Ptr a
FP.nullPtr
        then Video -> Maybe Video
forall a. a -> Maybe a
P.Just (Video -> Maybe Video) -> IO Video -> IO (Maybe Video)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr Video -> Video) -> Ptr Video -> IO Video
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr Video -> Video
Video Ptr Video
ptr
        else Maybe Video -> IO (Maybe Video)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Video
forall a. Maybe a
P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
type family ResolveVideoMethod (t :: Symbol) (o :: *) :: * where
    ResolveVideoMethod "actionSetEnabled" o = Gtk.Widget.WidgetActionSetEnabledMethodInfo
    ResolveVideoMethod "activate" o = Gtk.Widget.WidgetActivateMethodInfo
    ResolveVideoMethod "activateAction" o = Gtk.Widget.WidgetActivateActionMethodInfo
    ResolveVideoMethod "activateDefault" o = Gtk.Widget.WidgetActivateDefaultMethodInfo
    ResolveVideoMethod "addController" o = Gtk.Widget.WidgetAddControllerMethodInfo
    ResolveVideoMethod "addCssClass" o = Gtk.Widget.WidgetAddCssClassMethodInfo
    ResolveVideoMethod "addMnemonicLabel" o = Gtk.Widget.WidgetAddMnemonicLabelMethodInfo
    ResolveVideoMethod "addTickCallback" o = Gtk.Widget.WidgetAddTickCallbackMethodInfo
    ResolveVideoMethod "allocate" o = Gtk.Widget.WidgetAllocateMethodInfo
    ResolveVideoMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveVideoMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveVideoMethod "childFocus" o = Gtk.Widget.WidgetChildFocusMethodInfo
    ResolveVideoMethod "computeBounds" o = Gtk.Widget.WidgetComputeBoundsMethodInfo
    ResolveVideoMethod "computeExpand" o = Gtk.Widget.WidgetComputeExpandMethodInfo
    ResolveVideoMethod "computePoint" o = Gtk.Widget.WidgetComputePointMethodInfo
    ResolveVideoMethod "computeTransform" o = Gtk.Widget.WidgetComputeTransformMethodInfo
    ResolveVideoMethod "contains" o = Gtk.Widget.WidgetContainsMethodInfo
    ResolveVideoMethod "createPangoContext" o = Gtk.Widget.WidgetCreatePangoContextMethodInfo
    ResolveVideoMethod "createPangoLayout" o = Gtk.Widget.WidgetCreatePangoLayoutMethodInfo
    ResolveVideoMethod "disposeTemplate" o = Gtk.Widget.WidgetDisposeTemplateMethodInfo
    ResolveVideoMethod "dragCheckThreshold" o = Gtk.Widget.WidgetDragCheckThresholdMethodInfo
    ResolveVideoMethod "errorBell" o = Gtk.Widget.WidgetErrorBellMethodInfo
    ResolveVideoMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveVideoMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveVideoMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveVideoMethod "grabFocus" o = Gtk.Widget.WidgetGrabFocusMethodInfo
    ResolveVideoMethod "hasCssClass" o = Gtk.Widget.WidgetHasCssClassMethodInfo
    ResolveVideoMethod "hasDefault" o = Gtk.Widget.WidgetHasDefaultMethodInfo
    ResolveVideoMethod "hasFocus" o = Gtk.Widget.WidgetHasFocusMethodInfo
    ResolveVideoMethod "hasVisibleFocus" o = Gtk.Widget.WidgetHasVisibleFocusMethodInfo
    ResolveVideoMethod "hide" o = Gtk.Widget.WidgetHideMethodInfo
    ResolveVideoMethod "inDestruction" o = Gtk.Widget.WidgetInDestructionMethodInfo
    ResolveVideoMethod "initTemplate" o = Gtk.Widget.WidgetInitTemplateMethodInfo
    ResolveVideoMethod "insertActionGroup" o = Gtk.Widget.WidgetInsertActionGroupMethodInfo
    ResolveVideoMethod "insertAfter" o = Gtk.Widget.WidgetInsertAfterMethodInfo
    ResolveVideoMethod "insertBefore" o = Gtk.Widget.WidgetInsertBeforeMethodInfo
    ResolveVideoMethod "isAncestor" o = Gtk.Widget.WidgetIsAncestorMethodInfo
    ResolveVideoMethod "isDrawable" o = Gtk.Widget.WidgetIsDrawableMethodInfo
    ResolveVideoMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveVideoMethod "isFocus" o = Gtk.Widget.WidgetIsFocusMethodInfo
    ResolveVideoMethod "isSensitive" o = Gtk.Widget.WidgetIsSensitiveMethodInfo
    ResolveVideoMethod "isVisible" o = Gtk.Widget.WidgetIsVisibleMethodInfo
    ResolveVideoMethod "keynavFailed" o = Gtk.Widget.WidgetKeynavFailedMethodInfo
    ResolveVideoMethod "listMnemonicLabels" o = Gtk.Widget.WidgetListMnemonicLabelsMethodInfo
    ResolveVideoMethod "map" o = Gtk.Widget.WidgetMapMethodInfo
    ResolveVideoMethod "measure" o = Gtk.Widget.WidgetMeasureMethodInfo
    ResolveVideoMethod "mnemonicActivate" o = Gtk.Widget.WidgetMnemonicActivateMethodInfo
    ResolveVideoMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveVideoMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveVideoMethod "observeChildren" o = Gtk.Widget.WidgetObserveChildrenMethodInfo
    ResolveVideoMethod "observeControllers" o = Gtk.Widget.WidgetObserveControllersMethodInfo
    ResolveVideoMethod "pick" o = Gtk.Widget.WidgetPickMethodInfo
    ResolveVideoMethod "queueAllocate" o = Gtk.Widget.WidgetQueueAllocateMethodInfo
    ResolveVideoMethod "queueDraw" o = Gtk.Widget.WidgetQueueDrawMethodInfo
    ResolveVideoMethod "queueResize" o = Gtk.Widget.WidgetQueueResizeMethodInfo
    ResolveVideoMethod "realize" o = Gtk.Widget.WidgetRealizeMethodInfo
    ResolveVideoMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveVideoMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveVideoMethod "removeController" o = Gtk.Widget.WidgetRemoveControllerMethodInfo
    ResolveVideoMethod "removeCssClass" o = Gtk.Widget.WidgetRemoveCssClassMethodInfo
    ResolveVideoMethod "removeMnemonicLabel" o = Gtk.Widget.WidgetRemoveMnemonicLabelMethodInfo
    ResolveVideoMethod "removeTickCallback" o = Gtk.Widget.WidgetRemoveTickCallbackMethodInfo
    ResolveVideoMethod "resetProperty" o = Gtk.Accessible.AccessibleResetPropertyMethodInfo
    ResolveVideoMethod "resetRelation" o = Gtk.Accessible.AccessibleResetRelationMethodInfo
    ResolveVideoMethod "resetState" o = Gtk.Accessible.AccessibleResetStateMethodInfo
    ResolveVideoMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveVideoMethod "shouldLayout" o = Gtk.Widget.WidgetShouldLayoutMethodInfo
    ResolveVideoMethod "show" o = Gtk.Widget.WidgetShowMethodInfo
    ResolveVideoMethod "sizeAllocate" o = Gtk.Widget.WidgetSizeAllocateMethodInfo
    ResolveVideoMethod "snapshotChild" o = Gtk.Widget.WidgetSnapshotChildMethodInfo
    ResolveVideoMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveVideoMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveVideoMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveVideoMethod "translateCoordinates" o = Gtk.Widget.WidgetTranslateCoordinatesMethodInfo
    ResolveVideoMethod "triggerTooltipQuery" o = Gtk.Widget.WidgetTriggerTooltipQueryMethodInfo
    ResolveVideoMethod "unmap" o = Gtk.Widget.WidgetUnmapMethodInfo
    ResolveVideoMethod "unparent" o = Gtk.Widget.WidgetUnparentMethodInfo
    ResolveVideoMethod "unrealize" o = Gtk.Widget.WidgetUnrealizeMethodInfo
    ResolveVideoMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveVideoMethod "unsetStateFlags" o = Gtk.Widget.WidgetUnsetStateFlagsMethodInfo
    ResolveVideoMethod "updateProperty" o = Gtk.Accessible.AccessibleUpdatePropertyMethodInfo
    ResolveVideoMethod "updateRelation" o = Gtk.Accessible.AccessibleUpdateRelationMethodInfo
    ResolveVideoMethod "updateState" o = Gtk.Accessible.AccessibleUpdateStateMethodInfo
    ResolveVideoMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveVideoMethod "getAccessibleRole" o = Gtk.Accessible.AccessibleGetAccessibleRoleMethodInfo
    ResolveVideoMethod "getAllocatedBaseline" o = Gtk.Widget.WidgetGetAllocatedBaselineMethodInfo
    ResolveVideoMethod "getAllocatedHeight" o = Gtk.Widget.WidgetGetAllocatedHeightMethodInfo
    ResolveVideoMethod "getAllocatedWidth" o = Gtk.Widget.WidgetGetAllocatedWidthMethodInfo
    ResolveVideoMethod "getAllocation" o = Gtk.Widget.WidgetGetAllocationMethodInfo
    ResolveVideoMethod "getAncestor" o = Gtk.Widget.WidgetGetAncestorMethodInfo
    ResolveVideoMethod "getAutoplay" o = VideoGetAutoplayMethodInfo
    ResolveVideoMethod "getBuildableId" o = Gtk.Buildable.BuildableGetBuildableIdMethodInfo
    ResolveVideoMethod "getCanFocus" o = Gtk.Widget.WidgetGetCanFocusMethodInfo
    ResolveVideoMethod "getCanTarget" o = Gtk.Widget.WidgetGetCanTargetMethodInfo
    ResolveVideoMethod "getChildVisible" o = Gtk.Widget.WidgetGetChildVisibleMethodInfo
    ResolveVideoMethod "getClipboard" o = Gtk.Widget.WidgetGetClipboardMethodInfo
    ResolveVideoMethod "getCssClasses" o = Gtk.Widget.WidgetGetCssClassesMethodInfo
    ResolveVideoMethod "getCssName" o = Gtk.Widget.WidgetGetCssNameMethodInfo
    ResolveVideoMethod "getCursor" o = Gtk.Widget.WidgetGetCursorMethodInfo
    ResolveVideoMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveVideoMethod "getDirection" o = Gtk.Widget.WidgetGetDirectionMethodInfo
    ResolveVideoMethod "getDisplay" o = Gtk.Widget.WidgetGetDisplayMethodInfo
    ResolveVideoMethod "getFile" o = VideoGetFileMethodInfo
    ResolveVideoMethod "getFirstChild" o = Gtk.Widget.WidgetGetFirstChildMethodInfo
    ResolveVideoMethod "getFocusChild" o = Gtk.Widget.WidgetGetFocusChildMethodInfo
    ResolveVideoMethod "getFocusOnClick" o = Gtk.Widget.WidgetGetFocusOnClickMethodInfo
    ResolveVideoMethod "getFocusable" o = Gtk.Widget.WidgetGetFocusableMethodInfo
    ResolveVideoMethod "getFontMap" o = Gtk.Widget.WidgetGetFontMapMethodInfo
    ResolveVideoMethod "getFontOptions" o = Gtk.Widget.WidgetGetFontOptionsMethodInfo
    ResolveVideoMethod "getFrameClock" o = Gtk.Widget.WidgetGetFrameClockMethodInfo
    ResolveVideoMethod "getHalign" o = Gtk.Widget.WidgetGetHalignMethodInfo
    ResolveVideoMethod "getHasTooltip" o = Gtk.Widget.WidgetGetHasTooltipMethodInfo
    ResolveVideoMethod "getHeight" o = Gtk.Widget.WidgetGetHeightMethodInfo
    ResolveVideoMethod "getHexpand" o = Gtk.Widget.WidgetGetHexpandMethodInfo
    ResolveVideoMethod "getHexpandSet" o = Gtk.Widget.WidgetGetHexpandSetMethodInfo
    ResolveVideoMethod "getLastChild" o = Gtk.Widget.WidgetGetLastChildMethodInfo
    ResolveVideoMethod "getLayoutManager" o = Gtk.Widget.WidgetGetLayoutManagerMethodInfo
    ResolveVideoMethod "getLoop" o = VideoGetLoopMethodInfo
    ResolveVideoMethod "getMapped" o = Gtk.Widget.WidgetGetMappedMethodInfo
    ResolveVideoMethod "getMarginBottom" o = Gtk.Widget.WidgetGetMarginBottomMethodInfo
    ResolveVideoMethod "getMarginEnd" o = Gtk.Widget.WidgetGetMarginEndMethodInfo
    ResolveVideoMethod "getMarginStart" o = Gtk.Widget.WidgetGetMarginStartMethodInfo
    ResolveVideoMethod "getMarginTop" o = Gtk.Widget.WidgetGetMarginTopMethodInfo
    ResolveVideoMethod "getMediaStream" o = VideoGetMediaStreamMethodInfo
    ResolveVideoMethod "getName" o = Gtk.Widget.WidgetGetNameMethodInfo
    ResolveVideoMethod "getNative" o = Gtk.Widget.WidgetGetNativeMethodInfo
    ResolveVideoMethod "getNextSibling" o = Gtk.Widget.WidgetGetNextSiblingMethodInfo
    ResolveVideoMethod "getOpacity" o = Gtk.Widget.WidgetGetOpacityMethodInfo
    ResolveVideoMethod "getOverflow" o = Gtk.Widget.WidgetGetOverflowMethodInfo
    ResolveVideoMethod "getPangoContext" o = Gtk.Widget.WidgetGetPangoContextMethodInfo
    ResolveVideoMethod "getParent" o = Gtk.Widget.WidgetGetParentMethodInfo
    ResolveVideoMethod "getPreferredSize" o = Gtk.Widget.WidgetGetPreferredSizeMethodInfo
    ResolveVideoMethod "getPrevSibling" o = Gtk.Widget.WidgetGetPrevSiblingMethodInfo
    ResolveVideoMethod "getPrimaryClipboard" o = Gtk.Widget.WidgetGetPrimaryClipboardMethodInfo
    ResolveVideoMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveVideoMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveVideoMethod "getRealized" o = Gtk.Widget.WidgetGetRealizedMethodInfo
    ResolveVideoMethod "getReceivesDefault" o = Gtk.Widget.WidgetGetReceivesDefaultMethodInfo
    ResolveVideoMethod "getRequestMode" o = Gtk.Widget.WidgetGetRequestModeMethodInfo
    ResolveVideoMethod "getRoot" o = Gtk.Widget.WidgetGetRootMethodInfo
    ResolveVideoMethod "getScaleFactor" o = Gtk.Widget.WidgetGetScaleFactorMethodInfo
    ResolveVideoMethod "getSensitive" o = Gtk.Widget.WidgetGetSensitiveMethodInfo
    ResolveVideoMethod "getSettings" o = Gtk.Widget.WidgetGetSettingsMethodInfo
    ResolveVideoMethod "getSize" o = Gtk.Widget.WidgetGetSizeMethodInfo
    ResolveVideoMethod "getSizeRequest" o = Gtk.Widget.WidgetGetSizeRequestMethodInfo
    ResolveVideoMethod "getStateFlags" o = Gtk.Widget.WidgetGetStateFlagsMethodInfo
    ResolveVideoMethod "getStyleContext" o = Gtk.Widget.WidgetGetStyleContextMethodInfo
    ResolveVideoMethod "getTemplateChild" o = Gtk.Widget.WidgetGetTemplateChildMethodInfo
    ResolveVideoMethod "getTooltipMarkup" o = Gtk.Widget.WidgetGetTooltipMarkupMethodInfo
    ResolveVideoMethod "getTooltipText" o = Gtk.Widget.WidgetGetTooltipTextMethodInfo
    ResolveVideoMethod "getValign" o = Gtk.Widget.WidgetGetValignMethodInfo
    ResolveVideoMethod "getVexpand" o = Gtk.Widget.WidgetGetVexpandMethodInfo
    ResolveVideoMethod "getVexpandSet" o = Gtk.Widget.WidgetGetVexpandSetMethodInfo
    ResolveVideoMethod "getVisible" o = Gtk.Widget.WidgetGetVisibleMethodInfo
    ResolveVideoMethod "getWidth" o = Gtk.Widget.WidgetGetWidthMethodInfo
    ResolveVideoMethod "setAutoplay" o = VideoSetAutoplayMethodInfo
    ResolveVideoMethod "setCanFocus" o = Gtk.Widget.WidgetSetCanFocusMethodInfo
    ResolveVideoMethod "setCanTarget" o = Gtk.Widget.WidgetSetCanTargetMethodInfo
    ResolveVideoMethod "setChildVisible" o = Gtk.Widget.WidgetSetChildVisibleMethodInfo
    ResolveVideoMethod "setCssClasses" o = Gtk.Widget.WidgetSetCssClassesMethodInfo
    ResolveVideoMethod "setCursor" o = Gtk.Widget.WidgetSetCursorMethodInfo
    ResolveVideoMethod "setCursorFromName" o = Gtk.Widget.WidgetSetCursorFromNameMethodInfo
    ResolveVideoMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveVideoMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveVideoMethod "setDirection" o = Gtk.Widget.WidgetSetDirectionMethodInfo
    ResolveVideoMethod "setFile" o = VideoSetFileMethodInfo
    ResolveVideoMethod "setFilename" o = VideoSetFilenameMethodInfo
    ResolveVideoMethod "setFocusChild" o = Gtk.Widget.WidgetSetFocusChildMethodInfo
    ResolveVideoMethod "setFocusOnClick" o = Gtk.Widget.WidgetSetFocusOnClickMethodInfo
    ResolveVideoMethod "setFocusable" o = Gtk.Widget.WidgetSetFocusableMethodInfo
    ResolveVideoMethod "setFontMap" o = Gtk.Widget.WidgetSetFontMapMethodInfo
    ResolveVideoMethod "setFontOptions" o = Gtk.Widget.WidgetSetFontOptionsMethodInfo
    ResolveVideoMethod "setHalign" o = Gtk.Widget.WidgetSetHalignMethodInfo
    ResolveVideoMethod "setHasTooltip" o = Gtk.Widget.WidgetSetHasTooltipMethodInfo
    ResolveVideoMethod "setHexpand" o = Gtk.Widget.WidgetSetHexpandMethodInfo
    ResolveVideoMethod "setHexpandSet" o = Gtk.Widget.WidgetSetHexpandSetMethodInfo
    ResolveVideoMethod "setLayoutManager" o = Gtk.Widget.WidgetSetLayoutManagerMethodInfo
    ResolveVideoMethod "setLoop" o = VideoSetLoopMethodInfo
    ResolveVideoMethod "setMarginBottom" o = Gtk.Widget.WidgetSetMarginBottomMethodInfo
    ResolveVideoMethod "setMarginEnd" o = Gtk.Widget.WidgetSetMarginEndMethodInfo
    ResolveVideoMethod "setMarginStart" o = Gtk.Widget.WidgetSetMarginStartMethodInfo
    ResolveVideoMethod "setMarginTop" o = Gtk.Widget.WidgetSetMarginTopMethodInfo
    ResolveVideoMethod "setMediaStream" o = VideoSetMediaStreamMethodInfo
    ResolveVideoMethod "setName" o = Gtk.Widget.WidgetSetNameMethodInfo
    ResolveVideoMethod "setOpacity" o = Gtk.Widget.WidgetSetOpacityMethodInfo
    ResolveVideoMethod "setOverflow" o = Gtk.Widget.WidgetSetOverflowMethodInfo
    ResolveVideoMethod "setParent" o = Gtk.Widget.WidgetSetParentMethodInfo
    ResolveVideoMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveVideoMethod "setReceivesDefault" o = Gtk.Widget.WidgetSetReceivesDefaultMethodInfo
    ResolveVideoMethod "setResource" o = VideoSetResourceMethodInfo
    ResolveVideoMethod "setSensitive" o = Gtk.Widget.WidgetSetSensitiveMethodInfo
    ResolveVideoMethod "setSizeRequest" o = Gtk.Widget.WidgetSetSizeRequestMethodInfo
    ResolveVideoMethod "setStateFlags" o = Gtk.Widget.WidgetSetStateFlagsMethodInfo
    ResolveVideoMethod "setTooltipMarkup" o = Gtk.Widget.WidgetSetTooltipMarkupMethodInfo
    ResolveVideoMethod "setTooltipText" o = Gtk.Widget.WidgetSetTooltipTextMethodInfo
    ResolveVideoMethod "setValign" o = Gtk.Widget.WidgetSetValignMethodInfo
    ResolveVideoMethod "setVexpand" o = Gtk.Widget.WidgetSetVexpandMethodInfo
    ResolveVideoMethod "setVexpandSet" o = Gtk.Widget.WidgetSetVexpandSetMethodInfo
    ResolveVideoMethod "setVisible" o = Gtk.Widget.WidgetSetVisibleMethodInfo
    ResolveVideoMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveVideoMethod t Video, O.OverloadedMethod info Video p) => OL.IsLabel t (Video -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveVideoMethod t Video, O.OverloadedMethod info Video p, R.HasField t Video p) => R.HasField t Video p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolveVideoMethod t Video, O.OverloadedMethodInfo info Video) => OL.IsLabel t (O.MethodProxy info Video) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif

#endif

-- VVV Prop "autoplay"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@autoplay@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' video #autoplay
-- @
getVideoAutoplay :: (MonadIO m, IsVideo o) => o -> m Bool
getVideoAutoplay :: forall (m :: * -> *) o. (MonadIO m, IsVideo o) => o -> m Bool
getVideoAutoplay o
obj = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"autoplay"

-- | Set the value of the “@autoplay@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' video [ #autoplay 'Data.GI.Base.Attributes.:=' value ]
-- @
setVideoAutoplay :: (MonadIO m, IsVideo o) => o -> Bool -> m ()
setVideoAutoplay :: forall (m :: * -> *) o. (MonadIO m, IsVideo o) => o -> Bool -> m ()
setVideoAutoplay o
obj Bool
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"autoplay" Bool
val

-- | Construct a `GValueConstruct` with valid value for the “@autoplay@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructVideoAutoplay :: (IsVideo o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructVideoAutoplay :: forall o (m :: * -> *).
(IsVideo o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructVideoAutoplay Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"autoplay" Bool
val

#if defined(ENABLE_OVERLOADING)
data VideoAutoplayPropertyInfo
instance AttrInfo VideoAutoplayPropertyInfo where
    type AttrAllowedOps VideoAutoplayPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint VideoAutoplayPropertyInfo = IsVideo
    type AttrSetTypeConstraint VideoAutoplayPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint VideoAutoplayPropertyInfo = (~) Bool
    type AttrTransferType VideoAutoplayPropertyInfo = Bool
    type AttrGetType VideoAutoplayPropertyInfo = Bool
    type AttrLabel VideoAutoplayPropertyInfo = "autoplay"
    type AttrOrigin VideoAutoplayPropertyInfo = Video
    attrGet = getVideoAutoplay
    attrSet = setVideoAutoplay
    attrTransfer _ v = do
        return v
    attrConstruct = constructVideoAutoplay
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Video.autoplay"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-Video.html#g:attr:autoplay"
        })
#endif

-- VVV Prop "file"
   -- Type: TInterface (Name {namespace = "Gio", name = "File"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just True,Just True)

-- | Get the value of the “@file@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' video #file
-- @
getVideoFile :: (MonadIO m, IsVideo o) => o -> m (Maybe Gio.File.File)
getVideoFile :: forall (m :: * -> *) o.
(MonadIO m, IsVideo o) =>
o -> m (Maybe File)
getVideoFile o
obj = IO (Maybe File) -> m (Maybe File)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe File) -> m (Maybe File))
-> IO (Maybe File) -> m (Maybe File)
forall a b. (a -> b) -> a -> b
$ o -> String -> (ManagedPtr File -> File) -> IO (Maybe File)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"file" ManagedPtr File -> File
Gio.File.File

-- | Set the value of the “@file@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' video [ #file 'Data.GI.Base.Attributes.:=' value ]
-- @
setVideoFile :: (MonadIO m, IsVideo o, Gio.File.IsFile a) => o -> a -> m ()
setVideoFile :: forall (m :: * -> *) o a.
(MonadIO m, IsVideo o, IsFile a) =>
o -> a -> m ()
setVideoFile o
obj a
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Maybe a -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"file" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)

-- | Construct a `GValueConstruct` with valid value for the “@file@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructVideoFile :: (IsVideo o, MIO.MonadIO m, Gio.File.IsFile a) => a -> m (GValueConstruct o)
constructVideoFile :: forall o (m :: * -> *) a.
(IsVideo o, MonadIO m, IsFile a) =>
a -> m (GValueConstruct o)
constructVideoFile a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"file" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)

-- | Set the value of the “@file@” property to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #file
-- @
clearVideoFile :: (MonadIO m, IsVideo o) => o -> m ()
clearVideoFile :: forall (m :: * -> *) o. (MonadIO m, IsVideo o) => o -> m ()
clearVideoFile o
obj = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe File -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"file" (Maybe File
forall a. Maybe a
Nothing :: Maybe Gio.File.File)

#if defined(ENABLE_OVERLOADING)
data VideoFilePropertyInfo
instance AttrInfo VideoFilePropertyInfo where
    type AttrAllowedOps VideoFilePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint VideoFilePropertyInfo = IsVideo
    type AttrSetTypeConstraint VideoFilePropertyInfo = Gio.File.IsFile
    type AttrTransferTypeConstraint VideoFilePropertyInfo = Gio.File.IsFile
    type AttrTransferType VideoFilePropertyInfo = Gio.File.File
    type AttrGetType VideoFilePropertyInfo = (Maybe Gio.File.File)
    type AttrLabel VideoFilePropertyInfo = "file"
    type AttrOrigin VideoFilePropertyInfo = Video
    attrGet = getVideoFile
    attrSet = setVideoFile
    attrTransfer _ v = do
        unsafeCastTo Gio.File.File v
    attrConstruct = constructVideoFile
    attrClear = clearVideoFile
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Video.file"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-Video.html#g:attr:file"
        })
#endif

-- VVV Prop "loop"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@loop@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' video #loop
-- @
getVideoLoop :: (MonadIO m, IsVideo o) => o -> m Bool
getVideoLoop :: forall (m :: * -> *) o. (MonadIO m, IsVideo o) => o -> m Bool
getVideoLoop o
obj = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"loop"

-- | Set the value of the “@loop@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' video [ #loop 'Data.GI.Base.Attributes.:=' value ]
-- @
setVideoLoop :: (MonadIO m, IsVideo o) => o -> Bool -> m ()
setVideoLoop :: forall (m :: * -> *) o. (MonadIO m, IsVideo o) => o -> Bool -> m ()
setVideoLoop o
obj Bool
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"loop" Bool
val

-- | Construct a `GValueConstruct` with valid value for the “@loop@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructVideoLoop :: (IsVideo o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructVideoLoop :: forall o (m :: * -> *).
(IsVideo o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructVideoLoop Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"loop" Bool
val

#if defined(ENABLE_OVERLOADING)
data VideoLoopPropertyInfo
instance AttrInfo VideoLoopPropertyInfo where
    type AttrAllowedOps VideoLoopPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint VideoLoopPropertyInfo = IsVideo
    type AttrSetTypeConstraint VideoLoopPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint VideoLoopPropertyInfo = (~) Bool
    type AttrTransferType VideoLoopPropertyInfo = Bool
    type AttrGetType VideoLoopPropertyInfo = Bool
    type AttrLabel VideoLoopPropertyInfo = "loop"
    type AttrOrigin VideoLoopPropertyInfo = Video
    attrGet = getVideoLoop
    attrSet = setVideoLoop
    attrTransfer _ v = do
        return v
    attrConstruct = constructVideoLoop
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Video.loop"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-Video.html#g:attr:loop"
        })
#endif

-- VVV Prop "media-stream"
   -- Type: TInterface (Name {namespace = "Gtk", name = "MediaStream"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just True,Just True)

-- | Get the value of the “@media-stream@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' video #mediaStream
-- @
getVideoMediaStream :: (MonadIO m, IsVideo o) => o -> m (Maybe Gtk.MediaStream.MediaStream)
getVideoMediaStream :: forall (m :: * -> *) o.
(MonadIO m, IsVideo o) =>
o -> m (Maybe MediaStream)
getVideoMediaStream o
obj = IO (Maybe MediaStream) -> m (Maybe MediaStream)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe MediaStream) -> m (Maybe MediaStream))
-> IO (Maybe MediaStream) -> m (Maybe MediaStream)
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr MediaStream -> MediaStream)
-> IO (Maybe MediaStream)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"media-stream" ManagedPtr MediaStream -> MediaStream
Gtk.MediaStream.MediaStream

-- | Set the value of the “@media-stream@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' video [ #mediaStream 'Data.GI.Base.Attributes.:=' value ]
-- @
setVideoMediaStream :: (MonadIO m, IsVideo o, Gtk.MediaStream.IsMediaStream a) => o -> a -> m ()
setVideoMediaStream :: forall (m :: * -> *) o a.
(MonadIO m, IsVideo o, IsMediaStream a) =>
o -> a -> m ()
setVideoMediaStream o
obj a
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Maybe a -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"media-stream" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)

-- | Construct a `GValueConstruct` with valid value for the “@media-stream@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructVideoMediaStream :: (IsVideo o, MIO.MonadIO m, Gtk.MediaStream.IsMediaStream a) => a -> m (GValueConstruct o)
constructVideoMediaStream :: forall o (m :: * -> *) a.
(IsVideo o, MonadIO m, IsMediaStream a) =>
a -> m (GValueConstruct o)
constructVideoMediaStream a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"media-stream" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)

-- | Set the value of the “@media-stream@” property to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #mediaStream
-- @
clearVideoMediaStream :: (MonadIO m, IsVideo o) => o -> m ()
clearVideoMediaStream :: forall (m :: * -> *) o. (MonadIO m, IsVideo o) => o -> m ()
clearVideoMediaStream o
obj = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe MediaStream -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"media-stream" (Maybe MediaStream
forall a. Maybe a
Nothing :: Maybe Gtk.MediaStream.MediaStream)

#if defined(ENABLE_OVERLOADING)
data VideoMediaStreamPropertyInfo
instance AttrInfo VideoMediaStreamPropertyInfo where
    type AttrAllowedOps VideoMediaStreamPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint VideoMediaStreamPropertyInfo = IsVideo
    type AttrSetTypeConstraint VideoMediaStreamPropertyInfo = Gtk.MediaStream.IsMediaStream
    type AttrTransferTypeConstraint VideoMediaStreamPropertyInfo = Gtk.MediaStream.IsMediaStream
    type AttrTransferType VideoMediaStreamPropertyInfo = Gtk.MediaStream.MediaStream
    type AttrGetType VideoMediaStreamPropertyInfo = (Maybe Gtk.MediaStream.MediaStream)
    type AttrLabel VideoMediaStreamPropertyInfo = "media-stream"
    type AttrOrigin VideoMediaStreamPropertyInfo = Video
    attrGet = getVideoMediaStream
    attrSet = setVideoMediaStream
    attrTransfer _ v = do
        unsafeCastTo Gtk.MediaStream.MediaStream v
    attrConstruct = constructVideoMediaStream
    attrClear = clearVideoMediaStream
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Video.mediaStream"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-Video.html#g:attr:mediaStream"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Video
type instance O.AttributeList Video = VideoAttributeList
type VideoAttributeList = ('[ '("accessibleRole", Gtk.Accessible.AccessibleAccessibleRolePropertyInfo), '("autoplay", VideoAutoplayPropertyInfo), '("canFocus", Gtk.Widget.WidgetCanFocusPropertyInfo), '("canTarget", Gtk.Widget.WidgetCanTargetPropertyInfo), '("cssClasses", Gtk.Widget.WidgetCssClassesPropertyInfo), '("cssName", Gtk.Widget.WidgetCssNamePropertyInfo), '("cursor", Gtk.Widget.WidgetCursorPropertyInfo), '("file", VideoFilePropertyInfo), '("focusOnClick", Gtk.Widget.WidgetFocusOnClickPropertyInfo), '("focusable", Gtk.Widget.WidgetFocusablePropertyInfo), '("halign", Gtk.Widget.WidgetHalignPropertyInfo), '("hasDefault", Gtk.Widget.WidgetHasDefaultPropertyInfo), '("hasFocus", Gtk.Widget.WidgetHasFocusPropertyInfo), '("hasTooltip", Gtk.Widget.WidgetHasTooltipPropertyInfo), '("heightRequest", Gtk.Widget.WidgetHeightRequestPropertyInfo), '("hexpand", Gtk.Widget.WidgetHexpandPropertyInfo), '("hexpandSet", Gtk.Widget.WidgetHexpandSetPropertyInfo), '("layoutManager", Gtk.Widget.WidgetLayoutManagerPropertyInfo), '("loop", VideoLoopPropertyInfo), '("marginBottom", Gtk.Widget.WidgetMarginBottomPropertyInfo), '("marginEnd", Gtk.Widget.WidgetMarginEndPropertyInfo), '("marginStart", Gtk.Widget.WidgetMarginStartPropertyInfo), '("marginTop", Gtk.Widget.WidgetMarginTopPropertyInfo), '("mediaStream", VideoMediaStreamPropertyInfo), '("name", Gtk.Widget.WidgetNamePropertyInfo), '("opacity", Gtk.Widget.WidgetOpacityPropertyInfo), '("overflow", Gtk.Widget.WidgetOverflowPropertyInfo), '("parent", Gtk.Widget.WidgetParentPropertyInfo), '("receivesDefault", Gtk.Widget.WidgetReceivesDefaultPropertyInfo), '("root", Gtk.Widget.WidgetRootPropertyInfo), '("scaleFactor", Gtk.Widget.WidgetScaleFactorPropertyInfo), '("sensitive", Gtk.Widget.WidgetSensitivePropertyInfo), '("tooltipMarkup", Gtk.Widget.WidgetTooltipMarkupPropertyInfo), '("tooltipText", Gtk.Widget.WidgetTooltipTextPropertyInfo), '("valign", Gtk.Widget.WidgetValignPropertyInfo), '("vexpand", Gtk.Widget.WidgetVexpandPropertyInfo), '("vexpandSet", Gtk.Widget.WidgetVexpandSetPropertyInfo), '("visible", Gtk.Widget.WidgetVisiblePropertyInfo), '("widthRequest", Gtk.Widget.WidgetWidthRequestPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
videoAutoplay :: AttrLabelProxy "autoplay"
videoAutoplay = AttrLabelProxy

videoFile :: AttrLabelProxy "file"
videoFile = AttrLabelProxy

videoLoop :: AttrLabelProxy "loop"
videoLoop = AttrLabelProxy

videoMediaStream :: AttrLabelProxy "mediaStream"
videoMediaStream = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Video = VideoSignalList
type VideoSignalList = ('[ '("destroy", Gtk.Widget.WidgetDestroySignalInfo), '("directionChanged", Gtk.Widget.WidgetDirectionChangedSignalInfo), '("hide", Gtk.Widget.WidgetHideSignalInfo), '("keynavFailed", Gtk.Widget.WidgetKeynavFailedSignalInfo), '("map", Gtk.Widget.WidgetMapSignalInfo), '("mnemonicActivate", Gtk.Widget.WidgetMnemonicActivateSignalInfo), '("moveFocus", Gtk.Widget.WidgetMoveFocusSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("queryTooltip", Gtk.Widget.WidgetQueryTooltipSignalInfo), '("realize", Gtk.Widget.WidgetRealizeSignalInfo), '("show", Gtk.Widget.WidgetShowSignalInfo), '("stateFlagsChanged", Gtk.Widget.WidgetStateFlagsChangedSignalInfo), '("unmap", Gtk.Widget.WidgetUnmapSignalInfo), '("unrealize", Gtk.Widget.WidgetUnrealizeSignalInfo)] :: [(Symbol, *)])

#endif

-- method Video::new
-- method type : Constructor
-- Args: []
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "Video" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_video_new" gtk_video_new :: 
    IO (Ptr Video)

-- | Creates a new empty @GtkVideo@.
videoNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m Video
    -- ^ __Returns:__ a new @GtkVideo@
videoNew :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m Video
videoNew  = IO Video -> m Video
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Video -> m Video) -> IO Video -> m Video
forall a b. (a -> b) -> a -> b
$ do
    Ptr Video
result <- IO (Ptr Video)
gtk_video_new
    Text -> Ptr Video -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"videoNew" Ptr Video
result
    Video
result' <- ((ManagedPtr Video -> Video) -> Ptr Video -> IO Video
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Video -> Video
Video) Ptr Video
result
    Video -> IO Video
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Video
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Video::new_for_file
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "file"
--           , argType = TInterface Name { namespace = "Gio" , name = "File" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GFile`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "Video" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_video_new_for_file" gtk_video_new_for_file :: 
    Ptr Gio.File.File ->                    -- file : TInterface (Name {namespace = "Gio", name = "File"})
    IO (Ptr Video)

-- | Creates a @GtkVideo@ to play back the given /@file@/.
videoNewForFile ::
    (B.CallStack.HasCallStack, MonadIO m, Gio.File.IsFile a) =>
    Maybe (a)
    -- ^ /@file@/: a @GFile@
    -> m Video
    -- ^ __Returns:__ a new @GtkVideo@
videoNewForFile :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFile a) =>
Maybe a -> m Video
videoNewForFile Maybe a
file = IO Video -> m Video
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Video -> m Video) -> IO Video -> m Video
forall a b. (a -> b) -> a -> b
$ do
    Ptr File
maybeFile <- case Maybe a
file of
        Maybe a
Nothing -> Ptr File -> IO (Ptr File)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr File
forall a. Ptr a
nullPtr
        Just a
jFile -> do
            Ptr File
jFile' <- a -> IO (Ptr File)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
jFile
            Ptr File -> IO (Ptr File)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr File
jFile'
    Ptr Video
result <- Ptr File -> IO (Ptr Video)
gtk_video_new_for_file Ptr File
maybeFile
    Text -> Ptr Video -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"videoNewForFile" Ptr Video
result
    Video
result' <- ((ManagedPtr Video -> Video) -> Ptr Video -> IO Video
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Video -> Video
Video) Ptr Video
result
    Maybe a -> (a -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe a
file a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    Video -> IO Video
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Video
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Video::new_for_filename
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "filename"
--           , argType = TBasicType TFileName
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "filename to play back"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "Video" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_video_new_for_filename" gtk_video_new_for_filename :: 
    CString ->                              -- filename : TBasicType TFileName
    IO (Ptr Video)

-- | Creates a @GtkVideo@ to play back the given /@filename@/.
-- 
-- This is a utility function that calls 'GI.Gtk.Objects.Video.videoNewForFile',
-- See that function for details.
videoNewForFilename ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Maybe ([Char])
    -- ^ /@filename@/: filename to play back
    -> m Video
    -- ^ __Returns:__ a new @GtkVideo@
videoNewForFilename :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Maybe String -> m Video
videoNewForFilename Maybe String
filename = IO Video -> m Video
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Video -> m Video) -> IO Video -> m Video
forall a b. (a -> b) -> a -> b
$ do
    Ptr CChar
maybeFilename <- case Maybe String
filename of
        Maybe String
Nothing -> Ptr CChar -> IO (Ptr CChar)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
nullPtr
        Just String
jFilename -> do
            Ptr CChar
jFilename' <- String -> IO (Ptr CChar)
stringToCString String
jFilename
            Ptr CChar -> IO (Ptr CChar)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
jFilename'
    Ptr Video
result <- Ptr CChar -> IO (Ptr Video)
gtk_video_new_for_filename Ptr CChar
maybeFilename
    Text -> Ptr Video -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"videoNewForFilename" Ptr Video
result
    Video
result' <- ((ManagedPtr Video -> Video) -> Ptr Video -> IO Video
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Video -> Video
Video) Ptr Video
result
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
maybeFilename
    Video -> IO Video
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Video
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Video::new_for_media_stream
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "stream"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "MediaStream" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkMediaStream`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "Video" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_video_new_for_media_stream" gtk_video_new_for_media_stream :: 
    Ptr Gtk.MediaStream.MediaStream ->      -- stream : TInterface (Name {namespace = "Gtk", name = "MediaStream"})
    IO (Ptr Video)

-- | Creates a @GtkVideo@ to play back the given /@stream@/.
videoNewForMediaStream ::
    (B.CallStack.HasCallStack, MonadIO m, Gtk.MediaStream.IsMediaStream a) =>
    Maybe (a)
    -- ^ /@stream@/: a @GtkMediaStream@
    -> m Video
    -- ^ __Returns:__ a new @GtkVideo@
videoNewForMediaStream :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsMediaStream a) =>
Maybe a -> m Video
videoNewForMediaStream Maybe a
stream = IO Video -> m Video
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Video -> m Video) -> IO Video -> m Video
forall a b. (a -> b) -> a -> b
$ do
    Ptr MediaStream
maybeStream <- case Maybe a
stream of
        Maybe a
Nothing -> Ptr MediaStream -> IO (Ptr MediaStream)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr MediaStream
forall a. Ptr a
nullPtr
        Just a
jStream -> do
            Ptr MediaStream
jStream' <- a -> IO (Ptr MediaStream)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
jStream
            Ptr MediaStream -> IO (Ptr MediaStream)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr MediaStream
jStream'
    Ptr Video
result <- Ptr MediaStream -> IO (Ptr Video)
gtk_video_new_for_media_stream Ptr MediaStream
maybeStream
    Text -> Ptr Video -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"videoNewForMediaStream" Ptr Video
result
    Video
result' <- ((ManagedPtr Video -> Video) -> Ptr Video -> IO Video
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Video -> Video
Video) Ptr Video
result
    Maybe a -> (a -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe a
stream a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    Video -> IO Video
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Video
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Video::new_for_resource
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "resource_path"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "resource path to play back"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "Video" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_video_new_for_resource" gtk_video_new_for_resource :: 
    CString ->                              -- resource_path : TBasicType TUTF8
    IO (Ptr Video)

-- | Creates a @GtkVideo@ to play back the resource at the
-- given /@resourcePath@/.
-- 
-- This is a utility function that calls 'GI.Gtk.Objects.Video.videoNewForFile'.
videoNewForResource ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Maybe (T.Text)
    -- ^ /@resourcePath@/: resource path to play back
    -> m Video
    -- ^ __Returns:__ a new @GtkVideo@
videoNewForResource :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Maybe Text -> m Video
videoNewForResource Maybe Text
resourcePath = IO Video -> m Video
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Video -> m Video) -> IO Video -> m Video
forall a b. (a -> b) -> a -> b
$ do
    Ptr CChar
maybeResourcePath <- case Maybe Text
resourcePath of
        Maybe Text
Nothing -> Ptr CChar -> IO (Ptr CChar)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
nullPtr
        Just Text
jResourcePath -> do
            Ptr CChar
jResourcePath' <- Text -> IO (Ptr CChar)
textToCString Text
jResourcePath
            Ptr CChar -> IO (Ptr CChar)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
jResourcePath'
    Ptr Video
result <- Ptr CChar -> IO (Ptr Video)
gtk_video_new_for_resource Ptr CChar
maybeResourcePath
    Text -> Ptr Video -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"videoNewForResource" Ptr Video
result
    Video
result' <- ((ManagedPtr Video -> Video) -> Ptr Video -> IO Video
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Video -> Video
Video) Ptr Video
result
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
maybeResourcePath
    Video -> IO Video
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Video
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Video::get_autoplay
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Video" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkVideo`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_video_get_autoplay" gtk_video_get_autoplay :: 
    Ptr Video ->                            -- self : TInterface (Name {namespace = "Gtk", name = "Video"})
    IO CInt

-- | Returns 'P.True' if videos have been set to loop.
videoGetAutoplay ::
    (B.CallStack.HasCallStack, MonadIO m, IsVideo a) =>
    a
    -- ^ /@self@/: a @GtkVideo@
    -> m Bool
    -- ^ __Returns:__ 'P.True' if streams should autoplay
videoGetAutoplay :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsVideo a) =>
a -> m Bool
videoGetAutoplay a
self = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Video
self' <- a -> IO (Ptr Video)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CInt
result <- Ptr Video -> IO CInt
gtk_video_get_autoplay Ptr Video
self'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data VideoGetAutoplayMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsVideo a) => O.OverloadedMethod VideoGetAutoplayMethodInfo a signature where
    overloadedMethod = videoGetAutoplay

instance O.OverloadedMethodInfo VideoGetAutoplayMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Video.videoGetAutoplay",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-Video.html#v:videoGetAutoplay"
        })


#endif

-- method Video::get_file
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Video" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkVideo`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gio" , name = "File" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_video_get_file" gtk_video_get_file :: 
    Ptr Video ->                            -- self : TInterface (Name {namespace = "Gtk", name = "Video"})
    IO (Ptr Gio.File.File)

-- | Gets the file played by /@self@/ or 'P.Nothing' if not playing back
-- a file.
videoGetFile ::
    (B.CallStack.HasCallStack, MonadIO m, IsVideo a) =>
    a
    -- ^ /@self@/: a @GtkVideo@
    -> m (Maybe Gio.File.File)
    -- ^ __Returns:__ The file played by /@self@/
videoGetFile :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsVideo a) =>
a -> m (Maybe File)
videoGetFile a
self = IO (Maybe File) -> m (Maybe File)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe File) -> m (Maybe File))
-> IO (Maybe File) -> m (Maybe File)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Video
self' <- a -> IO (Ptr Video)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr File
result <- Ptr Video -> IO (Ptr File)
gtk_video_get_file Ptr Video
self'
    Maybe File
maybeResult <- Ptr File -> (Ptr File -> IO File) -> IO (Maybe File)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr File
result ((Ptr File -> IO File) -> IO (Maybe File))
-> (Ptr File -> IO File) -> IO (Maybe File)
forall a b. (a -> b) -> a -> b
$ \Ptr File
result' -> do
        File
result'' <- ((ManagedPtr File -> File) -> Ptr File -> IO File
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr File -> File
Gio.File.File) Ptr File
result'
        File -> IO File
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return File
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Maybe File -> IO (Maybe File)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe File
maybeResult

#if defined(ENABLE_OVERLOADING)
data VideoGetFileMethodInfo
instance (signature ~ (m (Maybe Gio.File.File)), MonadIO m, IsVideo a) => O.OverloadedMethod VideoGetFileMethodInfo a signature where
    overloadedMethod = videoGetFile

instance O.OverloadedMethodInfo VideoGetFileMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Video.videoGetFile",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-Video.html#v:videoGetFile"
        })


#endif

-- method Video::get_loop
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Video" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkVideo`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_video_get_loop" gtk_video_get_loop :: 
    Ptr Video ->                            -- self : TInterface (Name {namespace = "Gtk", name = "Video"})
    IO CInt

-- | Returns 'P.True' if videos have been set to loop.
videoGetLoop ::
    (B.CallStack.HasCallStack, MonadIO m, IsVideo a) =>
    a
    -- ^ /@self@/: a @GtkVideo@
    -> m Bool
    -- ^ __Returns:__ 'P.True' if streams should loop
videoGetLoop :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsVideo a) =>
a -> m Bool
videoGetLoop a
self = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Video
self' <- a -> IO (Ptr Video)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CInt
result <- Ptr Video -> IO CInt
gtk_video_get_loop Ptr Video
self'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data VideoGetLoopMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsVideo a) => O.OverloadedMethod VideoGetLoopMethodInfo a signature where
    overloadedMethod = videoGetLoop

instance O.OverloadedMethodInfo VideoGetLoopMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Video.videoGetLoop",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-Video.html#v:videoGetLoop"
        })


#endif

-- method Video::get_media_stream
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Video" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkVideo`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "MediaStream" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_video_get_media_stream" gtk_video_get_media_stream :: 
    Ptr Video ->                            -- self : TInterface (Name {namespace = "Gtk", name = "Video"})
    IO (Ptr Gtk.MediaStream.MediaStream)

-- | Gets the media stream managed by /@self@/ or 'P.Nothing' if none.
videoGetMediaStream ::
    (B.CallStack.HasCallStack, MonadIO m, IsVideo a) =>
    a
    -- ^ /@self@/: a @GtkVideo@
    -> m (Maybe Gtk.MediaStream.MediaStream)
    -- ^ __Returns:__ The media stream managed by /@self@/
videoGetMediaStream :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsVideo a) =>
a -> m (Maybe MediaStream)
videoGetMediaStream a
self = IO (Maybe MediaStream) -> m (Maybe MediaStream)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe MediaStream) -> m (Maybe MediaStream))
-> IO (Maybe MediaStream) -> m (Maybe MediaStream)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Video
self' <- a -> IO (Ptr Video)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr MediaStream
result <- Ptr Video -> IO (Ptr MediaStream)
gtk_video_get_media_stream Ptr Video
self'
    Maybe MediaStream
maybeResult <- Ptr MediaStream
-> (Ptr MediaStream -> IO MediaStream) -> IO (Maybe MediaStream)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr MediaStream
result ((Ptr MediaStream -> IO MediaStream) -> IO (Maybe MediaStream))
-> (Ptr MediaStream -> IO MediaStream) -> IO (Maybe MediaStream)
forall a b. (a -> b) -> a -> b
$ \Ptr MediaStream
result' -> do
        MediaStream
result'' <- ((ManagedPtr MediaStream -> MediaStream)
-> Ptr MediaStream -> IO MediaStream
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr MediaStream -> MediaStream
Gtk.MediaStream.MediaStream) Ptr MediaStream
result'
        MediaStream -> IO MediaStream
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return MediaStream
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Maybe MediaStream -> IO (Maybe MediaStream)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe MediaStream
maybeResult

#if defined(ENABLE_OVERLOADING)
data VideoGetMediaStreamMethodInfo
instance (signature ~ (m (Maybe Gtk.MediaStream.MediaStream)), MonadIO m, IsVideo a) => O.OverloadedMethod VideoGetMediaStreamMethodInfo a signature where
    overloadedMethod = videoGetMediaStream

instance O.OverloadedMethodInfo VideoGetMediaStreamMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Video.videoGetMediaStream",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-Video.html#v:videoGetMediaStream"
        })


#endif

-- method Video::set_autoplay
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Video" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkVideo`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "autoplay"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "whether media streams should autoplay"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_video_set_autoplay" gtk_video_set_autoplay :: 
    Ptr Video ->                            -- self : TInterface (Name {namespace = "Gtk", name = "Video"})
    CInt ->                                 -- autoplay : TBasicType TBoolean
    IO ()

-- | Sets whether /@self@/ automatically starts playback when it
-- becomes visible or when a new file gets loaded.
videoSetAutoplay ::
    (B.CallStack.HasCallStack, MonadIO m, IsVideo a) =>
    a
    -- ^ /@self@/: a @GtkVideo@
    -> Bool
    -- ^ /@autoplay@/: whether media streams should autoplay
    -> m ()
videoSetAutoplay :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsVideo a) =>
a -> Bool -> m ()
videoSetAutoplay a
self Bool
autoplay = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Video
self' <- a -> IO (Ptr Video)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    let autoplay' :: CInt
autoplay' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
autoplay
    Ptr Video -> CInt -> IO ()
gtk_video_set_autoplay Ptr Video
self' CInt
autoplay'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data VideoSetAutoplayMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsVideo a) => O.OverloadedMethod VideoSetAutoplayMethodInfo a signature where
    overloadedMethod = videoSetAutoplay

instance O.OverloadedMethodInfo VideoSetAutoplayMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Video.videoSetAutoplay",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-Video.html#v:videoSetAutoplay"
        })


#endif

-- method Video::set_file
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Video" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkVideo`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "file"
--           , argType = TInterface Name { namespace = "Gio" , name = "File" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the file to play" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_video_set_file" gtk_video_set_file :: 
    Ptr Video ->                            -- self : TInterface (Name {namespace = "Gtk", name = "Video"})
    Ptr Gio.File.File ->                    -- file : TInterface (Name {namespace = "Gio", name = "File"})
    IO ()

-- | Makes /@self@/ play the given /@file@/.
videoSetFile ::
    (B.CallStack.HasCallStack, MonadIO m, IsVideo a, Gio.File.IsFile b) =>
    a
    -- ^ /@self@/: a @GtkVideo@
    -> Maybe (b)
    -- ^ /@file@/: the file to play
    -> m ()
videoSetFile :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsVideo a, IsFile b) =>
a -> Maybe b -> m ()
videoSetFile a
self Maybe b
file = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Video
self' <- a -> IO (Ptr Video)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr File
maybeFile <- case Maybe b
file of
        Maybe b
Nothing -> Ptr File -> IO (Ptr File)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr File
forall a. Ptr a
nullPtr
        Just b
jFile -> do
            Ptr File
jFile' <- b -> IO (Ptr File)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jFile
            Ptr File -> IO (Ptr File)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr File
jFile'
    Ptr Video -> Ptr File -> IO ()
gtk_video_set_file Ptr Video
self' Ptr File
maybeFile
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
file b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data VideoSetFileMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsVideo a, Gio.File.IsFile b) => O.OverloadedMethod VideoSetFileMethodInfo a signature where
    overloadedMethod = videoSetFile

instance O.OverloadedMethodInfo VideoSetFileMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Video.videoSetFile",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-Video.html#v:videoSetFile"
        })


#endif

-- method Video::set_filename
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Video" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkVideo`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "filename"
--           , argType = TBasicType TFileName
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the filename to play"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_video_set_filename" gtk_video_set_filename :: 
    Ptr Video ->                            -- self : TInterface (Name {namespace = "Gtk", name = "Video"})
    CString ->                              -- filename : TBasicType TFileName
    IO ()

-- | Makes /@self@/ play the given /@filename@/.
-- 
-- This is a utility function that calls 'GI.Gtk.Objects.Video.videoSetFile',
videoSetFilename ::
    (B.CallStack.HasCallStack, MonadIO m, IsVideo a) =>
    a
    -- ^ /@self@/: a @GtkVideo@
    -> Maybe ([Char])
    -- ^ /@filename@/: the filename to play
    -> m ()
videoSetFilename :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsVideo a) =>
a -> Maybe String -> m ()
videoSetFilename a
self Maybe String
filename = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Video
self' <- a -> IO (Ptr Video)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr CChar
maybeFilename <- case Maybe String
filename of
        Maybe String
Nothing -> Ptr CChar -> IO (Ptr CChar)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
nullPtr
        Just String
jFilename -> do
            Ptr CChar
jFilename' <- String -> IO (Ptr CChar)
stringToCString String
jFilename
            Ptr CChar -> IO (Ptr CChar)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
jFilename'
    Ptr Video -> Ptr CChar -> IO ()
gtk_video_set_filename Ptr Video
self' Ptr CChar
maybeFilename
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
maybeFilename
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data VideoSetFilenameMethodInfo
instance (signature ~ (Maybe ([Char]) -> m ()), MonadIO m, IsVideo a) => O.OverloadedMethod VideoSetFilenameMethodInfo a signature where
    overloadedMethod = videoSetFilename

instance O.OverloadedMethodInfo VideoSetFilenameMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Video.videoSetFilename",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-Video.html#v:videoSetFilename"
        })


#endif

-- method Video::set_loop
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Video" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkVideo`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "loop"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "whether media streams should loop"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_video_set_loop" gtk_video_set_loop :: 
    Ptr Video ->                            -- self : TInterface (Name {namespace = "Gtk", name = "Video"})
    CInt ->                                 -- loop : TBasicType TBoolean
    IO ()

-- | Sets whether new files loaded by /@self@/ should be set to loop.
videoSetLoop ::
    (B.CallStack.HasCallStack, MonadIO m, IsVideo a) =>
    a
    -- ^ /@self@/: a @GtkVideo@
    -> Bool
    -- ^ /@loop@/: whether media streams should loop
    -> m ()
videoSetLoop :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsVideo a) =>
a -> Bool -> m ()
videoSetLoop a
self Bool
loop = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Video
self' <- a -> IO (Ptr Video)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    let loop' :: CInt
loop' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
loop
    Ptr Video -> CInt -> IO ()
gtk_video_set_loop Ptr Video
self' CInt
loop'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data VideoSetLoopMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsVideo a) => O.OverloadedMethod VideoSetLoopMethodInfo a signature where
    overloadedMethod = videoSetLoop

instance O.OverloadedMethodInfo VideoSetLoopMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Video.videoSetLoop",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-Video.html#v:videoSetLoop"
        })


#endif

-- method Video::set_media_stream
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Video" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkVideo`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "stream"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "MediaStream" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The media stream to play or %NULL to unset"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_video_set_media_stream" gtk_video_set_media_stream :: 
    Ptr Video ->                            -- self : TInterface (Name {namespace = "Gtk", name = "Video"})
    Ptr Gtk.MediaStream.MediaStream ->      -- stream : TInterface (Name {namespace = "Gtk", name = "MediaStream"})
    IO ()

-- | Sets the media stream to be played back.
-- 
-- /@self@/ will take full control of managing the media stream. If you
-- want to manage a media stream yourself, consider using a
-- t'GI.Gtk.Objects.Picture.Picture' for display.
-- 
-- If you want to display a file, consider using 'GI.Gtk.Objects.Video.videoSetFile'
-- instead.
videoSetMediaStream ::
    (B.CallStack.HasCallStack, MonadIO m, IsVideo a, Gtk.MediaStream.IsMediaStream b) =>
    a
    -- ^ /@self@/: a @GtkVideo@
    -> Maybe (b)
    -- ^ /@stream@/: The media stream to play or 'P.Nothing' to unset
    -> m ()
videoSetMediaStream :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsVideo a, IsMediaStream b) =>
a -> Maybe b -> m ()
videoSetMediaStream a
self Maybe b
stream = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Video
self' <- a -> IO (Ptr Video)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr MediaStream
maybeStream <- case Maybe b
stream of
        Maybe b
Nothing -> Ptr MediaStream -> IO (Ptr MediaStream)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr MediaStream
forall a. Ptr a
nullPtr
        Just b
jStream -> do
            Ptr MediaStream
jStream' <- b -> IO (Ptr MediaStream)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jStream
            Ptr MediaStream -> IO (Ptr MediaStream)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr MediaStream
jStream'
    Ptr Video -> Ptr MediaStream -> IO ()
gtk_video_set_media_stream Ptr Video
self' Ptr MediaStream
maybeStream
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
stream b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data VideoSetMediaStreamMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsVideo a, Gtk.MediaStream.IsMediaStream b) => O.OverloadedMethod VideoSetMediaStreamMethodInfo a signature where
    overloadedMethod = videoSetMediaStream

instance O.OverloadedMethodInfo VideoSetMediaStreamMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Video.videoSetMediaStream",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-Video.html#v:videoSetMediaStream"
        })


#endif

-- method Video::set_resource
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Video" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkVideo`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "resource_path"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the resource to set"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_video_set_resource" gtk_video_set_resource :: 
    Ptr Video ->                            -- self : TInterface (Name {namespace = "Gtk", name = "Video"})
    CString ->                              -- resource_path : TBasicType TUTF8
    IO ()

-- | Makes /@self@/ play the resource at the given /@resourcePath@/.
-- 
-- This is a utility function that calls 'GI.Gtk.Objects.Video.videoSetFile'.
videoSetResource ::
    (B.CallStack.HasCallStack, MonadIO m, IsVideo a) =>
    a
    -- ^ /@self@/: a @GtkVideo@
    -> Maybe (T.Text)
    -- ^ /@resourcePath@/: the resource to set
    -> m ()
videoSetResource :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsVideo a) =>
a -> Maybe Text -> m ()
videoSetResource a
self Maybe Text
resourcePath = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Video
self' <- a -> IO (Ptr Video)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr CChar
maybeResourcePath <- case Maybe Text
resourcePath of
        Maybe Text
Nothing -> Ptr CChar -> IO (Ptr CChar)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
nullPtr
        Just Text
jResourcePath -> do
            Ptr CChar
jResourcePath' <- Text -> IO (Ptr CChar)
textToCString Text
jResourcePath
            Ptr CChar -> IO (Ptr CChar)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
jResourcePath'
    Ptr Video -> Ptr CChar -> IO ()
gtk_video_set_resource Ptr Video
self' Ptr CChar
maybeResourcePath
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
maybeResourcePath
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data VideoSetResourceMethodInfo
instance (signature ~ (Maybe (T.Text) -> m ()), MonadIO m, IsVideo a) => O.OverloadedMethod VideoSetResourceMethodInfo a signature where
    overloadedMethod = videoSetResource

instance O.OverloadedMethodInfo VideoSetResourceMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Video.videoSetResource",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-Video.html#v:videoSetResource"
        })


#endif