{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.GES.Objects.ClipAsset
(
ClipAsset(..) ,
IsClipAsset ,
toClipAsset ,
#if defined(ENABLE_OVERLOADING)
ResolveClipAssetMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
ClipAssetGetFrameTimeMethodInfo ,
#endif
clipAssetGetFrameTime ,
#if defined(ENABLE_OVERLOADING)
ClipAssetGetNaturalFramerateMethodInfo ,
#endif
clipAssetGetNaturalFramerate ,
#if defined(ENABLE_OVERLOADING)
ClipAssetGetSupportedFormatsMethodInfo ,
#endif
clipAssetGetSupportedFormats ,
#if defined(ENABLE_OVERLOADING)
ClipAssetSetSupportedFormatsMethodInfo ,
#endif
clipAssetSetSupportedFormats ,
#if defined(ENABLE_OVERLOADING)
ClipAssetSupportedFormatsPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
clipAssetSupportedFormats ,
#endif
constructClipAssetSupportedFormats ,
getClipAssetSupportedFormats ,
setClipAssetSupportedFormats ,
) 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.Flags as GES.Flags
import {-# SOURCE #-} qualified GI.GES.Interfaces.MetaContainer as GES.MetaContainer
import {-# SOURCE #-} qualified GI.GES.Objects.Asset as GES.Asset
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gio.Interfaces.AsyncInitable as Gio.AsyncInitable
import qualified GI.Gio.Interfaces.Initable as Gio.Initable
newtype ClipAsset = ClipAsset (SP.ManagedPtr ClipAsset)
deriving (ClipAsset -> ClipAsset -> Bool
(ClipAsset -> ClipAsset -> Bool)
-> (ClipAsset -> ClipAsset -> Bool) -> Eq ClipAsset
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ClipAsset -> ClipAsset -> Bool
== :: ClipAsset -> ClipAsset -> Bool
$c/= :: ClipAsset -> ClipAsset -> Bool
/= :: ClipAsset -> ClipAsset -> Bool
Eq)
instance SP.ManagedPtrNewtype ClipAsset where
toManagedPtr :: ClipAsset -> ManagedPtr ClipAsset
toManagedPtr (ClipAsset ManagedPtr ClipAsset
p) = ManagedPtr ClipAsset
p
foreign import ccall "ges_clip_asset_get_type"
c_ges_clip_asset_get_type :: IO B.Types.GType
instance B.Types.TypedObject ClipAsset where
glibType :: IO GType
glibType = IO GType
c_ges_clip_asset_get_type
instance B.Types.GObject ClipAsset
class (SP.GObject o, O.IsDescendantOf ClipAsset o) => IsClipAsset o
instance (SP.GObject o, O.IsDescendantOf ClipAsset o) => IsClipAsset o
instance O.HasParentTypes ClipAsset
type instance O.ParentTypes ClipAsset = '[GES.Asset.Asset, GObject.Object.Object, GES.MetaContainer.MetaContainer, Gio.AsyncInitable.AsyncInitable, Gio.Initable.Initable]
toClipAsset :: (MIO.MonadIO m, IsClipAsset o) => o -> m ClipAsset
toClipAsset :: forall (m :: * -> *) o.
(MonadIO m, IsClipAsset o) =>
o -> m ClipAsset
toClipAsset = IO ClipAsset -> m ClipAsset
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO ClipAsset -> m ClipAsset)
-> (o -> IO ClipAsset) -> o -> m ClipAsset
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr ClipAsset -> ClipAsset) -> o -> IO ClipAsset
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr ClipAsset -> ClipAsset
ClipAsset
instance B.GValue.IsGValue (Maybe ClipAsset) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_ges_clip_asset_get_type
gvalueSet_ :: Ptr GValue -> Maybe ClipAsset -> IO ()
gvalueSet_ Ptr GValue
gv Maybe ClipAsset
P.Nothing = Ptr GValue -> Ptr ClipAsset -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr ClipAsset
forall a. Ptr a
FP.nullPtr :: FP.Ptr ClipAsset)
gvalueSet_ Ptr GValue
gv (P.Just ClipAsset
obj) = ClipAsset -> (Ptr ClipAsset -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr ClipAsset
obj (Ptr GValue -> Ptr ClipAsset -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe ClipAsset)
gvalueGet_ Ptr GValue
gv = do
Ptr ClipAsset
ptr <- Ptr GValue -> IO (Ptr ClipAsset)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr ClipAsset)
if Ptr ClipAsset
ptr Ptr ClipAsset -> Ptr ClipAsset -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr ClipAsset
forall a. Ptr a
FP.nullPtr
then ClipAsset -> Maybe ClipAsset
forall a. a -> Maybe a
P.Just (ClipAsset -> Maybe ClipAsset)
-> IO ClipAsset -> IO (Maybe ClipAsset)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr ClipAsset -> ClipAsset)
-> Ptr ClipAsset -> IO ClipAsset
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr ClipAsset -> ClipAsset
ClipAsset Ptr ClipAsset
ptr
else Maybe ClipAsset -> IO (Maybe ClipAsset)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ClipAsset
forall a. Maybe a
P.Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolveClipAssetMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolveClipAssetMethod "addMetasFromString" o = GES.MetaContainer.MetaContainerAddMetasFromStringMethodInfo
ResolveClipAssetMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveClipAssetMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveClipAssetMethod "checkMetaRegistered" o = GES.MetaContainer.MetaContainerCheckMetaRegisteredMethodInfo
ResolveClipAssetMethod "extract" o = GES.Asset.AssetExtractMethodInfo
ResolveClipAssetMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveClipAssetMethod "foreach" o = GES.MetaContainer.MetaContainerForeachMethodInfo
ResolveClipAssetMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveClipAssetMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveClipAssetMethod "init" o = Gio.Initable.InitableInitMethodInfo
ResolveClipAssetMethod "initAsync" o = Gio.AsyncInitable.AsyncInitableInitAsyncMethodInfo
ResolveClipAssetMethod "initFinish" o = Gio.AsyncInitable.AsyncInitableInitFinishMethodInfo
ResolveClipAssetMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveClipAssetMethod "listProxies" o = GES.Asset.AssetListProxiesMethodInfo
ResolveClipAssetMethod "metasToString" o = GES.MetaContainer.MetaContainerMetasToStringMethodInfo
ResolveClipAssetMethod "newFinish" o = Gio.AsyncInitable.AsyncInitableNewFinishMethodInfo
ResolveClipAssetMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveClipAssetMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveClipAssetMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveClipAssetMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveClipAssetMethod "registerMeta" o = GES.MetaContainer.MetaContainerRegisterMetaMethodInfo
ResolveClipAssetMethod "registerMetaBoolean" o = GES.MetaContainer.MetaContainerRegisterMetaBooleanMethodInfo
ResolveClipAssetMethod "registerMetaDate" o = GES.MetaContainer.MetaContainerRegisterMetaDateMethodInfo
ResolveClipAssetMethod "registerMetaDateTime" o = GES.MetaContainer.MetaContainerRegisterMetaDateTimeMethodInfo
ResolveClipAssetMethod "registerMetaDouble" o = GES.MetaContainer.MetaContainerRegisterMetaDoubleMethodInfo
ResolveClipAssetMethod "registerMetaFloat" o = GES.MetaContainer.MetaContainerRegisterMetaFloatMethodInfo
ResolveClipAssetMethod "registerMetaInt" o = GES.MetaContainer.MetaContainerRegisterMetaIntMethodInfo
ResolveClipAssetMethod "registerMetaInt64" o = GES.MetaContainer.MetaContainerRegisterMetaInt64MethodInfo
ResolveClipAssetMethod "registerMetaString" o = GES.MetaContainer.MetaContainerRegisterMetaStringMethodInfo
ResolveClipAssetMethod "registerMetaUint" o = GES.MetaContainer.MetaContainerRegisterMetaUintMethodInfo
ResolveClipAssetMethod "registerMetaUint64" o = GES.MetaContainer.MetaContainerRegisterMetaUint64MethodInfo
ResolveClipAssetMethod "registerStaticMeta" o = GES.MetaContainer.MetaContainerRegisterStaticMetaMethodInfo
ResolveClipAssetMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveClipAssetMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveClipAssetMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveClipAssetMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveClipAssetMethod "unproxy" o = GES.Asset.AssetUnproxyMethodInfo
ResolveClipAssetMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveClipAssetMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveClipAssetMethod "getBoolean" o = GES.MetaContainer.MetaContainerGetBooleanMethodInfo
ResolveClipAssetMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveClipAssetMethod "getDate" o = GES.MetaContainer.MetaContainerGetDateMethodInfo
ResolveClipAssetMethod "getDateTime" o = GES.MetaContainer.MetaContainerGetDateTimeMethodInfo
ResolveClipAssetMethod "getDouble" o = GES.MetaContainer.MetaContainerGetDoubleMethodInfo
ResolveClipAssetMethod "getError" o = GES.Asset.AssetGetErrorMethodInfo
ResolveClipAssetMethod "getExtractableType" o = GES.Asset.AssetGetExtractableTypeMethodInfo
ResolveClipAssetMethod "getFloat" o = GES.MetaContainer.MetaContainerGetFloatMethodInfo
ResolveClipAssetMethod "getFrameTime" o = ClipAssetGetFrameTimeMethodInfo
ResolveClipAssetMethod "getId" o = GES.Asset.AssetGetIdMethodInfo
ResolveClipAssetMethod "getInt" o = GES.MetaContainer.MetaContainerGetIntMethodInfo
ResolveClipAssetMethod "getInt64" o = GES.MetaContainer.MetaContainerGetInt64MethodInfo
ResolveClipAssetMethod "getMarkerList" o = GES.MetaContainer.MetaContainerGetMarkerListMethodInfo
ResolveClipAssetMethod "getMeta" o = GES.MetaContainer.MetaContainerGetMetaMethodInfo
ResolveClipAssetMethod "getNaturalFramerate" o = ClipAssetGetNaturalFramerateMethodInfo
ResolveClipAssetMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveClipAssetMethod "getProxy" o = GES.Asset.AssetGetProxyMethodInfo
ResolveClipAssetMethod "getProxyTarget" o = GES.Asset.AssetGetProxyTargetMethodInfo
ResolveClipAssetMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveClipAssetMethod "getString" o = GES.MetaContainer.MetaContainerGetStringMethodInfo
ResolveClipAssetMethod "getSupportedFormats" o = ClipAssetGetSupportedFormatsMethodInfo
ResolveClipAssetMethod "getUint" o = GES.MetaContainer.MetaContainerGetUintMethodInfo
ResolveClipAssetMethod "getUint64" o = GES.MetaContainer.MetaContainerGetUint64MethodInfo
ResolveClipAssetMethod "setBoolean" o = GES.MetaContainer.MetaContainerSetBooleanMethodInfo
ResolveClipAssetMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveClipAssetMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveClipAssetMethod "setDate" o = GES.MetaContainer.MetaContainerSetDateMethodInfo
ResolveClipAssetMethod "setDateTime" o = GES.MetaContainer.MetaContainerSetDateTimeMethodInfo
ResolveClipAssetMethod "setDouble" o = GES.MetaContainer.MetaContainerSetDoubleMethodInfo
ResolveClipAssetMethod "setFloat" o = GES.MetaContainer.MetaContainerSetFloatMethodInfo
ResolveClipAssetMethod "setInt" o = GES.MetaContainer.MetaContainerSetIntMethodInfo
ResolveClipAssetMethod "setInt64" o = GES.MetaContainer.MetaContainerSetInt64MethodInfo
ResolveClipAssetMethod "setMarkerList" o = GES.MetaContainer.MetaContainerSetMarkerListMethodInfo
ResolveClipAssetMethod "setMeta" o = GES.MetaContainer.MetaContainerSetMetaMethodInfo
ResolveClipAssetMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveClipAssetMethod "setProxy" o = GES.Asset.AssetSetProxyMethodInfo
ResolveClipAssetMethod "setString" o = GES.MetaContainer.MetaContainerSetStringMethodInfo
ResolveClipAssetMethod "setSupportedFormats" o = ClipAssetSetSupportedFormatsMethodInfo
ResolveClipAssetMethod "setUint" o = GES.MetaContainer.MetaContainerSetUintMethodInfo
ResolveClipAssetMethod "setUint64" o = GES.MetaContainer.MetaContainerSetUint64MethodInfo
ResolveClipAssetMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveClipAssetMethod t ClipAsset, O.OverloadedMethod info ClipAsset p) => OL.IsLabel t (ClipAsset -> 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 ~ ResolveClipAssetMethod t ClipAsset, O.OverloadedMethod info ClipAsset p, R.HasField t ClipAsset p) => R.HasField t ClipAsset p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveClipAssetMethod t ClipAsset, O.OverloadedMethodInfo info ClipAsset) => OL.IsLabel t (O.MethodProxy info ClipAsset) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif
getClipAssetSupportedFormats :: (MonadIO m, IsClipAsset o) => o -> m [GES.Flags.TrackType]
getClipAssetSupportedFormats :: forall (m :: * -> *) o.
(MonadIO m, IsClipAsset o) =>
o -> m [TrackType]
getClipAssetSupportedFormats o
obj = IO [TrackType] -> m [TrackType]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO [TrackType] -> m [TrackType])
-> IO [TrackType] -> m [TrackType]
forall a b. (a -> b) -> a -> b
$ o -> String -> IO [TrackType]
forall a b.
(GObject a, IsGFlag b, BoxedFlags b) =>
a -> String -> IO [b]
B.Properties.getObjectPropertyFlags o
obj String
"supported-formats"
setClipAssetSupportedFormats :: (MonadIO m, IsClipAsset o) => o -> [GES.Flags.TrackType] -> m ()
setClipAssetSupportedFormats :: forall (m :: * -> *) o.
(MonadIO m, IsClipAsset o) =>
o -> [TrackType] -> m ()
setClipAssetSupportedFormats o
obj [TrackType]
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 -> [TrackType] -> IO ()
forall a b.
(IsGFlag b, BoxedFlags b, GObject a) =>
a -> String -> [b] -> IO ()
B.Properties.setObjectPropertyFlags o
obj String
"supported-formats" [TrackType]
val
constructClipAssetSupportedFormats :: (IsClipAsset o, MIO.MonadIO m) => [GES.Flags.TrackType] -> m (GValueConstruct o)
constructClipAssetSupportedFormats :: forall o (m :: * -> *).
(IsClipAsset o, MonadIO m) =>
[TrackType] -> m (GValueConstruct o)
constructClipAssetSupportedFormats [TrackType]
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 -> [TrackType] -> IO (GValueConstruct o)
forall a o.
(IsGFlag a, BoxedFlags a) =>
String -> [a] -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyFlags String
"supported-formats" [TrackType]
val
#if defined(ENABLE_OVERLOADING)
data ClipAssetSupportedFormatsPropertyInfo
instance AttrInfo ClipAssetSupportedFormatsPropertyInfo where
type AttrAllowedOps ClipAssetSupportedFormatsPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint ClipAssetSupportedFormatsPropertyInfo = IsClipAsset
type AttrSetTypeConstraint ClipAssetSupportedFormatsPropertyInfo = (~) [GES.Flags.TrackType]
type AttrTransferTypeConstraint ClipAssetSupportedFormatsPropertyInfo = (~) [GES.Flags.TrackType]
type AttrTransferType ClipAssetSupportedFormatsPropertyInfo = [GES.Flags.TrackType]
type AttrGetType ClipAssetSupportedFormatsPropertyInfo = [GES.Flags.TrackType]
type AttrLabel ClipAssetSupportedFormatsPropertyInfo = "supported-formats"
type AttrOrigin ClipAssetSupportedFormatsPropertyInfo = ClipAsset
attrGet = getClipAssetSupportedFormats
attrSet = setClipAssetSupportedFormats
attrTransfer _ v = do
return v
attrConstruct = constructClipAssetSupportedFormats
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GES.Objects.ClipAsset.supportedFormats"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.4/docs/GI-GES-Objects-ClipAsset.html#g:attr:supportedFormats"
})
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList ClipAsset
type instance O.AttributeList ClipAsset = ClipAssetAttributeList
type ClipAssetAttributeList = ('[ '("extractableType", GES.Asset.AssetExtractableTypePropertyInfo), '("id", GES.Asset.AssetIdPropertyInfo), '("proxy", GES.Asset.AssetProxyPropertyInfo), '("proxyTarget", GES.Asset.AssetProxyTargetPropertyInfo), '("supportedFormats", ClipAssetSupportedFormatsPropertyInfo)] :: [(Symbol, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
clipAssetSupportedFormats :: AttrLabelProxy "supportedFormats"
clipAssetSupportedFormats = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList ClipAsset = ClipAssetSignalList
type ClipAssetSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo), '("notifyMeta", GES.MetaContainer.MetaContainerNotifyMetaSignalInfo)] :: [(Symbol, DK.Type)])
#endif
foreign import ccall "ges_clip_asset_get_frame_time" ges_clip_asset_get_frame_time ::
Ptr ClipAsset ->
Int64 ->
IO Word64
clipAssetGetFrameTime ::
(B.CallStack.HasCallStack, MonadIO m, IsClipAsset a) =>
a
-> Int64
-> m Word64
clipAssetGetFrameTime :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsClipAsset a) =>
a -> Int64 -> m Word64
clipAssetGetFrameTime a
self Int64
frameNumber = IO Word64 -> m Word64
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word64 -> m Word64) -> IO Word64 -> m Word64
forall a b. (a -> b) -> a -> b
$ do
Ptr ClipAsset
self' <- a -> IO (Ptr ClipAsset)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
Word64
result <- Ptr ClipAsset -> Int64 -> IO Word64
ges_clip_asset_get_frame_time Ptr ClipAsset
self' Int64
frameNumber
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
Word64 -> IO Word64
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word64
result
#if defined(ENABLE_OVERLOADING)
data ClipAssetGetFrameTimeMethodInfo
instance (signature ~ (Int64 -> m Word64), MonadIO m, IsClipAsset a) => O.OverloadedMethod ClipAssetGetFrameTimeMethodInfo a signature where
overloadedMethod = clipAssetGetFrameTime
instance O.OverloadedMethodInfo ClipAssetGetFrameTimeMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GES.Objects.ClipAsset.clipAssetGetFrameTime",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.4/docs/GI-GES-Objects-ClipAsset.html#v:clipAssetGetFrameTime"
})
#endif
foreign import ccall "ges_clip_asset_get_natural_framerate" ges_clip_asset_get_natural_framerate ::
Ptr ClipAsset ->
Ptr Int32 ->
Ptr Int32 ->
IO CInt
clipAssetGetNaturalFramerate ::
(B.CallStack.HasCallStack, MonadIO m, IsClipAsset a) =>
a
-> m ((Bool, Int32, Int32))
clipAssetGetNaturalFramerate :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsClipAsset a) =>
a -> m (Bool, Int32, Int32)
clipAssetGetNaturalFramerate 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 ClipAsset
self' <- a -> IO (Ptr ClipAsset)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
Ptr Int32
framerateN <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
Ptr Int32
framerateD <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
CInt
result <- Ptr ClipAsset -> Ptr Int32 -> Ptr Int32 -> IO CInt
ges_clip_asset_get_natural_framerate Ptr ClipAsset
self' Ptr Int32
framerateN Ptr Int32
framerateD
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
Int32
framerateN' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
framerateN
Int32
framerateD' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
framerateD
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
framerateN
Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
framerateD
(Bool, Int32, Int32) -> IO (Bool, Int32, Int32)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', Int32
framerateN', Int32
framerateD')
#if defined(ENABLE_OVERLOADING)
data ClipAssetGetNaturalFramerateMethodInfo
instance (signature ~ (m ((Bool, Int32, Int32))), MonadIO m, IsClipAsset a) => O.OverloadedMethod ClipAssetGetNaturalFramerateMethodInfo a signature where
overloadedMethod = clipAssetGetNaturalFramerate
instance O.OverloadedMethodInfo ClipAssetGetNaturalFramerateMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GES.Objects.ClipAsset.clipAssetGetNaturalFramerate",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.4/docs/GI-GES-Objects-ClipAsset.html#v:clipAssetGetNaturalFramerate"
})
#endif
foreign import ccall "ges_clip_asset_get_supported_formats" ges_clip_asset_get_supported_formats ::
Ptr ClipAsset ->
IO CUInt
clipAssetGetSupportedFormats ::
(B.CallStack.HasCallStack, MonadIO m, IsClipAsset a) =>
a
-> m [GES.Flags.TrackType]
clipAssetGetSupportedFormats :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsClipAsset a) =>
a -> m [TrackType]
clipAssetGetSupportedFormats a
self = IO [TrackType] -> m [TrackType]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [TrackType] -> m [TrackType])
-> IO [TrackType] -> m [TrackType]
forall a b. (a -> b) -> a -> b
$ do
Ptr ClipAsset
self' <- a -> IO (Ptr ClipAsset)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
CUInt
result <- Ptr ClipAsset -> IO CUInt
ges_clip_asset_get_supported_formats Ptr ClipAsset
self'
let result' :: [TrackType]
result' = CUInt -> [TrackType]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
[TrackType] -> IO [TrackType]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [TrackType]
result'
#if defined(ENABLE_OVERLOADING)
data ClipAssetGetSupportedFormatsMethodInfo
instance (signature ~ (m [GES.Flags.TrackType]), MonadIO m, IsClipAsset a) => O.OverloadedMethod ClipAssetGetSupportedFormatsMethodInfo a signature where
overloadedMethod = clipAssetGetSupportedFormats
instance O.OverloadedMethodInfo ClipAssetGetSupportedFormatsMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GES.Objects.ClipAsset.clipAssetGetSupportedFormats",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.4/docs/GI-GES-Objects-ClipAsset.html#v:clipAssetGetSupportedFormats"
})
#endif
foreign import ccall "ges_clip_asset_set_supported_formats" ges_clip_asset_set_supported_formats ::
Ptr ClipAsset ->
CUInt ->
IO ()
clipAssetSetSupportedFormats ::
(B.CallStack.HasCallStack, MonadIO m, IsClipAsset a) =>
a
-> [GES.Flags.TrackType]
-> m ()
clipAssetSetSupportedFormats :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsClipAsset a) =>
a -> [TrackType] -> m ()
clipAssetSetSupportedFormats a
self [TrackType]
supportedformats = 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 ClipAsset
self' <- a -> IO (Ptr ClipAsset)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
let supportedformats' :: CUInt
supportedformats' = [TrackType] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [TrackType]
supportedformats
Ptr ClipAsset -> CUInt -> IO ()
ges_clip_asset_set_supported_formats Ptr ClipAsset
self' CUInt
supportedformats'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ClipAssetSetSupportedFormatsMethodInfo
instance (signature ~ ([GES.Flags.TrackType] -> m ()), MonadIO m, IsClipAsset a) => O.OverloadedMethod ClipAssetSetSupportedFormatsMethodInfo a signature where
overloadedMethod = clipAssetSetSupportedFormats
instance O.OverloadedMethodInfo ClipAssetSetSupportedFormatsMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GES.Objects.ClipAsset.clipAssetSetSupportedFormats",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.4/docs/GI-GES-Objects-ClipAsset.html#v:clipAssetSetSupportedFormats"
})
#endif