{-# LANGUAGE ImplicitParams, RankNTypes, TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- t'GI.Clutter.Interfaces.Media.Media' is an opaque structure whose members cannot be directly
-- accessed
-- 
-- /Since: 0.2/

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

module GI.Clutter.Interfaces.Media
    ( 

-- * Exported types
    Media(..)                               ,
    IsMedia                                 ,
    toMedia                                 ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getAudioVolume]("GI.Clutter.Interfaces.Media#g:method:getAudioVolume"), [getBufferFill]("GI.Clutter.Interfaces.Media#g:method:getBufferFill"), [getCanSeek]("GI.Clutter.Interfaces.Media#g:method:getCanSeek"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getDuration]("GI.Clutter.Interfaces.Media#g:method:getDuration"), [getPlaying]("GI.Clutter.Interfaces.Media#g:method:getPlaying"), [getProgress]("GI.Clutter.Interfaces.Media#g:method:getProgress"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getSubtitleFontName]("GI.Clutter.Interfaces.Media#g:method:getSubtitleFontName"), [getSubtitleUri]("GI.Clutter.Interfaces.Media#g:method:getSubtitleUri"), [getUri]("GI.Clutter.Interfaces.Media#g:method:getUri").
-- 
-- ==== Setters
-- [setAudioVolume]("GI.Clutter.Interfaces.Media#g:method:setAudioVolume"), [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setFilename]("GI.Clutter.Interfaces.Media#g:method:setFilename"), [setPlaying]("GI.Clutter.Interfaces.Media#g:method:setPlaying"), [setProgress]("GI.Clutter.Interfaces.Media#g:method:setProgress"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setSubtitleFontName]("GI.Clutter.Interfaces.Media#g:method:setSubtitleFontName"), [setSubtitleUri]("GI.Clutter.Interfaces.Media#g:method:setSubtitleUri"), [setUri]("GI.Clutter.Interfaces.Media#g:method:setUri").

#if defined(ENABLE_OVERLOADING)
    ResolveMediaMethod                      ,
#endif

-- ** getAudioVolume #method:getAudioVolume#

#if defined(ENABLE_OVERLOADING)
    MediaGetAudioVolumeMethodInfo           ,
#endif
    mediaGetAudioVolume                     ,


-- ** getBufferFill #method:getBufferFill#

#if defined(ENABLE_OVERLOADING)
    MediaGetBufferFillMethodInfo            ,
#endif
    mediaGetBufferFill                      ,


-- ** getCanSeek #method:getCanSeek#

#if defined(ENABLE_OVERLOADING)
    MediaGetCanSeekMethodInfo               ,
#endif
    mediaGetCanSeek                         ,


-- ** getDuration #method:getDuration#

#if defined(ENABLE_OVERLOADING)
    MediaGetDurationMethodInfo              ,
#endif
    mediaGetDuration                        ,


-- ** getPlaying #method:getPlaying#

#if defined(ENABLE_OVERLOADING)
    MediaGetPlayingMethodInfo               ,
#endif
    mediaGetPlaying                         ,


-- ** getProgress #method:getProgress#

#if defined(ENABLE_OVERLOADING)
    MediaGetProgressMethodInfo              ,
#endif
    mediaGetProgress                        ,


-- ** getSubtitleFontName #method:getSubtitleFontName#

#if defined(ENABLE_OVERLOADING)
    MediaGetSubtitleFontNameMethodInfo      ,
#endif
    mediaGetSubtitleFontName                ,


-- ** getSubtitleUri #method:getSubtitleUri#

#if defined(ENABLE_OVERLOADING)
    MediaGetSubtitleUriMethodInfo           ,
#endif
    mediaGetSubtitleUri                     ,


-- ** getUri #method:getUri#

#if defined(ENABLE_OVERLOADING)
    MediaGetUriMethodInfo                   ,
#endif
    mediaGetUri                             ,


-- ** setAudioVolume #method:setAudioVolume#

#if defined(ENABLE_OVERLOADING)
    MediaSetAudioVolumeMethodInfo           ,
#endif
    mediaSetAudioVolume                     ,


-- ** setFilename #method:setFilename#

#if defined(ENABLE_OVERLOADING)
    MediaSetFilenameMethodInfo              ,
#endif
    mediaSetFilename                        ,


-- ** setPlaying #method:setPlaying#

#if defined(ENABLE_OVERLOADING)
    MediaSetPlayingMethodInfo               ,
#endif
    mediaSetPlaying                         ,


-- ** setProgress #method:setProgress#

#if defined(ENABLE_OVERLOADING)
    MediaSetProgressMethodInfo              ,
#endif
    mediaSetProgress                        ,


-- ** setSubtitleFontName #method:setSubtitleFontName#

#if defined(ENABLE_OVERLOADING)
    MediaSetSubtitleFontNameMethodInfo      ,
#endif
    mediaSetSubtitleFontName                ,


-- ** setSubtitleUri #method:setSubtitleUri#

#if defined(ENABLE_OVERLOADING)
    MediaSetSubtitleUriMethodInfo           ,
#endif
    mediaSetSubtitleUri                     ,


-- ** setUri #method:setUri#

#if defined(ENABLE_OVERLOADING)
    MediaSetUriMethodInfo                   ,
#endif
    mediaSetUri                             ,




 -- * Properties


-- ** audioVolume #attr:audioVolume#
-- | The volume of the audio, as a normalized value between
-- 0.0 and 1.0.
-- 
-- /Since: 1.0/

#if defined(ENABLE_OVERLOADING)
    MediaAudioVolumePropertyInfo            ,
#endif
    constructMediaAudioVolume               ,
    getMediaAudioVolume                     ,
#if defined(ENABLE_OVERLOADING)
    mediaAudioVolume                        ,
#endif
    setMediaAudioVolume                     ,


-- ** bufferFill #attr:bufferFill#
-- | The fill level of the buffer for the current stream,
-- as a value between 0.0 and 1.0.
-- 
-- /Since: 1.0/

#if defined(ENABLE_OVERLOADING)
    MediaBufferFillPropertyInfo             ,
#endif
    getMediaBufferFill                      ,
#if defined(ENABLE_OVERLOADING)
    mediaBufferFill                         ,
#endif


-- ** canSeek #attr:canSeek#
-- | Whether the current stream is seekable.
-- 
-- /Since: 0.2/

#if defined(ENABLE_OVERLOADING)
    MediaCanSeekPropertyInfo                ,
#endif
    getMediaCanSeek                         ,
#if defined(ENABLE_OVERLOADING)
    mediaCanSeek                            ,
#endif


-- ** duration #attr:duration#
-- | The duration of the current stream, in seconds
-- 
-- /Since: 0.2/

#if defined(ENABLE_OVERLOADING)
    MediaDurationPropertyInfo               ,
#endif
    getMediaDuration                        ,
#if defined(ENABLE_OVERLOADING)
    mediaDuration                           ,
#endif


-- ** playing #attr:playing#
-- | Whether the t'GI.Clutter.Interfaces.Media.Media' actor is playing.
-- 
-- /Since: 0.2/

#if defined(ENABLE_OVERLOADING)
    MediaPlayingPropertyInfo                ,
#endif
    constructMediaPlaying                   ,
    getMediaPlaying                         ,
#if defined(ENABLE_OVERLOADING)
    mediaPlaying                            ,
#endif
    setMediaPlaying                         ,


-- ** progress #attr:progress#
-- | The current progress of the playback, as a normalized
-- value between 0.0 and 1.0.
-- 
-- /Since: 1.0/

#if defined(ENABLE_OVERLOADING)
    MediaProgressPropertyInfo               ,
#endif
    constructMediaProgress                  ,
    getMediaProgress                        ,
#if defined(ENABLE_OVERLOADING)
    mediaProgress                           ,
#endif
    setMediaProgress                        ,


-- ** subtitleFontName #attr:subtitleFontName#
-- | The font used to display subtitles. The font description has to
-- follow the same grammar as the one recognized by
-- 'GI.Pango.Functions.fontDescriptionFromString'.
-- 
-- /Since: 1.2/

#if defined(ENABLE_OVERLOADING)
    MediaSubtitleFontNamePropertyInfo       ,
#endif
    constructMediaSubtitleFontName          ,
    getMediaSubtitleFontName                ,
#if defined(ENABLE_OVERLOADING)
    mediaSubtitleFontName                   ,
#endif
    setMediaSubtitleFontName                ,


-- ** subtitleUri #attr:subtitleUri#
-- | The location of a subtitle file, expressed as a valid URI.
-- 
-- /Since: 1.2/

#if defined(ENABLE_OVERLOADING)
    MediaSubtitleUriPropertyInfo            ,
#endif
    constructMediaSubtitleUri               ,
    getMediaSubtitleUri                     ,
#if defined(ENABLE_OVERLOADING)
    mediaSubtitleUri                        ,
#endif
    setMediaSubtitleUri                     ,


-- ** uri #attr:uri#
-- | The location of a media file, expressed as a valid URI.
-- 
-- /Since: 0.2/

#if defined(ENABLE_OVERLOADING)
    MediaUriPropertyInfo                    ,
#endif
    constructMediaUri                       ,
    getMediaUri                             ,
#if defined(ENABLE_OVERLOADING)
    mediaUri                                ,
#endif
    setMediaUri                             ,




 -- * Signals


-- ** eos #signal:eos#

    MediaEosCallback                        ,
#if defined(ENABLE_OVERLOADING)
    MediaEosSignalInfo                      ,
#endif
    afterMediaEos                           ,
    onMediaEos                              ,


-- ** error #signal:error#

    MediaErrorCallback                      ,
#if defined(ENABLE_OVERLOADING)
    MediaErrorSignalInfo                    ,
#endif
    afterMediaError                         ,
    onMediaError                            ,




    ) 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.Kind as DK
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

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

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

