{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.GES.Objects.VideoSource
(
VideoSource(..) ,
IsVideoSource ,
toVideoSource ,
#if defined(ENABLE_OVERLOADING)
ResolveVideoSourceMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
VideoSourceGetNaturalSizeMethodInfo ,
#endif
videoSourceGetNaturalSize ,
) 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 {-# SOURCE #-} qualified GI.GES.Interfaces.Extractable as GES.Extractable
import {-# SOURCE #-} qualified GI.GES.Interfaces.MetaContainer as GES.MetaContainer
import {-# SOURCE #-} qualified GI.GES.Objects.Source as GES.Source
import {-# SOURCE #-} qualified GI.GES.Objects.TimelineElement as GES.TimelineElement
import {-# SOURCE #-} qualified GI.GES.Objects.TrackElement as GES.TrackElement
import qualified GI.GObject.Objects.Object as GObject.Object
newtype VideoSource = VideoSource (SP.ManagedPtr VideoSource)
deriving (VideoSource -> VideoSource -> Bool
(VideoSource -> VideoSource -> Bool)
-> (VideoSource -> VideoSource -> Bool) -> Eq VideoSource
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: VideoSource -> VideoSource -> Bool
== :: VideoSource -> VideoSource -> Bool
$c/= :: VideoSource -> VideoSource -> Bool
/= :: VideoSource -> VideoSource -> Bool
Eq)
instance SP.ManagedPtrNewtype VideoSource where
toManagedPtr :: VideoSource -> ManagedPtr VideoSource
toManagedPtr (VideoSource ManagedPtr VideoSource
p) = ManagedPtr VideoSource
p
foreign import ccall "ges_video_source_get_type"
c_ges_video_source_get_type :: IO B.Types.GType
instance B.Types.TypedObject VideoSource where
glibType :: IO GType
glibType = IO GType
c_ges_video_source_get_type
instance B.Types.GObject VideoSource
class (SP.GObject o, O.IsDescendantOf VideoSource o) => IsVideoSource o
instance (SP.GObject o, O.IsDescendantOf VideoSource o) => IsVideoSource o
instance O.HasParentTypes VideoSource
type instance O.ParentTypes VideoSource = '[GES.Source.Source, GES.TrackElement.TrackElement, GES.TimelineElement.TimelineElement, GObject.Object.Object, GES.Extractable.Extractable, GES.MetaContainer.MetaContainer]
toVideoSource :: (MIO.MonadIO m, IsVideoSource o) => o -> m VideoSource
toVideoSource :: forall (m :: * -> *) o.
(MonadIO m, IsVideoSource o) =>
o -> m VideoSource
toVideoSource = IO VideoSource -> m VideoSource
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO VideoSource -> m VideoSource)
-> (o -> IO VideoSource) -> o -> m VideoSource
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr VideoSource -> VideoSource) -> o -> IO VideoSource
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr VideoSource -> VideoSource
VideoSource
instance B.GValue.IsGValue (Maybe VideoSource) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_ges_video_source_get_type
gvalueSet_ :: Ptr GValue -> Maybe VideoSource -> IO ()
gvalueSet_ Ptr GValue
gv Maybe VideoSource
P.Nothing = Ptr GValue -> Ptr VideoSource -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr VideoSource
forall a. Ptr a
FP.nullPtr :: FP.Ptr VideoSource)
gvalueSet_ Ptr GValue
gv (P.Just VideoSource
obj) = VideoSource -> (Ptr VideoSource -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr VideoSource
obj (Ptr GValue -> Ptr VideoSource -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe VideoSource)
gvalueGet_ Ptr GValue
gv = do
Ptr VideoSource
ptr <- Ptr GValue -> IO (Ptr VideoSource)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr VideoSource)
if Ptr VideoSource
ptr Ptr VideoSource -> Ptr VideoSource -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr VideoSource
forall a. Ptr a
FP.nullPtr
then VideoSource -> Maybe VideoSource
forall a. a -> Maybe a
P.Just (VideoSource -> Maybe VideoSource)
-> IO VideoSource -> IO (Maybe VideoSource)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr VideoSource -> VideoSource)
-> Ptr VideoSource -> IO VideoSource
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr VideoSource -> VideoSource
VideoSource Ptr VideoSource
ptr
else Maybe VideoSource -> IO (Maybe VideoSource)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe VideoSource
forall a. Maybe a
P.Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolveVideoSourceMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolveVideoSourceMethod "addChildProperty" o = GES.TimelineElement.TimelineElementAddChildPropertyMethodInfo
ResolveVideoSourceMethod "addChildrenProps" o = GES.TrackElement.TrackElementAddChildrenPropsMethodInfo
ResolveVideoSourceMethod "addMetasFromString" o = GES.MetaContainer.MetaContainerAddMetasFromStringMethodInfo
ResolveVideoSourceMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveVideoSourceMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveVideoSourceMethod "checkMetaRegistered" o = GES.MetaContainer.MetaContainerCheckMetaRegisteredMethodInfo
ResolveVideoSourceMethod "clampControlSource" o = GES.TrackElement.TrackElementClampControlSourceMethodInfo
ResolveVideoSourceMethod "copy" o = GES.TimelineElement.TimelineElementCopyMethodInfo
ResolveVideoSourceMethod "edit" o = GES.TrackElement.TrackElementEditMethodInfo
ResolveVideoSourceMethod "editFull" o = GES.TimelineElement.TimelineElementEditFullMethodInfo
ResolveVideoSourceMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveVideoSourceMethod "foreach" o = GES.MetaContainer.MetaContainerForeachMethodInfo
ResolveVideoSourceMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveVideoSourceMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveVideoSourceMethod "hasInternalSource" o = GES.TrackElement.TrackElementHasInternalSourceMethodInfo
ResolveVideoSourceMethod "isActive" o = GES.TrackElement.TrackElementIsActiveMethodInfo
ResolveVideoSourceMethod "isCore" o = GES.TrackElement.TrackElementIsCoreMethodInfo
ResolveVideoSourceMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveVideoSourceMethod "listChildrenProperties" o = GES.TrackElement.TrackElementListChildrenPropertiesMethodInfo
ResolveVideoSourceMethod "lookupChild" o = GES.TrackElement.TrackElementLookupChildMethodInfo
ResolveVideoSourceMethod "metasToString" o = GES.MetaContainer.MetaContainerMetasToStringMethodInfo
ResolveVideoSourceMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveVideoSourceMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveVideoSourceMethod "paste" o = GES.TimelineElement.TimelineElementPasteMethodInfo
ResolveVideoSourceMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveVideoSourceMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveVideoSourceMethod "registerMeta" o = GES.MetaContainer.MetaContainerRegisterMetaMethodInfo
ResolveVideoSourceMethod "registerMetaBoolean" o = GES.MetaContainer.MetaContainerRegisterMetaBooleanMethodInfo
ResolveVideoSourceMethod "registerMetaDate" o = GES.MetaContainer.MetaContainerRegisterMetaDateMethodInfo
ResolveVideoSourceMethod "registerMetaDateTime" o = GES.MetaContainer.MetaContainerRegisterMetaDateTimeMethodInfo
ResolveVideoSourceMethod "registerMetaDouble" o = GES.MetaContainer.MetaContainerRegisterMetaDoubleMethodInfo
ResolveVideoSourceMethod "registerMetaFloat" o = GES.MetaContainer.MetaContainerRegisterMetaFloatMethodInfo
ResolveVideoSourceMethod "registerMetaInt" o = GES.MetaContainer.MetaContainerRegisterMetaIntMethodInfo
ResolveVideoSourceMethod "registerMetaInt64" o = GES.MetaContainer.MetaContainerRegisterMetaInt64MethodInfo
ResolveVideoSourceMethod "registerMetaString" o = GES.MetaContainer.MetaContainerRegisterMetaStringMethodInfo
ResolveVideoSourceMethod "registerMetaUint" o = GES.MetaContainer.MetaContainerRegisterMetaUintMethodInfo
ResolveVideoSourceMethod "registerMetaUint64" o = GES.MetaContainer.MetaContainerRegisterMetaUint64MethodInfo
ResolveVideoSourceMethod "registerStaticMeta" o = GES.MetaContainer.MetaContainerRegisterStaticMetaMethodInfo
ResolveVideoSourceMethod "removeChildProperty" o = GES.TimelineElement.TimelineElementRemoveChildPropertyMethodInfo
ResolveVideoSourceMethod "removeControlBinding" o = GES.TrackElement.TrackElementRemoveControlBindingMethodInfo
ResolveVideoSourceMethod "ripple" o = GES.TimelineElement.TimelineElementRippleMethodInfo
ResolveVideoSourceMethod "rippleEnd" o = GES.TimelineElement.TimelineElementRippleEndMethodInfo
ResolveVideoSourceMethod "rollEnd" o = GES.TimelineElement.TimelineElementRollEndMethodInfo
ResolveVideoSourceMethod "rollStart" o = GES.TimelineElement.TimelineElementRollStartMethodInfo
ResolveVideoSourceMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveVideoSourceMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveVideoSourceMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveVideoSourceMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveVideoSourceMethod "trim" o = GES.TimelineElement.TimelineElementTrimMethodInfo
ResolveVideoSourceMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveVideoSourceMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveVideoSourceMethod "getAllControlBindings" o = GES.TrackElement.TrackElementGetAllControlBindingsMethodInfo
ResolveVideoSourceMethod "getAsset" o = GES.Extractable.ExtractableGetAssetMethodInfo
ResolveVideoSourceMethod "getAutoClampControlSources" o = GES.TrackElement.TrackElementGetAutoClampControlSourcesMethodInfo
ResolveVideoSourceMethod "getBoolean" o = GES.MetaContainer.MetaContainerGetBooleanMethodInfo
ResolveVideoSourceMethod "getChildProperty" o = GES.TimelineElement.TimelineElementGetChildPropertyMethodInfo
ResolveVideoSourceMethod "getChildPropertyByPspec" o = GES.TimelineElement.TimelineElementGetChildPropertyByPspecMethodInfo
ResolveVideoSourceMethod "getControlBinding" o = GES.TrackElement.TrackElementGetControlBindingMethodInfo
ResolveVideoSourceMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveVideoSourceMethod "getDate" o = GES.MetaContainer.MetaContainerGetDateMethodInfo
ResolveVideoSourceMethod "getDateTime" o = GES.MetaContainer.MetaContainerGetDateTimeMethodInfo
ResolveVideoSourceMethod "getDouble" o = GES.MetaContainer.MetaContainerGetDoubleMethodInfo
ResolveVideoSourceMethod "getDuration" o = GES.TimelineElement.TimelineElementGetDurationMethodInfo
ResolveVideoSourceMethod "getElement" o = GES.TrackElement.TrackElementGetElementMethodInfo
ResolveVideoSourceMethod "getFloat" o = GES.MetaContainer.MetaContainerGetFloatMethodInfo
ResolveVideoSourceMethod "getGnlobject" o = GES.TrackElement.TrackElementGetGnlobjectMethodInfo
ResolveVideoSourceMethod "getId" o = GES.Extractable.ExtractableGetIdMethodInfo
ResolveVideoSourceMethod "getInpoint" o = GES.TimelineElement.TimelineElementGetInpointMethodInfo
ResolveVideoSourceMethod "getInt" o = GES.MetaContainer.MetaContainerGetIntMethodInfo
ResolveVideoSourceMethod "getInt64" o = GES.MetaContainer.MetaContainerGetInt64MethodInfo
ResolveVideoSourceMethod "getLayerPriority" o = GES.TimelineElement.TimelineElementGetLayerPriorityMethodInfo
ResolveVideoSourceMethod "getMarkerList" o = GES.MetaContainer.MetaContainerGetMarkerListMethodInfo
ResolveVideoSourceMethod "getMaxDuration" o = GES.TimelineElement.TimelineElementGetMaxDurationMethodInfo
ResolveVideoSourceMethod "getMeta" o = GES.MetaContainer.MetaContainerGetMetaMethodInfo
ResolveVideoSourceMethod "getName" o = GES.TimelineElement.TimelineElementGetNameMethodInfo
ResolveVideoSourceMethod "getNaturalFramerate" o = GES.TimelineElement.TimelineElementGetNaturalFramerateMethodInfo
ResolveVideoSourceMethod "getNaturalSize" o = VideoSourceGetNaturalSizeMethodInfo
ResolveVideoSourceMethod "getNleobject" o = GES.TrackElement.TrackElementGetNleobjectMethodInfo
ResolveVideoSourceMethod "getParent" o = GES.TimelineElement.TimelineElementGetParentMethodInfo
ResolveVideoSourceMethod "getPriority" o = GES.TimelineElement.TimelineElementGetPriorityMethodInfo
ResolveVideoSourceMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveVideoSourceMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveVideoSourceMethod "getStart" o = GES.TimelineElement.TimelineElementGetStartMethodInfo
ResolveVideoSourceMethod "getString" o = GES.MetaContainer.MetaContainerGetStringMethodInfo
ResolveVideoSourceMethod "getTimeline" o = GES.TimelineElement.TimelineElementGetTimelineMethodInfo
ResolveVideoSourceMethod "getToplevelParent" o = GES.TimelineElement.TimelineElementGetToplevelParentMethodInfo
ResolveVideoSourceMethod "getTrack" o = GES.TrackElement.TrackElementGetTrackMethodInfo
ResolveVideoSourceMethod "getTrackType" o = GES.TrackElement.TrackElementGetTrackTypeMethodInfo
ResolveVideoSourceMethod "getTrackTypes" o = GES.TimelineElement.TimelineElementGetTrackTypesMethodInfo
ResolveVideoSourceMethod "getUint" o = GES.MetaContainer.MetaContainerGetUintMethodInfo
ResolveVideoSourceMethod "getUint64" o = GES.MetaContainer.MetaContainerGetUint64MethodInfo
ResolveVideoSourceMethod "setActive" o = GES.TrackElement.TrackElementSetActiveMethodInfo
ResolveVideoSourceMethod "setAsset" o = GES.Extractable.ExtractableSetAssetMethodInfo
ResolveVideoSourceMethod "setAutoClampControlSources" o = GES.TrackElement.TrackElementSetAutoClampControlSourcesMethodInfo
ResolveVideoSourceMethod "setBoolean" o = GES.MetaContainer.MetaContainerSetBooleanMethodInfo
ResolveVideoSourceMethod "setChildProperty" o = GES.TimelineElement.TimelineElementSetChildPropertyMethodInfo
ResolveVideoSourceMethod "setChildPropertyByPspec" o = GES.TimelineElement.TimelineElementSetChildPropertyByPspecMethodInfo
ResolveVideoSourceMethod "setChildPropertyFull" o = GES.TimelineElement.TimelineElementSetChildPropertyFullMethodInfo
ResolveVideoSourceMethod "setControlSource" o = GES.TrackElement.TrackElementSetControlSourceMethodInfo
ResolveVideoSourceMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveVideoSourceMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveVideoSourceMethod "setDate" o = GES.MetaContainer.MetaContainerSetDateMethodInfo
ResolveVideoSourceMethod "setDateTime" o = GES.MetaContainer.MetaContainerSetDateTimeMethodInfo
ResolveVideoSourceMethod "setDouble" o = GES.MetaContainer.MetaContainerSetDoubleMethodInfo
ResolveVideoSourceMethod "setDuration" o = GES.TimelineElement.TimelineElementSetDurationMethodInfo
ResolveVideoSourceMethod "setFloat" o = GES.MetaContainer.MetaContainerSetFloatMethodInfo
ResolveVideoSourceMethod "setHasInternalSource" o = GES.TrackElement.TrackElementSetHasInternalSourceMethodInfo
ResolveVideoSourceMethod "setInpoint" o = GES.TimelineElement.TimelineElementSetInpointMethodInfo
ResolveVideoSourceMethod "setInt" o = GES.MetaContainer.MetaContainerSetIntMethodInfo
ResolveVideoSourceMethod "setInt64" o = GES.MetaContainer.MetaContainerSetInt64MethodInfo
ResolveVideoSourceMethod "setMarkerList" o = GES.MetaContainer.MetaContainerSetMarkerListMethodInfo
ResolveVideoSourceMethod "setMaxDuration" o = GES.TimelineElement.TimelineElementSetMaxDurationMethodInfo
ResolveVideoSourceMethod "setMeta" o = GES.MetaContainer.MetaContainerSetMetaMethodInfo
ResolveVideoSourceMethod "setName" o = GES.TimelineElement.TimelineElementSetNameMethodInfo
ResolveVideoSourceMethod "setParent" o = GES.TimelineElement.TimelineElementSetParentMethodInfo
ResolveVideoSourceMethod "setPriority" o = GES.TimelineElement.TimelineElementSetPriorityMethodInfo
ResolveVideoSourceMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveVideoSourceMethod "setStart" o = GES.TimelineElement.TimelineElementSetStartMethodInfo
ResolveVideoSourceMethod "setString" o = GES.MetaContainer.MetaContainerSetStringMethodInfo
ResolveVideoSourceMethod "setTimeline" o = GES.TimelineElement.TimelineElementSetTimelineMethodInfo
ResolveVideoSourceMethod "setTrackType" o = GES.TrackElement.TrackElementSetTrackTypeMethodInfo
ResolveVideoSourceMethod "setUint" o = GES.MetaContainer.MetaContainerSetUintMethodInfo
ResolveVideoSourceMethod "setUint64" o = GES.MetaContainer.MetaContainerSetUint64MethodInfo
ResolveVideoSourceMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveVideoSourceMethod t VideoSource, O.OverloadedMethod info VideoSource p) => OL.IsLabel t (VideoSource -> 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 ~ ResolveVideoSourceMethod t VideoSource, O.OverloadedMethod info VideoSource p, R.HasField t VideoSource p) => R.HasField t VideoSource p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveVideoSourceMethod t VideoSource, O.OverloadedMethodInfo info VideoSource) => OL.IsLabel t (O.MethodProxy info VideoSource) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList VideoSource
type instance O.AttributeList VideoSource = VideoSourceAttributeList
type VideoSourceAttributeList = ('[ '("active", GES.TrackElement.TrackElementActivePropertyInfo), '("autoClampControlSources", GES.TrackElement.TrackElementAutoClampControlSourcesPropertyInfo), '("duration", GES.TimelineElement.TimelineElementDurationPropertyInfo), '("hasInternalSource", GES.TrackElement.TrackElementHasInternalSourcePropertyInfo), '("inPoint", GES.TimelineElement.TimelineElementInPointPropertyInfo), '("maxDuration", GES.TimelineElement.TimelineElementMaxDurationPropertyInfo), '("name", GES.TimelineElement.TimelineElementNamePropertyInfo), '("parent", GES.TimelineElement.TimelineElementParentPropertyInfo), '("priority", GES.TimelineElement.TimelineElementPriorityPropertyInfo), '("serialize", GES.TimelineElement.TimelineElementSerializePropertyInfo), '("start", GES.TimelineElement.TimelineElementStartPropertyInfo), '("timeline", GES.TimelineElement.TimelineElementTimelinePropertyInfo), '("track", GES.TrackElement.TrackElementTrackPropertyInfo), '("trackType", GES.TrackElement.TrackElementTrackTypePropertyInfo)] :: [(Symbol, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList VideoSource = VideoSourceSignalList
type VideoSourceSignalList = ('[ '("childPropertyAdded", GES.TimelineElement.TimelineElementChildPropertyAddedSignalInfo), '("childPropertyRemoved", GES.TimelineElement.TimelineElementChildPropertyRemovedSignalInfo), '("controlBindingAdded", GES.TrackElement.TrackElementControlBindingAddedSignalInfo), '("controlBindingRemoved", GES.TrackElement.TrackElementControlBindingRemovedSignalInfo), '("deepNotify", GES.TimelineElement.TimelineElementDeepNotifySignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("notifyMeta", GES.MetaContainer.MetaContainerNotifyMetaSignalInfo)] :: [(Symbol, DK.Type)])
#endif
foreign import ccall "ges_video_source_get_natural_size" ges_video_source_get_natural_size ::
Ptr VideoSource ->
Ptr Int32 ->
Ptr Int32 ->
IO CInt
videoSourceGetNaturalSize ::
(B.CallStack.HasCallStack, MonadIO m, IsVideoSource a) =>
a
-> m ((Bool, Int32, Int32))
videoSourceGetNaturalSize :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsVideoSource a) =>
a -> m (Bool, Int32, Int32)
videoSourceGetNaturalSize a
self = IO (Bool, Int32, Int32) -> m (Bool, Int32, Int32)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, Int32, Int32) -> m (Bool, Int32, Int32))
-> IO (Bool, Int32, Int32) -> m (Bool, Int32, Int32)
forall a b. (a -> b) -> a -> b
$ do
Ptr VideoSource
self' <- a -> IO (Ptr VideoSource)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
Ptr Int32
width <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
Ptr Int32
height <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
CInt
result <- Ptr VideoSource -> Ptr Int32 -> Ptr Int32 -> IO CInt
ges_video_source_get_natural_size Ptr VideoSource
self' Ptr Int32
width Ptr Int32
height
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
Int32
width' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
width
Int32
height' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
height
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
width
Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
height
(Bool, Int32, Int32) -> IO (Bool, Int32, Int32)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', Int32
width', Int32
height')
#if defined(ENABLE_OVERLOADING)
data VideoSourceGetNaturalSizeMethodInfo
instance (signature ~ (m ((Bool, Int32, Int32))), MonadIO m, IsVideoSource a) => O.OverloadedMethod VideoSourceGetNaturalSizeMethodInfo a signature where
overloadedMethod = videoSourceGetNaturalSize
instance O.OverloadedMethodInfo VideoSourceGetNaturalSizeMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GES.Objects.VideoSource.videoSourceGetNaturalSize",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.4/docs/GI-GES-Objects-VideoSource.html#v:videoSourceGetNaturalSize"
})
#endif