foreign import ccall "clutter_media_get_type"
    c_clutter_media_get_type :: IO B.Types.GType

instance B.Types.TypedObject Media where
    glibType :: IO GType
glibType = IO GType
c_clutter_media_get_type

instance B.Types.GObject Media

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

instance O.HasParentTypes Media
type instance O.ParentTypes Media = '[GObject.Object.Object]

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

-- | Convert 'Media' 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 Media) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_clutter_media_get_type
    gvalueSet_ :: Ptr GValue -> Maybe Media -> IO ()
gvalueSet_ Ptr GValue
gv Maybe Media
P.Nothing = Ptr GValue -> Ptr Media -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr Media
forall a. Ptr a
FP.nullPtr :: FP.Ptr Media)
    gvalueSet_ Ptr GValue
gv (P.Just Media
obj) = Media -> (Ptr Media -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Media
obj (Ptr GValue -> Ptr Media -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe Media)
gvalueGet_ Ptr GValue
gv = do
        Ptr Media
ptr <- Ptr GValue -> IO (Ptr Media)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr Media)
        if Ptr Media
ptr Ptr Media -> Ptr Media -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr Media
forall a. Ptr a
FP.nullPtr
        then Media -> Maybe Media
forall a. a -> Maybe a
P.Just (Media -> Maybe Media) -> IO Media -> IO (Maybe Media)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr Media -> Media) -> Ptr Media -> IO Media
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr Media -> Media
Media Ptr Media
ptr
        else Maybe Media -> IO (Maybe Media)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Media
forall a. Maybe a
P.Nothing
        
    

-- VVV Prop "audio-volume"
   -- Type: TBasicType TDouble
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

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

-- | Set the value of the “@audio-volume@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' media [ #audioVolume 'Data.GI.Base.Attributes.:=' value ]
-- @
setMediaAudioVolume :: (MonadIO m, IsMedia o) => o -> Double -> m ()
setMediaAudioVolume :: forall (m :: * -> *) o.
(MonadIO m, IsMedia o) =>
o -> Double -> m ()
setMediaAudioVolume o
obj Double
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 -> Double -> IO ()
forall a. GObject a => a -> String -> Double -> IO ()
B.Properties.setObjectPropertyDouble o
obj String
"audio-volume" Double
val

-- | Construct a `GValueConstruct` with valid value for the “@audio-volume@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructMediaAudioVolume :: (IsMedia o, MIO.MonadIO m) => Double -> m (GValueConstruct o)
constructMediaAudioVolume :: forall o (m :: * -> *).
(IsMedia o, MonadIO m) =>
Double -> m (GValueConstruct o)
constructMediaAudioVolume Double
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 -> Double -> IO (GValueConstruct o)
forall o. String -> Double -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyDouble String
"audio-volume" Double
val

#if defined(ENABLE_OVERLOADING)
data MediaAudioVolumePropertyInfo
instance AttrInfo MediaAudioVolumePropertyInfo where
    type AttrAllowedOps MediaAudioVolumePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint MediaAudioVolumePropertyInfo = IsMedia
    type AttrSetTypeConstraint MediaAudioVolumePropertyInfo = (~) Double
    type AttrTransferTypeConstraint MediaAudioVolumePropertyInfo = (~) Double
    type AttrTransferType MediaAudioVolumePropertyInfo = Double
    type AttrGetType MediaAudioVolumePropertyInfo = Double
    type AttrLabel MediaAudioVolumePropertyInfo = "audio-volume"
    type AttrOrigin MediaAudioVolumePropertyInfo = Media
    attrGet = getMediaAudioVolume
    attrSet = setMediaAudioVolume
    attrTransfer _ v = do
        return v
    attrConstruct = constructMediaAudioVolume
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Interfaces.Media.audioVolume"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.5/docs/GI-Clutter-Interfaces-Media.html#g:attr:audioVolume"
        })
#endif

-- VVV Prop "buffer-fill"
   -- Type: TBasicType TDouble
   -- Flags: [PropertyReadable]
   -- Nullable: (Just False,Nothing)

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

#if defined(ENABLE_OVERLOADING)
data MediaBufferFillPropertyInfo
instance AttrInfo MediaBufferFillPropertyInfo where
    type AttrAllowedOps MediaBufferFillPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint MediaBufferFillPropertyInfo = IsMedia
    type AttrSetTypeConstraint MediaBufferFillPropertyInfo = (~) ()
    type AttrTransferTypeConstraint MediaBufferFillPropertyInfo = (~) ()
    type AttrTransferType MediaBufferFillPropertyInfo = ()
    type AttrGetType MediaBufferFillPropertyInfo = Double
    type AttrLabel MediaBufferFillPropertyInfo = "buffer-fill"
    type AttrOrigin MediaBufferFillPropertyInfo = Media
    attrGet = getMediaBufferFill
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Interfaces.Media.bufferFill"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.5/docs/GI-Clutter-Interfaces-Media.html#g:attr:bufferFill"
        })
#endif

-- VVV Prop "can-seek"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@can-seek@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' media #canSeek
-- @
getMediaCanSeek :: (MonadIO m, IsMedia o) => o -> m Bool
getMediaCanSeek :: forall (m :: * -> *) o. (MonadIO m, IsMedia o) => o -> m Bool
getMediaCanSeek 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
"can-seek"

#if defined(ENABLE_OVERLOADING)
data MediaCanSeekPropertyInfo
instance AttrInfo MediaCanSeekPropertyInfo where
    type AttrAllowedOps MediaCanSeekPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint MediaCanSeekPropertyInfo = IsMedia
    type AttrSetTypeConstraint MediaCanSeekPropertyInfo = (~) ()
    type AttrTransferTypeConstraint MediaCanSeekPropertyInfo = (~) ()
    type AttrTransferType MediaCanSeekPropertyInfo = ()
    type AttrGetType MediaCanSeekPropertyInfo = Bool
    type AttrLabel MediaCanSeekPropertyInfo = "can-seek"
    type AttrOrigin MediaCanSeekPropertyInfo = Media
    attrGet = getMediaCanSeek
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Interfaces.Media.canSeek"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.5/docs/GI-Clutter-Interfaces-Media.html#g:attr:canSeek"
        })
#endif

-- VVV Prop "duration"
   -- Type: TBasicType TDouble
   -- Flags: [PropertyReadable]
   -- Nullable: (Just False,Nothing)

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

#if defined(ENABLE_OVERLOADING)
data MediaDurationPropertyInfo
instance AttrInfo MediaDurationPropertyInfo where
    type AttrAllowedOps MediaDurationPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint MediaDurationPropertyInfo = IsMedia
    type AttrSetTypeConstraint MediaDurationPropertyInfo = (~) ()
    type AttrTransferTypeConstraint MediaDurationPropertyInfo = (~) ()
    type AttrTransferType MediaDurationPropertyInfo = ()
    type AttrGetType MediaDurationPropertyInfo = Double
    type AttrLabel MediaDurationPropertyInfo = "duration"
    type AttrOrigin MediaDurationPropertyInfo = Media
    attrGet = getMediaDuration
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Interfaces.Media.duration"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.5/docs/GI-Clutter-Interfaces-Media.html#g:attr:duration"
        })
#endif

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

-- | Get the value of the “@playing@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' media #playing
-- @
getMediaPlaying :: (MonadIO m, IsMedia o) => o -> m Bool
getMediaPlaying :: forall (m :: * -> *) o. (MonadIO m, IsMedia o) => o -> m Bool
getMediaPlaying 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
"playing"

-- | Set the value of the “@playing@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' media [ #playing 'Data.GI.Base.Attributes.:=' value ]
-- @
setMediaPlaying :: (MonadIO m, IsMedia o) => o -> Bool -> m ()
setMediaPlaying :: forall (m :: * -> *) o. (MonadIO m, IsMedia o) => o -> Bool -> m ()
setMediaPlaying 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
"playing" Bool
val

-- | Construct a `GValueConstruct` with valid value for the “@playing@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructMediaPlaying :: (IsMedia o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructMediaPlaying :: forall o (m :: * -> *).
(IsMedia o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructMediaPlaying 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
"playing" Bool
val

#if defined(ENABLE_OVERLOADING)
data MediaPlayingPropertyInfo
instance AttrInfo MediaPlayingPropertyInfo where
    type AttrAllowedOps MediaPlayingPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint MediaPlayingPropertyInfo = IsMedia
    type AttrSetTypeConstraint MediaPlayingPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint MediaPlayingPropertyInfo = (~) Bool
    type AttrTransferType MediaPlayingPropertyInfo = Bool
    type AttrGetType MediaPlayingPropertyInfo = Bool
    type AttrLabel MediaPlayingPropertyInfo = "playing"
    type AttrOrigin MediaPlayingPropertyInfo = Media
    attrGet = getMediaPlaying
    attrSet = setMediaPlaying
    attrTransfer _ v = do
        return v
    attrConstruct = constructMediaPlaying
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Interfaces.Media.playing"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.5/docs/GI-Clutter-Interfaces-Media.html#g:attr:playing"
        })
#endif

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

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

-- | Set the value of the “@progress@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' media [ #progress 'Data.GI.Base.Attributes.:=' value ]
-- @
setMediaProgress :: (MonadIO m, IsMedia o) => o -> Double -> m ()
setMediaProgress :: forall (m :: * -> *) o.
(MonadIO m, IsMedia o) =>
o -> Double -> m ()
setMediaProgress o
obj Double
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 -> Double -> IO ()
forall a. GObject a => a -> String -> Double -> IO ()
B.Properties.setObjectPropertyDouble o
obj String
"progress" Double
val

-- | Construct a `GValueConstruct` with valid value for the “@progress@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructMediaProgress :: (IsMedia o, MIO.MonadIO m) => Double -> m (GValueConstruct o)
constructMediaProgress :: forall o (m :: * -> *).
(IsMedia o, MonadIO m) =>
Double -> m (GValueConstruct o)
constructMediaProgress Double
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 -> Double -> IO (GValueConstruct o)
forall o. String -> Double -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyDouble String
"progress" Double
val

#if defined(ENABLE_OVERLOADING)
data MediaProgressPropertyInfo
instance AttrInfo MediaProgressPropertyInfo where
    type AttrAllowedOps MediaProgressPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint MediaProgressPropertyInfo = IsMedia
    type AttrSetTypeConstraint MediaProgressPropertyInfo = (~) Double
    type AttrTransferTypeConstraint MediaProgressPropertyInfo = (~) Double
    type AttrTransferType MediaProgressPropertyInfo = Double
    type AttrGetType MediaProgressPropertyInfo = Double
    type AttrLabel MediaProgressPropertyInfo = "progress"
    type AttrOrigin MediaProgressPropertyInfo = Media
    attrGet = getMediaProgress
    attrSet = setMediaProgress
    attrTransfer _ v = do
        return v
    attrConstruct = constructMediaProgress
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Interfaces.Media.progress"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.5/docs/GI-Clutter-Interfaces-Media.html#g:attr:progress"
        })
#endif

-- VVV Prop "subtitle-font-name"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Just False)

-- | Get the value of the “@subtitle-font-name@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' media #subtitleFontName
-- @
getMediaSubtitleFontName :: (MonadIO m, IsMedia o) => o -> m (Maybe T.Text)
getMediaSubtitleFontName :: forall (m :: * -> *) o.
(MonadIO m, IsMedia o) =>
o -> m (Maybe Text)
getMediaSubtitleFontName o
obj = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"subtitle-font-name"

-- | Set the value of the “@subtitle-font-name@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' media [ #subtitleFontName 'Data.GI.Base.Attributes.:=' value ]
-- @
setMediaSubtitleFontName :: (MonadIO m, IsMedia o) => o -> T.Text -> m ()
setMediaSubtitleFontName :: forall (m :: * -> *) o. (MonadIO m, IsMedia o) => o -> Text -> m ()
setMediaSubtitleFontName o
obj Text
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 Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"subtitle-font-name" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Construct a `GValueConstruct` with valid value for the “@subtitle-font-name@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructMediaSubtitleFontName :: (IsMedia o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructMediaSubtitleFontName :: forall o (m :: * -> *).
(IsMedia o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructMediaSubtitleFontName Text
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 Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"subtitle-font-name" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

#if defined(ENABLE_OVERLOADING)
data MediaSubtitleFontNamePropertyInfo
instance AttrInfo MediaSubtitleFontNamePropertyInfo where
    type AttrAllowedOps MediaSubtitleFontNamePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint MediaSubtitleFontNamePropertyInfo = IsMedia
    type AttrSetTypeConstraint MediaSubtitleFontNamePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint MediaSubtitleFontNamePropertyInfo = (~) T.Text
    type AttrTransferType MediaSubtitleFontNamePropertyInfo = T.Text
    type AttrGetType MediaSubtitleFontNamePropertyInfo = (Maybe T.Text)
    type AttrLabel MediaSubtitleFontNamePropertyInfo = "subtitle-font-name"
    type AttrOrigin MediaSubtitleFontNamePropertyInfo = Media
    attrGet = getMediaSubtitleFontName
    attrSet = setMediaSubtitleFontName
    attrTransfer _ v = do
        return v
    attrConstruct = constructMediaSubtitleFontName
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Interfaces.Media.subtitleFontName"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.5/docs/GI-Clutter-Interfaces-Media.html#g:attr:subtitleFontName"
        })
#endif

-- VVV Prop "subtitle-uri"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Just False)

-- | Get the value of the “@subtitle-uri@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' media #subtitleUri
-- @
getMediaSubtitleUri :: (MonadIO m, IsMedia o) => o -> m (Maybe T.Text)
getMediaSubtitleUri :: forall (m :: * -> *) o.
(MonadIO m, IsMedia o) =>
o -> m (Maybe Text)
getMediaSubtitleUri o
obj = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"subtitle-uri"

-- | Set the value of the “@subtitle-uri@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' media [ #subtitleUri 'Data.GI.Base.Attributes.:=' value ]
-- @
setMediaSubtitleUri :: (MonadIO m, IsMedia o) => o -> T.Text -> m ()
setMediaSubtitleUri :: forall (m :: * -> *) o. (MonadIO m, IsMedia o) => o -> Text -> m ()
setMediaSubtitleUri o
obj Text
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 Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"subtitle-uri" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Construct a `GValueConstruct` with valid value for the “@subtitle-uri@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructMediaSubtitleUri :: (IsMedia o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructMediaSubtitleUri :: forall o (m :: * -> *).
(IsMedia o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructMediaSubtitleUri Text
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 Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"subtitle-uri" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

#if defined(ENABLE_OVERLOADING)
data MediaSubtitleUriPropertyInfo
instance AttrInfo MediaSubtitleUriPropertyInfo where
    type AttrAllowedOps MediaSubtitleUriPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint MediaSubtitleUriPropertyInfo = IsMedia
    type AttrSetTypeConstraint MediaSubtitleUriPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint MediaSubtitleUriPropertyInfo = (~) T.Text
    type AttrTransferType MediaSubtitleUriPropertyInfo = T.Text
    type AttrGetType MediaSubtitleUriPropertyInfo = (Maybe T.Text)
    type AttrLabel MediaSubtitleUriPropertyInfo = "subtitle-uri"
    type AttrOrigin MediaSubtitleUriPropertyInfo = Media
    attrGet = getMediaSubtitleUri
    attrSet = setMediaSubtitleUri
    attrTransfer _ v = do
        return v
    attrConstruct = constructMediaSubtitleUri
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Interfaces.Media.subtitleUri"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.5/docs/GI-Clutter-Interfaces-Media.html#g:attr:subtitleUri"
        })
#endif

-- VVV Prop "uri"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Just False)

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

-- | Set the value of the “@uri@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' media [ #uri 'Data.GI.Base.Attributes.:=' value ]
-- @
setMediaUri :: (MonadIO m, IsMedia o) => o -> T.Text -> m ()
setMediaUri :: forall (m :: * -> *) o. (MonadIO m, IsMedia o) => o -> Text -> m ()
setMediaUri o
obj Text
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 Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"uri" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Construct a `GValueConstruct` with valid value for the “@uri@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructMediaUri :: (IsMedia o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructMediaUri :: forall o (m :: * -> *).
(IsMedia o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructMediaUri Text
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 Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"uri" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

#if defined(ENABLE_OVERLOADING)
data MediaUriPropertyInfo
instance AttrInfo MediaUriPropertyInfo where
    type AttrAllowedOps MediaUriPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint MediaUriPropertyInfo = IsMedia
    type AttrSetTypeConstraint MediaUriPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint MediaUriPropertyInfo = (~) T.Text
    type AttrTransferType MediaUriPropertyInfo = T.Text
    type AttrGetType MediaUriPropertyInfo = (Maybe T.Text)
    type AttrLabel MediaUriPropertyInfo = "uri"
    type AttrOrigin MediaUriPropertyInfo = Media
    attrGet = getMediaUri
    attrSet = setMediaUri
    attrTransfer _ v = do
        return v
    attrConstruct = constructMediaUri
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Interfaces.Media.uri"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.5/docs/GI-Clutter-Interfaces-Media.html#g:attr:uri"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Media
type instance O.AttributeList Media = MediaAttributeList
type MediaAttributeList = ('[ '("audioVolume", MediaAudioVolumePropertyInfo), '("bufferFill", MediaBufferFillPropertyInfo), '("canSeek", MediaCanSeekPropertyInfo), '("duration", MediaDurationPropertyInfo), '("playing", MediaPlayingPropertyInfo), '("progress", MediaProgressPropertyInfo), '("subtitleFontName", MediaSubtitleFontNamePropertyInfo), '("subtitleUri", MediaSubtitleUriPropertyInfo), '("uri", MediaUriPropertyInfo)] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
mediaAudioVolume :: AttrLabelProxy "audioVolume"
mediaAudioVolume = AttrLabelProxy

mediaBufferFill :: AttrLabelProxy "bufferFill"
mediaBufferFill = AttrLabelProxy

mediaCanSeek :: AttrLabelProxy "canSeek"
mediaCanSeek = AttrLabelProxy

mediaDuration :: AttrLabelProxy "duration"
mediaDuration = AttrLabelProxy

mediaPlaying :: AttrLabelProxy "playing"
mediaPlaying = AttrLabelProxy

mediaProgress :: AttrLabelProxy "progress"
mediaProgress = AttrLabelProxy

mediaSubtitleFontName :: AttrLabelProxy "subtitleFontName"
mediaSubtitleFontName = AttrLabelProxy

mediaSubtitleUri :: AttrLabelProxy "subtitleUri"
mediaSubtitleUri = AttrLabelProxy

mediaUri :: AttrLabelProxy "uri"
mediaUri = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveMediaMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveMediaMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveMediaMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveMediaMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveMediaMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveMediaMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveMediaMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveMediaMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveMediaMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveMediaMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveMediaMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveMediaMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveMediaMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveMediaMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveMediaMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveMediaMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveMediaMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveMediaMethod "getAudioVolume" o = MediaGetAudioVolumeMethodInfo
    ResolveMediaMethod "getBufferFill" o = MediaGetBufferFillMethodInfo
    ResolveMediaMethod "getCanSeek" o = MediaGetCanSeekMethodInfo
    ResolveMediaMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveMediaMethod "getDuration" o = MediaGetDurationMethodInfo
    ResolveMediaMethod "getPlaying" o = MediaGetPlayingMethodInfo
    ResolveMediaMethod "getProgress" o = MediaGetProgressMethodInfo
    ResolveMediaMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveMediaMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveMediaMethod "getSubtitleFontName" o = MediaGetSubtitleFontNameMethodInfo
    ResolveMediaMethod "getSubtitleUri" o = MediaGetSubtitleUriMethodInfo
    ResolveMediaMethod "getUri" o = MediaGetUriMethodInfo
    ResolveMediaMethod "setAudioVolume" o = MediaSetAudioVolumeMethodInfo
    ResolveMediaMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveMediaMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveMediaMethod "setFilename" o = MediaSetFilenameMethodInfo
    ResolveMediaMethod "setPlaying" o = MediaSetPlayingMethodInfo
    ResolveMediaMethod "setProgress" o = MediaSetProgressMethodInfo
    ResolveMediaMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveMediaMethod "setSubtitleFontName" o = MediaSetSubtitleFontNameMethodInfo
    ResolveMediaMethod "setSubtitleUri" o = MediaSetSubtitleUriMethodInfo
    ResolveMediaMethod "setUri" o = MediaSetUriMethodInfo
    ResolveMediaMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveMediaMethod t Media, O.OverloadedMethod info Media p) => OL.IsLabel t (Media -> 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 ~ ResolveMediaMethod t Media, O.OverloadedMethod info Media p, R.HasField t Media p) => R.HasField t Media p where
    getField = O.overloadedMethod @info

#endif

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

#endif

-- method Media::get_audio_volume
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "media"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "Media" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterMedia" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TDouble)
-- throws : False
-- Skip return : False

foreign import ccall "clutter_media_get_audio_volume" clutter_media_get_audio_volume :: 
    Ptr Media ->                            -- media : TInterface (Name {namespace = "Clutter", name = "Media"})
    IO CDouble

{-# DEPRECATED mediaGetAudioVolume ["(Since version 1.12)"] #-}
-- | Retrieves the playback volume of /@media@/.
-- 
-- /Since: 1.0/
mediaGetAudioVolume ::
    (B.CallStack.HasCallStack, MonadIO m, IsMedia a) =>
    a
    -- ^ /@media@/: a t'GI.Clutter.Interfaces.Media.Media'
    -> m Double
    -- ^ __Returns:__ The playback volume between 0.0 and 1.0
mediaGetAudioVolume :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsMedia a) =>
a -> m Double
mediaGetAudioVolume a
media = IO Double -> m Double
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ do
    Ptr Media
media' <- a -> IO (Ptr Media)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
media
    CDouble
result <- Ptr Media -> IO CDouble
clutter_media_get_audio_volume Ptr Media
media'
    let result' :: Double
result' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
media
    Double -> IO Double
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Double
result'

#if defined(ENABLE_OVERLOADING)
data MediaGetAudioVolumeMethodInfo
instance (signature ~ (m Double), MonadIO m, IsMedia a) => O.OverloadedMethod MediaGetAudioVolumeMethodInfo a signature where
    overloadedMethod = mediaGetAudioVolume

instance O.OverloadedMethodInfo MediaGetAudioVolumeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Interfaces.Media.mediaGetAudioVolume",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.5/docs/GI-Clutter-Interfaces-Media.html#v:mediaGetAudioVolume"
        })


#endif

-- method Media::get_buffer_fill
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "media"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "Media" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterMedia" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TDouble)
-- throws : False
-- Skip return : False

foreign import ccall "clutter_media_get_buffer_fill" clutter_media_get_buffer_fill :: 
    Ptr Media ->                            -- media : TInterface (Name {namespace = "Clutter", name = "Media"})
    IO CDouble

{-# DEPRECATED mediaGetBufferFill ["(Since version 1.12)"] #-}
-- | Retrieves the amount of the stream that is buffered.
-- 
-- /Since: 1.0/
mediaGetBufferFill ::
    (B.CallStack.HasCallStack, MonadIO m, IsMedia a) =>
    a
    -- ^ /@media@/: a t'GI.Clutter.Interfaces.Media.Media'
    -> m Double
    -- ^ __Returns:__ the fill level, between 0.0 and 1.0
mediaGetBufferFill :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsMedia a) =>
a -> m Double
mediaGetBufferFill a
media = IO Double -> m Double
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ do
    Ptr Media
media' <- a -> IO (Ptr Media)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
media
    CDouble
result <- Ptr Media -> IO CDouble
clutter_media_get_buffer_fill Ptr Media
media'
    let result' :: Double
result' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
media
    Double -> IO Double
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Double
result'

#if defined(ENABLE_OVERLOADING)
data MediaGetBufferFillMethodInfo
instance (signature ~ (m Double), MonadIO m, IsMedia a) => O.OverloadedMethod MediaGetBufferFillMethodInfo a signature where
    overloadedMethod = mediaGetBufferFill

instance O.OverloadedMethodInfo MediaGetBufferFillMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Interfaces.Media.mediaGetBufferFill",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.5/docs/GI-Clutter-Interfaces-Media.html#v:mediaGetBufferFill"
        })


#endif

-- method Media::get_can_seek
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "media"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "Media" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterMedia" , 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 "clutter_media_get_can_seek" clutter_media_get_can_seek :: 
    Ptr Media ->                            -- media : TInterface (Name {namespace = "Clutter", name = "Media"})
    IO CInt

{-# DEPRECATED mediaGetCanSeek ["(Since version 1.12)"] #-}
-- | Retrieves whether /@media@/ is seekable or not.
-- 
-- /Since: 0.2/
mediaGetCanSeek ::
    (B.CallStack.HasCallStack, MonadIO m, IsMedia a) =>
    a
    -- ^ /@media@/: a t'GI.Clutter.Interfaces.Media.Media'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@media@/ can seek, 'P.False' otherwise.
mediaGetCanSeek :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsMedia a) =>
a -> m Bool
mediaGetCanSeek a
media = 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 Media
media' <- a -> IO (Ptr Media)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
media
    CInt
result <- Ptr Media -> IO CInt
clutter_media_get_can_seek Ptr Media
media'
    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
media
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data MediaGetCanSeekMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsMedia a) => O.OverloadedMethod MediaGetCanSeekMethodInfo a signature where
    overloadedMethod = mediaGetCanSeek

instance O.OverloadedMethodInfo MediaGetCanSeekMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Interfaces.Media.mediaGetCanSeek",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.5/docs/GI-Clutter-Interfaces-Media.html#v:mediaGetCanSeek"
        })


#endif

-- method Media::get_duration
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "media"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "Media" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterMedia" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TDouble)
-- throws : False
-- Skip return : False

foreign import ccall "clutter_media_get_duration" clutter_media_get_duration :: 
    Ptr Media ->                            -- media : TInterface (Name {namespace = "Clutter", name = "Media"})
    IO CDouble

{-# DEPRECATED mediaGetDuration ["(Since version 1.12)"] #-}
-- | Retrieves the duration of the media stream that /@media@/ represents.
-- 
-- /Since: 0.2/
mediaGetDuration ::
    (B.CallStack.HasCallStack, MonadIO m, IsMedia a) =>
    a
    -- ^ /@media@/: a t'GI.Clutter.Interfaces.Media.Media'
    -> m Double
    -- ^ __Returns:__ the duration of the media stream, in seconds
mediaGetDuration :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsMedia a) =>
a -> m Double
mediaGetDuration a
media = IO Double -> m Double
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ do
    Ptr Media
media' <- a -> IO (Ptr Media)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
media
    CDouble
result <- Ptr Media -> IO CDouble
clutter_media_get_duration Ptr Media
media'
    let result' :: Double
result' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
media
    Double -> IO Double
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Double
result'

#if defined(ENABLE_OVERLOADING)
data MediaGetDurationMethodInfo
instance (signature ~ (m Double), MonadIO m, IsMedia a) => O.OverloadedMethod MediaGetDurationMethodInfo a signature where
    overloadedMethod = mediaGetDuration

instance O.OverloadedMethodInfo MediaGetDurationMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Interfaces.Media.mediaGetDuration",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.5/docs/GI-Clutter-Interfaces-Media.html#v:mediaGetDuration"
        })


#endif

-- method Media::get_playing
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "media"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "Media" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #ClutterMedia object"
--                 , 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 "clutter_media_get_playing" clutter_media_get_playing :: 
    Ptr Media ->                            -- media : TInterface (Name {namespace = "Clutter", name = "Media"})
    IO CInt

{-# DEPRECATED mediaGetPlaying ["(Since version 1.12)"] #-}
-- | Retrieves the playing status of /@media@/.
-- 
-- /Since: 0.2/
mediaGetPlaying ::
    (B.CallStack.HasCallStack, MonadIO m, IsMedia a) =>
    a
    -- ^ /@media@/: A t'GI.Clutter.Interfaces.Media.Media' object
    -> m Bool
    -- ^ __Returns:__ 'P.True' if playing, 'P.False' if stopped.
mediaGetPlaying :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsMedia a) =>
a -> m Bool
mediaGetPlaying a
media = 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 Media
media' <- a -> IO (Ptr Media)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
media
    CInt
result <- Ptr Media -> IO CInt
clutter_media_get_playing Ptr Media
media'
    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
media
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data MediaGetPlayingMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsMedia a) => O.OverloadedMethod MediaGetPlayingMethodInfo a signature where
    overloadedMethod = mediaGetPlaying

instance O.OverloadedMethodInfo MediaGetPlayingMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Interfaces.Media.mediaGetPlaying",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.5/docs/GI-Clutter-Interfaces-Media.html#v:mediaGetPlaying"
        })


#endif

-- method Media::get_progress
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "media"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "Media" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterMedia" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TDouble)
-- throws : False
-- Skip return : False

foreign import ccall "clutter_media_get_progress" clutter_media_get_progress :: 
    Ptr Media ->                            -- media : TInterface (Name {namespace = "Clutter", name = "Media"})
    IO CDouble

{-# DEPRECATED mediaGetProgress ["(Since version 1.12)"] #-}
-- | Retrieves the playback progress of /@media@/.
-- 
-- /Since: 1.0/
mediaGetProgress ::
    (B.CallStack.HasCallStack, MonadIO m, IsMedia a) =>
    a
    -- ^ /@media@/: a t'GI.Clutter.Interfaces.Media.Media'
    -> m Double
    -- ^ __Returns:__ the playback progress, between 0.0 and 1.0
mediaGetProgress :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsMedia a) =>
a -> m Double
mediaGetProgress a
media = IO Double -> m Double
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ do
    Ptr Media
media' <- a -> IO (Ptr Media)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
media
    CDouble
result <- Ptr Media -> IO CDouble
clutter_media_get_progress Ptr Media
media'
    let result' :: Double
result' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
media
    Double -> IO Double
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Double
result'

#if defined(ENABLE_OVERLOADING)
data MediaGetProgressMethodInfo
instance (signature ~ (m Double), MonadIO m, IsMedia a) => O.OverloadedMethod MediaGetProgressMethodInfo a signature where
    overloadedMethod = mediaGetProgress

instance O.OverloadedMethodInfo MediaGetProgressMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Interfaces.Media.mediaGetProgress",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.5/docs/GI-Clutter-Interfaces-Media.html#v:mediaGetProgress"
        })


#endif

-- method Media::get_subtitle_font_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "media"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "Media" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterMedia" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "clutter_media_get_subtitle_font_name" clutter_media_get_subtitle_font_name :: 
    Ptr Media ->                            -- media : TInterface (Name {namespace = "Clutter", name = "Media"})
    IO CString

{-# DEPRECATED mediaGetSubtitleFontName ["(Since version 1.12)"] #-}
-- | Retrieves the font name currently used.
-- 
-- /Since: 1.2/
mediaGetSubtitleFontName ::
    (B.CallStack.HasCallStack, MonadIO m, IsMedia a) =>
    a
    -- ^ /@media@/: a t'GI.Clutter.Interfaces.Media.Media'
    -> m T.Text
    -- ^ __Returns:__ a string containing the font name. Use 'GI.GLib.Functions.free'
    --   to free the returned string
mediaGetSubtitleFontName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsMedia a) =>
a -> m Text
mediaGetSubtitleFontName a
media = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr Media
media' <- a -> IO (Ptr Media)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
media
    CString
result <- Ptr Media -> IO CString
clutter_media_get_subtitle_font_name Ptr Media
media'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"mediaGetSubtitleFontName" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
media
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data MediaGetSubtitleFontNameMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsMedia a) => O.OverloadedMethod MediaGetSubtitleFontNameMethodInfo a signature where
    overloadedMethod = mediaGetSubtitleFontName

instance O.OverloadedMethodInfo MediaGetSubtitleFontNameMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Interfaces.Media.mediaGetSubtitleFontName",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.5/docs/GI-Clutter-Interfaces-Media.html#v:mediaGetSubtitleFontName"
        })


#endif

-- method Media::get_subtitle_uri
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "media"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "Media" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterMedia" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "clutter_media_get_subtitle_uri" clutter_media_get_subtitle_uri :: 
    Ptr Media ->                            -- media : TInterface (Name {namespace = "Clutter", name = "Media"})
    IO CString

{-# DEPRECATED mediaGetSubtitleUri ["(Since version 1.12)"] #-}
-- | Retrieves the URI of the subtitle file in use.
-- 
-- /Since: 1.2/
mediaGetSubtitleUri ::
    (B.CallStack.HasCallStack, MonadIO m, IsMedia a) =>
    a
    -- ^ /@media@/: a t'GI.Clutter.Interfaces.Media.Media'
    -> m T.Text
    -- ^ __Returns:__ the URI of the subtitle file. Use 'GI.GLib.Functions.free'
    --   to free the returned string
mediaGetSubtitleUri :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsMedia a) =>
a -> m Text
mediaGetSubtitleUri a
media = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr Media
media' <- a -> IO (Ptr Media)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
media
    CString
result <- Ptr Media -> IO CString
clutter_media_get_subtitle_uri Ptr Media
media'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"mediaGetSubtitleUri" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
media
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data MediaGetSubtitleUriMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsMedia a) => O.OverloadedMethod MediaGetSubtitleUriMethodInfo a signature where
    overloadedMethod = mediaGetSubtitleUri

instance O.OverloadedMethodInfo MediaGetSubtitleUriMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Interfaces.Media.mediaGetSubtitleUri",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.5/docs/GI-Clutter-Interfaces-Media.html#v:mediaGetSubtitleUri"
        })


#endif

-- method Media::get_uri
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "media"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "Media" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterMedia" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "clutter_media_get_uri" clutter_media_get_uri :: 
    Ptr Media ->                            -- media : TInterface (Name {namespace = "Clutter", name = "Media"})
    IO CString

{-# DEPRECATED mediaGetUri ["(Since version 1.12)"] #-}
-- | Retrieves the URI from /@media@/.
-- 
-- /Since: 0.2/
mediaGetUri ::
    (B.CallStack.HasCallStack, MonadIO m, IsMedia a) =>
    a
    -- ^ /@media@/: a t'GI.Clutter.Interfaces.Media.Media'
    -> m T.Text
    -- ^ __Returns:__ the URI of the media stream. Use 'GI.GLib.Functions.free'
    --   to free the returned string
mediaGetUri :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsMedia a) =>
a -> m Text
mediaGetUri a
media = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr Media
media' <- a -> IO (Ptr Media)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
media
    CString
result <- Ptr Media -> IO CString
clutter_media_get_uri Ptr Media
media'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"mediaGetUri" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
media
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data MediaGetUriMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsMedia a) => O.OverloadedMethod MediaGetUriMethodInfo a signature where
    overloadedMethod = mediaGetUri

instance O.OverloadedMethodInfo MediaGetUriMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Interfaces.Media.mediaGetUri",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.5/docs/GI-Clutter-Interfaces-Media.html#v:mediaGetUri"
        })


#endif

-- method Media::set_audio_volume
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "media"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "Media" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterMedia" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "volume"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the volume as a double between 0.0 and 1.0"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "clutter_media_set_audio_volume" clutter_media_set_audio_volume :: 
    Ptr Media ->                            -- media : TInterface (Name {namespace = "Clutter", name = "Media"})
    CDouble ->                              -- volume : TBasicType TDouble
    IO ()

{-# DEPRECATED mediaSetAudioVolume ["(Since version 1.12)"] #-}
-- | Sets the playback volume of /@media@/ to /@volume@/.
-- 
-- /Since: 1.0/
mediaSetAudioVolume ::
    (B.CallStack.HasCallStack, MonadIO m, IsMedia a) =>
    a
    -- ^ /@media@/: a t'GI.Clutter.Interfaces.Media.Media'
    -> Double
    -- ^ /@volume@/: the volume as a double between 0.0 and 1.0
    -> m ()
mediaSetAudioVolume :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsMedia a) =>
a -> Double -> m ()
mediaSetAudioVolume a
media Double
volume = 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 Media
media' <- a -> IO (Ptr Media)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
media
    let volume' :: CDouble
volume' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
volume
    Ptr Media -> CDouble -> IO ()
clutter_media_set_audio_volume Ptr Media
media' CDouble
volume'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
media
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data MediaSetAudioVolumeMethodInfo
instance (signature ~ (Double -> m ()), MonadIO m, IsMedia a) => O.OverloadedMethod MediaSetAudioVolumeMethodInfo a signature where
    overloadedMethod = mediaSetAudioVolume

instance O.OverloadedMethodInfo MediaSetAudioVolumeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Interfaces.Media.mediaSetAudioVolume",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.5/docs/GI-Clutter-Interfaces-Media.html#v:mediaSetAudioVolume"
        })


#endif

-- method Media::set_filename
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "media"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "Media" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterMedia" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "filename"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A filename" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "clutter_media_set_filename" clutter_media_set_filename :: 
    Ptr Media ->                            -- media : TInterface (Name {namespace = "Clutter", name = "Media"})
    CString ->                              -- filename : TBasicType TUTF8
    IO ()

{-# DEPRECATED mediaSetFilename ["(Since version 1.12)"] #-}
-- | Sets the source of /@media@/ using a file path.
-- 
-- /Since: 0.2/
mediaSetFilename ::
    (B.CallStack.HasCallStack, MonadIO m, IsMedia a) =>
    a
    -- ^ /@media@/: a t'GI.Clutter.Interfaces.Media.Media'
    -> T.Text
    -- ^ /@filename@/: A filename
    -> m ()
mediaSetFilename :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsMedia a) =>
a -> Text -> m ()
mediaSetFilename a
media Text
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 Media
media' <- a -> IO (Ptr Media)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
media
    CString
filename' <- Text -> IO CString
textToCString Text
filename
    Ptr Media -> CString -> IO ()
clutter_media_set_filename Ptr Media
media' CString
filename'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
media
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
filename'
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data MediaSetFilenameMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsMedia a) => O.OverloadedMethod MediaSetFilenameMethodInfo a signature where
    overloadedMethod = mediaSetFilename

instance O.OverloadedMethodInfo MediaSetFilenameMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Interfaces.Media.mediaSetFilename",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.5/docs/GI-Clutter-Interfaces-Media.html#v:mediaSetFilename"
        })


#endif

-- method Media::set_playing
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "media"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "Media" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterMedia" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "playing"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "%TRUE to start playing"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "clutter_media_set_playing" clutter_media_set_playing :: 
    Ptr Media ->                            -- media : TInterface (Name {namespace = "Clutter", name = "Media"})
    CInt ->                                 -- playing : TBasicType TBoolean
    IO ()

{-# DEPRECATED mediaSetPlaying ["(Since version 1.12)"] #-}
-- | Starts or stops playing of /@media@/.
--  
-- The implementation might be asynchronous, so the way to know whether
-- the actual playing state of the /@media@/ is to use the [Object::notify]("GI.GObject.Objects.Object#g:signal:notify")
-- signal on the t'GI.Clutter.Interfaces.Media.Media':@/playing/@ property and then retrieve the
-- current state with 'GI.Clutter.Interfaces.Media.mediaGetPlaying'. ClutterGstVideoTexture
-- in clutter-gst is an example of such an asynchronous implementation.
-- 
-- /Since: 0.2/
mediaSetPlaying ::
    (B.CallStack.HasCallStack, MonadIO m, IsMedia a) =>
    a
    -- ^ /@media@/: a t'GI.Clutter.Interfaces.Media.Media'
    -> Bool
    -- ^ /@playing@/: 'P.True' to start playing
    -> m ()
mediaSetPlaying :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsMedia a) =>
a -> Bool -> m ()
mediaSetPlaying a
media Bool
playing = 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 Media
media' <- a -> IO (Ptr Media)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
media
    let playing' :: CInt
playing' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.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
P.fromEnum) Bool
playing
    Ptr Media -> CInt -> IO ()
clutter_media_set_playing Ptr Media
media' CInt
playing'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
media
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data MediaSetPlayingMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsMedia a) => O.OverloadedMethod MediaSetPlayingMethodInfo a signature where
    overloadedMethod = mediaSetPlaying

instance O.OverloadedMethodInfo MediaSetPlayingMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Interfaces.Media.mediaSetPlaying",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.5/docs/GI-Clutter-Interfaces-Media.html#v:mediaSetPlaying"
        })


#endif

-- method Media::set_progress
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "media"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "Media" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterMedia" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "progress"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the progress of the playback, between 0.0 and 1.0"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "clutter_media_set_progress" clutter_media_set_progress :: 
    Ptr Media ->                            -- media : TInterface (Name {namespace = "Clutter", name = "Media"})
    CDouble ->                              -- progress : TBasicType TDouble
    IO ()

{-# DEPRECATED mediaSetProgress ["(Since version 1.12)"] #-}
-- | Sets the playback progress of /@media@/. The /@progress@/ is
-- a normalized value between 0.0 (begin) and 1.0 (end).
-- 
-- /Since: 1.0/
mediaSetProgress ::
    (B.CallStack.HasCallStack, MonadIO m, IsMedia a) =>
    a
    -- ^ /@media@/: a t'GI.Clutter.Interfaces.Media.Media'
    -> Double
    -- ^ /@progress@/: the progress of the playback, between 0.0 and 1.0
    -> m ()
mediaSetProgress :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsMedia a) =>
a -> Double -> m ()
mediaSetProgress a
media Double
progress = 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 Media
media' <- a -> IO (Ptr Media)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
media
    let progress' :: CDouble
progress' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
progress
    Ptr Media -> CDouble -> IO ()
clutter_media_set_progress Ptr Media
media' CDouble
progress'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
media
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data MediaSetProgressMethodInfo
instance (signature ~ (Double -> m ()), MonadIO m, IsMedia a) => O.OverloadedMethod MediaSetProgressMethodInfo a signature where
    overloadedMethod = mediaSetProgress

instance O.OverloadedMethodInfo MediaSetProgressMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Interfaces.Media.mediaSetProgress",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.5/docs/GI-Clutter-Interfaces-Media.html#v:mediaSetProgress"
        })


#endif

-- method Media::set_subtitle_font_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "media"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "Media" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterMedia" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "font_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a font name, or %NULL to set the default font name"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "clutter_media_set_subtitle_font_name" clutter_media_set_subtitle_font_name :: 
    Ptr Media ->                            -- media : TInterface (Name {namespace = "Clutter", name = "Media"})
    CString ->                              -- font_name : TBasicType TUTF8
    IO ()

{-# DEPRECATED mediaSetSubtitleFontName ["(Since version 1.12)"] #-}
-- | Sets the font used by the subtitle renderer. The /@fontName@/ string must be
-- either 'P.Nothing', which means that the default font name of the underlying
-- implementation will be used; or must follow the grammar recognized by
-- 'GI.Pango.Functions.fontDescriptionFromString' like:
-- 
-- >
-- >  clutter_media_set_subtitle_font_name (media, "Sans 24pt");
-- 
-- 
-- /Since: 1.2/
mediaSetSubtitleFontName ::
    (B.CallStack.HasCallStack, MonadIO m, IsMedia a) =>
    a
    -- ^ /@media@/: a t'GI.Clutter.Interfaces.Media.Media'
    -> T.Text
    -- ^ /@fontName@/: a font name, or 'P.Nothing' to set the default font name
    -> m ()
mediaSetSubtitleFontName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsMedia a) =>
a -> Text -> m ()
mediaSetSubtitleFontName a
media Text
fontName = 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 Media
media' <- a -> IO (Ptr Media)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
media
    CString
fontName' <- Text -> IO CString
textToCString Text
fontName
    Ptr Media -> CString -> IO ()
clutter_media_set_subtitle_font_name Ptr Media
media' CString
fontName'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
media
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
fontName'
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data MediaSetSubtitleFontNameMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsMedia a) => O.OverloadedMethod MediaSetSubtitleFontNameMethodInfo a signature where
    overloadedMethod = mediaSetSubtitleFontName

instance O.OverloadedMethodInfo MediaSetSubtitleFontNameMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Interfaces.Media.mediaSetSubtitleFontName",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.5/docs/GI-Clutter-Interfaces-Media.html#v:mediaSetSubtitleFontName"
        })


#endif

-- method Media::set_subtitle_uri
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "media"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "Media" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterMedia" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "uri"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the URI of a subtitle file"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "clutter_media_set_subtitle_uri" clutter_media_set_subtitle_uri :: 
    Ptr Media ->                            -- media : TInterface (Name {namespace = "Clutter", name = "Media"})
    CString ->                              -- uri : TBasicType TUTF8
    IO ()

{-# DEPRECATED mediaSetSubtitleUri ["(Since version 1.12)"] #-}
-- | Sets the location of a subtitle file to display while playing /@media@/.
-- 
-- /Since: 1.2/
mediaSetSubtitleUri ::
    (B.CallStack.HasCallStack, MonadIO m, IsMedia a) =>
    a
    -- ^ /@media@/: a t'GI.Clutter.Interfaces.Media.Media'
    -> T.Text
    -- ^ /@uri@/: the URI of a subtitle file
    -> m ()
mediaSetSubtitleUri :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsMedia a) =>
a -> Text -> m ()
mediaSetSubtitleUri a
media Text
uri = 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 Media
media' <- a -> IO (Ptr Media)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
media
    CString
uri' <- Text -> IO CString
textToCString Text
uri
    Ptr Media -> CString -> IO ()
clutter_media_set_subtitle_uri Ptr Media
media' CString
uri'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
media
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
uri'
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data MediaSetSubtitleUriMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsMedia a) => O.OverloadedMethod MediaSetSubtitleUriMethodInfo a signature where
    overloadedMethod = mediaSetSubtitleUri

instance O.OverloadedMethodInfo MediaSetSubtitleUriMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Interfaces.Media.mediaSetSubtitleUri",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.5/docs/GI-Clutter-Interfaces-Media.html#v:mediaSetSubtitleUri"
        })


#endif

-- method Media::set_uri
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "media"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "Media" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterMedia" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "uri"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the URI of the media stream"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "clutter_media_set_uri" clutter_media_set_uri :: 
    Ptr Media ->                            -- media : TInterface (Name {namespace = "Clutter", name = "Media"})
    CString ->                              -- uri : TBasicType TUTF8
    IO ()

{-# DEPRECATED mediaSetUri ["(Since version 1.12)"] #-}
-- | Sets the URI of /@media@/ to /@uri@/.
-- 
-- /Since: 0.2/
mediaSetUri ::
    (B.CallStack.HasCallStack, MonadIO m, IsMedia a) =>
    a
    -- ^ /@media@/: a t'GI.Clutter.Interfaces.Media.Media'
    -> T.Text
    -- ^ /@uri@/: the URI of the media stream
    -> m ()
mediaSetUri :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsMedia a) =>
a -> Text -> m ()
mediaSetUri a
media Text
uri = 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 Media
media' <- a -> IO (Ptr Media)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
media
    CString
uri' <- Text -> IO CString
textToCString Text
uri
    Ptr Media -> CString -> IO ()
clutter_media_set_uri Ptr Media
media' CString
uri'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
media
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
uri'
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data MediaSetUriMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsMedia a) => O.OverloadedMethod MediaSetUriMethodInfo a signature where
    overloadedMethod = mediaSetUri

instance O.OverloadedMethodInfo MediaSetUriMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Interfaces.Media.mediaSetUri",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.5/docs/GI-Clutter-Interfaces-Media.html#v:mediaSetUri"
        })


#endif

-- signal Media::eos
{-# DEPRECATED MediaEosCallback ["(Since version 1.12)"] #-}
-- | The [eos](#g:signal:eos) signal is emitted each time the media stream ends.
-- 
-- /Since: 0.2/
type MediaEosCallback =
    IO ()

type C_MediaEosCallback =
    Ptr Media ->                            -- object
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_MediaEosCallback`.
foreign import ccall "wrapper"
    mk_MediaEosCallback :: C_MediaEosCallback -> IO (FunPtr C_MediaEosCallback)

wrap_MediaEosCallback :: 
    GObject a => (a -> MediaEosCallback) ->
    C_MediaEosCallback
wrap_MediaEosCallback :: forall a. GObject a => (a -> IO ()) -> C_MediaEosCallback
wrap_MediaEosCallback a -> IO ()
gi'cb Ptr Media
gi'selfPtr Ptr ()
_ = do
    Ptr Media -> (Media -> IO ()) -> IO ()
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr Media
gi'selfPtr ((Media -> IO ()) -> IO ()) -> (Media -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Media
gi'self -> a -> IO ()
gi'cb (Media -> a
forall a b. Coercible a b => a -> b
Coerce.coerce Media
gi'self) 


-- | Connect a signal handler for the [eos](#signal:eos) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' media #eos callback
-- @
-- 
-- 
onMediaEos :: (IsMedia a, MonadIO m) => a -> ((?self :: a) => MediaEosCallback) -> m SignalHandlerId
onMediaEos :: forall a (m :: * -> *).
(IsMedia a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
onMediaEos a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
    let wrapped' :: C_MediaEosCallback
wrapped' = (a -> IO ()) -> C_MediaEosCallback
forall a. GObject a => (a -> IO ()) -> C_MediaEosCallback
wrap_MediaEosCallback a -> IO ()
wrapped
    FunPtr C_MediaEosCallback
wrapped'' <- C_MediaEosCallback -> IO (FunPtr C_MediaEosCallback)
mk_MediaEosCallback C_MediaEosCallback
wrapped'
    a
-> Text
-> FunPtr C_MediaEosCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"eos" FunPtr C_MediaEosCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [eos](#signal:eos) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' media #eos callback
-- @
-- 
-- 
-- 
-- By default the object invoking the signal is not passed to the callback.
-- If you need to access it, you can use the implit @?self@ parameter.
-- Note that this requires activating the @ImplicitParams@ GHC extension.
-- 
afterMediaEos :: (IsMedia a, MonadIO m) => a -> ((?self :: a) => MediaEosCallback) -> m SignalHandlerId
afterMediaEos :: forall a (m :: * -> *).
(IsMedia a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
afterMediaEos a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
    let wrapped' :: C_MediaEosCallback
wrapped' = (a -> IO ()) -> C_MediaEosCallback
forall a. GObject a => (a -> IO ()) -> C_MediaEosCallback
wrap_MediaEosCallback a -> IO ()
wrapped
    FunPtr C_MediaEosCallback
wrapped'' <- C_MediaEosCallback -> IO (FunPtr C_MediaEosCallback)
mk_MediaEosCallback C_MediaEosCallback
wrapped'
    a
-> Text
-> FunPtr C_MediaEosCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"eos" FunPtr C_MediaEosCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data MediaEosSignalInfo
instance SignalInfo MediaEosSignalInfo where
    type HaskellCallbackType MediaEosSignalInfo = MediaEosCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_MediaEosCallback cb
        cb'' <- mk_MediaEosCallback cb'
        connectSignalFunPtr obj "eos" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Interfaces.Media::eos"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.5/docs/GI-Clutter-Interfaces-Media.html#g:signal:eos"})

#endif

-- signal Media::error
{-# DEPRECATED MediaErrorCallback ["(Since version 1.12)"] #-}
-- | The [error](#g:signal:error) signal is emitted each time an error occurred.
-- 
-- /Since: 0.2/
type MediaErrorCallback =
    GError
    -- ^ /@error@/: the t'GError'
    -> IO ()

type C_MediaErrorCallback =
    Ptr Media ->                            -- object
    Ptr GError ->
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_MediaErrorCallback`.
foreign import ccall "wrapper"
    mk_MediaErrorCallback :: C_MediaErrorCallback -> IO (FunPtr C_MediaErrorCallback)

wrap_MediaErrorCallback :: 
    GObject a => (a -> MediaErrorCallback) ->
    C_MediaErrorCallback
wrap_MediaErrorCallback :: forall a.
GObject a =>
(a -> MediaErrorCallback) -> C_MediaErrorCallback
wrap_MediaErrorCallback a -> MediaErrorCallback
gi'cb Ptr Media
gi'selfPtr Ptr GError
error_ Ptr ()
_ = do
    GError
error_' <- ((ManagedPtr GError -> GError) -> Ptr GError -> IO GError
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr GError -> GError
GError) Ptr GError
error_
    Ptr Media -> (Media -> IO ()) -> IO ()
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr Media
gi'selfPtr ((Media -> IO ()) -> IO ()) -> (Media -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Media
gi'self -> a -> MediaErrorCallback
gi'cb (Media -> a
forall a b. Coercible a b => a -> b
Coerce.coerce Media
gi'self)  GError
error_'


-- | Connect a signal handler for the [error](#signal:error) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' media #error callback
-- @
-- 
-- 
onMediaError :: (IsMedia a, MonadIO m) => a -> ((?self :: a) => MediaErrorCallback) -> m SignalHandlerId
onMediaError :: forall a (m :: * -> *).
(IsMedia a, MonadIO m) =>
a -> ((?self::a) => MediaErrorCallback) -> m SignalHandlerId
onMediaError a
obj (?self::a) => MediaErrorCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> MediaErrorCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => MediaErrorCallback
MediaErrorCallback
cb
    let wrapped' :: C_MediaErrorCallback
wrapped' = (a -> MediaErrorCallback) -> C_MediaErrorCallback
forall a.
GObject a =>
(a -> MediaErrorCallback) -> C_MediaErrorCallback
wrap_MediaErrorCallback a -> MediaErrorCallback
wrapped
    FunPtr C_MediaErrorCallback
wrapped'' <- C_MediaErrorCallback -> IO (FunPtr C_MediaErrorCallback)
mk_MediaErrorCallback C_MediaErrorCallback
wrapped'
    a
-> Text
-> FunPtr C_MediaErrorCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"error" FunPtr C_MediaErrorCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [error](#signal:error) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' media #error callback
-- @
-- 
-- 
-- 
-- By default the object invoking the signal is not passed to the callback.
-- If you need to access it, you can use the implit @?self@ parameter.
-- Note that this requires activating the @ImplicitParams@ GHC extension.
-- 
afterMediaError :: (IsMedia a, MonadIO m) => a -> ((?self :: a) => MediaErrorCallback) -> m SignalHandlerId
afterMediaError :: forall a (m :: * -> *).
(IsMedia a, MonadIO m) =>
a -> ((?self::a) => MediaErrorCallback) -> m SignalHandlerId
afterMediaError a
obj (?self::a) => MediaErrorCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> MediaErrorCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => MediaErrorCallback
MediaErrorCallback
cb
    let wrapped' :: C_MediaErrorCallback
wrapped' = (a -> MediaErrorCallback) -> C_MediaErrorCallback
forall a.
GObject a =>
(a -> MediaErrorCallback) -> C_MediaErrorCallback
wrap_MediaErrorCallback a -> MediaErrorCallback
wrapped
    FunPtr C_MediaErrorCallback
wrapped'' <- C_MediaErrorCallback -> IO (FunPtr C_MediaErrorCallback)
mk_MediaErrorCallback C_MediaErrorCallback
wrapped'
    a
-> Text
-> FunPtr C_MediaErrorCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"error" FunPtr C_MediaErrorCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data MediaErrorSignalInfo
instance SignalInfo MediaErrorSignalInfo where
    type HaskellCallbackType MediaErrorSignalInfo = MediaErrorCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_MediaErrorCallback cb
        cb'' <- mk_MediaErrorCallback cb'
        connectSignalFunPtr obj "error" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Interfaces.Media::error"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.5/docs/GI-Clutter-Interfaces-Media.html#g:signal:error"})

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Media = MediaSignalList
type MediaSignalList = ('[ '("eos", MediaEosSignalInfo), '("error", MediaErrorSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, DK.Type)])

#endif