{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.GES.Objects.UriClipAsset
(
UriClipAsset(..) ,
IsUriClipAsset ,
toUriClipAsset ,
#if defined(ENABLE_OVERLOADING)
ResolveUriClipAssetMethod ,
#endif
uriClipAssetFinish ,
#if defined(ENABLE_OVERLOADING)
UriClipAssetGetDurationMethodInfo ,
#endif
uriClipAssetGetDuration ,
#if defined(ENABLE_OVERLOADING)
UriClipAssetGetInfoMethodInfo ,
#endif
uriClipAssetGetInfo ,
#if defined(ENABLE_OVERLOADING)
UriClipAssetGetMaxDurationMethodInfo ,
#endif
uriClipAssetGetMaxDuration ,
#if defined(ENABLE_OVERLOADING)
UriClipAssetGetStreamAssetsMethodInfo ,
#endif
uriClipAssetGetStreamAssets ,
#if defined(ENABLE_OVERLOADING)
UriClipAssetIsImageMethodInfo ,
#endif
uriClipAssetIsImage ,
uriClipAssetNew ,
uriClipAssetRequestSync ,
#if defined(ENABLE_OVERLOADING)
UriClipAssetDurationPropertyInfo ,
#endif
constructUriClipAssetDuration ,
getUriClipAssetDuration ,
setUriClipAssetDuration ,
#if defined(ENABLE_OVERLOADING)
uriClipAssetDuration ,
#endif
#if defined(ENABLE_OVERLOADING)
UriClipAssetIsNestedTimelinePropertyInfo,
#endif
getUriClipAssetIsNestedTimeline ,
#if defined(ENABLE_OVERLOADING)
uriClipAssetIsNestedTimeline ,
#endif
) where
import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P
import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R
import {-# SOURCE #-} qualified GI.GES.Interfaces.MetaContainer as GES.MetaContainer
import {-# SOURCE #-} qualified GI.GES.Objects.Asset as GES.Asset
import {-# SOURCE #-} qualified GI.GES.Objects.ClipAsset as GES.ClipAsset
import {-# SOURCE #-} qualified GI.GES.Objects.SourceClipAsset as GES.SourceClipAsset
import {-# SOURCE #-} qualified GI.GES.Objects.UriSourceAsset as GES.UriSourceAsset
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gio.Callbacks as Gio.Callbacks
import qualified GI.Gio.Interfaces.AsyncInitable as Gio.AsyncInitable
import qualified GI.Gio.Interfaces.AsyncResult as Gio.AsyncResult
import qualified GI.Gio.Interfaces.Initable as Gio.Initable
import qualified GI.Gio.Objects.Cancellable as Gio.Cancellable
import qualified GI.GstPbutils.Objects.DiscovererInfo as GstPbutils.DiscovererInfo
newtype UriClipAsset = UriClipAsset (SP.ManagedPtr UriClipAsset)
deriving (UriClipAsset -> UriClipAsset -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UriClipAsset -> UriClipAsset -> Bool
$c/= :: UriClipAsset -> UriClipAsset -> Bool
== :: UriClipAsset -> UriClipAsset -> Bool
$c== :: UriClipAsset -> UriClipAsset -> Bool
Eq)
instance SP.ManagedPtrNewtype UriClipAsset where
toManagedPtr :: UriClipAsset -> ManagedPtr UriClipAsset
toManagedPtr (UriClipAsset ManagedPtr UriClipAsset
p) = ManagedPtr UriClipAsset
p
foreign import ccall "ges_uri_clip_asset_get_type"
c_ges_uri_clip_asset_get_type :: IO B.Types.GType
instance B.Types.TypedObject UriClipAsset where
glibType :: IO GType
glibType = IO GType
c_ges_uri_clip_asset_get_type
instance B.Types.GObject UriClipAsset
class (SP.GObject o, O.IsDescendantOf UriClipAsset o) => IsUriClipAsset o
instance (SP.GObject o, O.IsDescendantOf UriClipAsset o) => IsUriClipAsset o
instance O.HasParentTypes UriClipAsset
type instance O.ParentTypes UriClipAsset = '[GES.SourceClipAsset.SourceClipAsset, GES.ClipAsset.ClipAsset, GES.Asset.Asset, GObject.Object.Object, GES.MetaContainer.MetaContainer, Gio.AsyncInitable.AsyncInitable, Gio.Initable.Initable]
toUriClipAsset :: (MIO.MonadIO m, IsUriClipAsset o) => o -> m UriClipAsset
toUriClipAsset :: forall (m :: * -> *) o.
(MonadIO m, IsUriClipAsset o) =>
o -> m UriClipAsset
toUriClipAsset = forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr UriClipAsset -> UriClipAsset
UriClipAsset
instance B.GValue.IsGValue (Maybe UriClipAsset) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_ges_uri_clip_asset_get_type
gvalueSet_ :: Ptr GValue -> Maybe UriClipAsset -> IO ()
gvalueSet_ Ptr GValue
gv Maybe UriClipAsset
P.Nothing = forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (forall a. Ptr a
FP.nullPtr :: FP.Ptr UriClipAsset)
gvalueSet_ Ptr GValue
gv (P.Just UriClipAsset
obj) = forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr UriClipAsset
obj (forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe UriClipAsset)
gvalueGet_ Ptr GValue
gv = do
Ptr UriClipAsset
ptr <- forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr UriClipAsset)
if Ptr UriClipAsset
ptr forall a. Eq a => a -> a -> Bool
/= forall a. Ptr a
FP.nullPtr
then forall a. a -> Maybe a
P.Just forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr UriClipAsset -> UriClipAsset
UriClipAsset Ptr UriClipAsset
ptr
else forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
P.Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolveUriClipAssetMethod (t :: Symbol) (o :: *) :: * where
ResolveUriClipAssetMethod "addMetasFromString" o = GES.MetaContainer.MetaContainerAddMetasFromStringMethodInfo
ResolveUriClipAssetMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveUriClipAssetMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveUriClipAssetMethod "checkMetaRegistered" o = GES.MetaContainer.MetaContainerCheckMetaRegisteredMethodInfo
ResolveUriClipAssetMethod "extract" o = GES.Asset.AssetExtractMethodInfo
ResolveUriClipAssetMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveUriClipAssetMethod "foreach" o = GES.MetaContainer.MetaContainerForeachMethodInfo
ResolveUriClipAssetMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveUriClipAssetMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveUriClipAssetMethod "init" o = Gio.Initable.InitableInitMethodInfo
ResolveUriClipAssetMethod "initAsync" o = Gio.AsyncInitable.AsyncInitableInitAsyncMethodInfo
ResolveUriClipAssetMethod "initFinish" o = Gio.AsyncInitable.AsyncInitableInitFinishMethodInfo
ResolveUriClipAssetMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveUriClipAssetMethod "isImage" o = UriClipAssetIsImageMethodInfo
ResolveUriClipAssetMethod "listProxies" o = GES.Asset.AssetListProxiesMethodInfo
ResolveUriClipAssetMethod "metasToString" o = GES.MetaContainer.MetaContainerMetasToStringMethodInfo
ResolveUriClipAssetMethod "newFinish" o = Gio.AsyncInitable.AsyncInitableNewFinishMethodInfo
ResolveUriClipAssetMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveUriClipAssetMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveUriClipAssetMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveUriClipAssetMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveUriClipAssetMethod "registerMeta" o = GES.MetaContainer.MetaContainerRegisterMetaMethodInfo
ResolveUriClipAssetMethod "registerMetaBoolean" o = GES.MetaContainer.MetaContainerRegisterMetaBooleanMethodInfo
ResolveUriClipAssetMethod "registerMetaDate" o = GES.MetaContainer.MetaContainerRegisterMetaDateMethodInfo
ResolveUriClipAssetMethod "registerMetaDateTime" o = GES.MetaContainer.MetaContainerRegisterMetaDateTimeMethodInfo
ResolveUriClipAssetMethod "registerMetaDouble" o = GES.MetaContainer.MetaContainerRegisterMetaDoubleMethodInfo
ResolveUriClipAssetMethod "registerMetaFloat" o = GES.MetaContainer.MetaContainerRegisterMetaFloatMethodInfo
ResolveUriClipAssetMethod "registerMetaInt" o = GES.MetaContainer.MetaContainerRegisterMetaIntMethodInfo
ResolveUriClipAssetMethod "registerMetaInt64" o = GES.MetaContainer.MetaContainerRegisterMetaInt64MethodInfo
ResolveUriClipAssetMethod "registerMetaString" o = GES.MetaContainer.MetaContainerRegisterMetaStringMethodInfo
ResolveUriClipAssetMethod "registerMetaUint" o = GES.MetaContainer.MetaContainerRegisterMetaUintMethodInfo
ResolveUriClipAssetMethod "registerMetaUint64" o = GES.MetaContainer.MetaContainerRegisterMetaUint64MethodInfo
ResolveUriClipAssetMethod "registerStaticMeta" o = GES.MetaContainer.MetaContainerRegisterStaticMetaMethodInfo
ResolveUriClipAssetMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveUriClipAssetMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveUriClipAssetMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveUriClipAssetMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveUriClipAssetMethod "unproxy" o = GES.Asset.AssetUnproxyMethodInfo
ResolveUriClipAssetMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveUriClipAssetMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveUriClipAssetMethod "getBoolean" o = GES.MetaContainer.MetaContainerGetBooleanMethodInfo
ResolveUriClipAssetMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveUriClipAssetMethod "getDate" o = GES.MetaContainer.MetaContainerGetDateMethodInfo
ResolveUriClipAssetMethod "getDateTime" o = GES.MetaContainer.MetaContainerGetDateTimeMethodInfo
ResolveUriClipAssetMethod "getDouble" o = GES.MetaContainer.MetaContainerGetDoubleMethodInfo
ResolveUriClipAssetMethod "getDuration" o = UriClipAssetGetDurationMethodInfo
ResolveUriClipAssetMethod "getError" o = GES.Asset.AssetGetErrorMethodInfo
ResolveUriClipAssetMethod "getExtractableType" o = GES.Asset.AssetGetExtractableTypeMethodInfo
ResolveUriClipAssetMethod "getFloat" o = GES.MetaContainer.MetaContainerGetFloatMethodInfo
ResolveUriClipAssetMethod "getFrameTime" o = GES.ClipAsset.ClipAssetGetFrameTimeMethodInfo
ResolveUriClipAssetMethod "getId" o = GES.Asset.AssetGetIdMethodInfo
ResolveUriClipAssetMethod "getInfo" o = UriClipAssetGetInfoMethodInfo
ResolveUriClipAssetMethod "getInt" o = GES.MetaContainer.MetaContainerGetIntMethodInfo
ResolveUriClipAssetMethod "getInt64" o = GES.MetaContainer.MetaContainerGetInt64MethodInfo
ResolveUriClipAssetMethod "getMarkerList" o = GES.MetaContainer.MetaContainerGetMarkerListMethodInfo
ResolveUriClipAssetMethod "getMaxDuration" o = UriClipAssetGetMaxDurationMethodInfo
ResolveUriClipAssetMethod "getMeta" o = GES.MetaContainer.MetaContainerGetMetaMethodInfo
ResolveUriClipAssetMethod "getNaturalFramerate" o = GES.ClipAsset.ClipAssetGetNaturalFramerateMethodInfo
ResolveUriClipAssetMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveUriClipAssetMethod "getProxy" o = GES.Asset.AssetGetProxyMethodInfo
ResolveUriClipAssetMethod "getProxyTarget" o = GES.Asset.AssetGetProxyTargetMethodInfo
ResolveUriClipAssetMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveUriClipAssetMethod "getStreamAssets" o = UriClipAssetGetStreamAssetsMethodInfo
ResolveUriClipAssetMethod "getString" o = GES.MetaContainer.MetaContainerGetStringMethodInfo
ResolveUriClipAssetMethod "getSupportedFormats" o = GES.ClipAsset.ClipAssetGetSupportedFormatsMethodInfo
ResolveUriClipAssetMethod "getUint" o = GES.MetaContainer.MetaContainerGetUintMethodInfo
ResolveUriClipAssetMethod "getUint64" o = GES.MetaContainer.MetaContainerGetUint64MethodInfo
ResolveUriClipAssetMethod "setBoolean" o = GES.MetaContainer.MetaContainerSetBooleanMethodInfo
ResolveUriClipAssetMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveUriClipAssetMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveUriClipAssetMethod "setDate" o = GES.MetaContainer.MetaContainerSetDateMethodInfo
ResolveUriClipAssetMethod "setDateTime" o = GES.MetaContainer.MetaContainerSetDateTimeMethodInfo
ResolveUriClipAssetMethod "setDouble" o = GES.MetaContainer.MetaContainerSetDoubleMethodInfo
ResolveUriClipAssetMethod "setFloat" o = GES.MetaContainer.MetaContainerSetFloatMethodInfo
ResolveUriClipAssetMethod "setInt" o = GES.MetaContainer.MetaContainerSetIntMethodInfo
ResolveUriClipAssetMethod "setInt64" o = GES.MetaContainer.MetaContainerSetInt64MethodInfo
ResolveUriClipAssetMethod "setMarkerList" o = GES.MetaContainer.MetaContainerSetMarkerListMethodInfo
ResolveUriClipAssetMethod "setMeta" o = GES.MetaContainer.MetaContainerSetMetaMethodInfo
ResolveUriClipAssetMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveUriClipAssetMethod "setProxy" o = GES.Asset.AssetSetProxyMethodInfo
ResolveUriClipAssetMethod "setString" o = GES.MetaContainer.MetaContainerSetStringMethodInfo
ResolveUriClipAssetMethod "setSupportedFormats" o = GES.ClipAsset.ClipAssetSetSupportedFormatsMethodInfo
ResolveUriClipAssetMethod "setUint" o = GES.MetaContainer.MetaContainerSetUintMethodInfo
ResolveUriClipAssetMethod "setUint64" o = GES.MetaContainer.MetaContainerSetUint64MethodInfo
ResolveUriClipAssetMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveUriClipAssetMethod t UriClipAsset, O.OverloadedMethod info UriClipAsset p) => OL.IsLabel t (UriClipAsset -> 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 ~ ResolveUriClipAssetMethod t UriClipAsset, O.OverloadedMethod info UriClipAsset p, R.HasField t UriClipAsset p) => R.HasField t UriClipAsset p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveUriClipAssetMethod t UriClipAsset, O.OverloadedMethodInfo info UriClipAsset) => OL.IsLabel t (O.MethodProxy info UriClipAsset) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif
getUriClipAssetDuration :: (MonadIO m, IsUriClipAsset o) => o -> m Word64
getUriClipAssetDuration :: forall (m :: * -> *) o.
(MonadIO m, IsUriClipAsset o) =>
o -> m Word64
getUriClipAssetDuration o
obj = forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO forall a b. (a -> b) -> a -> b
$ forall a. GObject a => a -> String -> IO Word64
B.Properties.getObjectPropertyUInt64 o
obj String
"duration"
setUriClipAssetDuration :: (MonadIO m, IsUriClipAsset o) => o -> Word64 -> m ()
setUriClipAssetDuration :: forall (m :: * -> *) o.
(MonadIO m, IsUriClipAsset o) =>
o -> Word64 -> m ()
setUriClipAssetDuration o
obj Word64
val = forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO forall a b. (a -> b) -> a -> b
$ do
forall a. GObject a => a -> String -> Word64 -> IO ()
B.Properties.setObjectPropertyUInt64 o
obj String
"duration" Word64
val
constructUriClipAssetDuration :: (IsUriClipAsset o, MIO.MonadIO m) => Word64 -> m (GValueConstruct o)
constructUriClipAssetDuration :: forall o (m :: * -> *).
(IsUriClipAsset o, MonadIO m) =>
Word64 -> m (GValueConstruct o)
constructUriClipAssetDuration Word64
val = forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO forall a b. (a -> b) -> a -> b
$ do
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO forall a b. (a -> b) -> a -> b
$ forall o. String -> Word64 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyUInt64 String
"duration" Word64
val
#if defined(ENABLE_OVERLOADING)
data UriClipAssetDurationPropertyInfo
instance AttrInfo UriClipAssetDurationPropertyInfo where
type AttrAllowedOps UriClipAssetDurationPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint UriClipAssetDurationPropertyInfo = IsUriClipAsset
type AttrSetTypeConstraint UriClipAssetDurationPropertyInfo = (~) Word64
type AttrTransferTypeConstraint UriClipAssetDurationPropertyInfo = (~) Word64
type AttrTransferType UriClipAssetDurationPropertyInfo = Word64
type AttrGetType UriClipAssetDurationPropertyInfo = Word64
type AttrLabel UriClipAssetDurationPropertyInfo = "duration"
type AttrOrigin UriClipAssetDurationPropertyInfo = UriClipAsset
attrGet = getUriClipAssetDuration
attrSet = setUriClipAssetDuration
attrTransfer _ v = do
return v
attrConstruct = constructUriClipAssetDuration
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GES.Objects.UriClipAsset.duration"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.1/docs/GI-GES-Objects-UriClipAsset.html#g:attr:duration"
})
#endif
getUriClipAssetIsNestedTimeline :: (MonadIO m, IsUriClipAsset o) => o -> m Bool
getUriClipAssetIsNestedTimeline :: forall (m :: * -> *) o.
(MonadIO m, IsUriClipAsset o) =>
o -> m Bool
getUriClipAssetIsNestedTimeline o
obj = forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO forall a b. (a -> b) -> a -> b
$ forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"is-nested-timeline"
#if defined(ENABLE_OVERLOADING)
data UriClipAssetIsNestedTimelinePropertyInfo
instance AttrInfo UriClipAssetIsNestedTimelinePropertyInfo where
type AttrAllowedOps UriClipAssetIsNestedTimelinePropertyInfo = '[ 'AttrGet]
type AttrBaseTypeConstraint UriClipAssetIsNestedTimelinePropertyInfo = IsUriClipAsset
type AttrSetTypeConstraint UriClipAssetIsNestedTimelinePropertyInfo = (~) ()
type AttrTransferTypeConstraint UriClipAssetIsNestedTimelinePropertyInfo = (~) ()
type AttrTransferType UriClipAssetIsNestedTimelinePropertyInfo = ()
type AttrGetType UriClipAssetIsNestedTimelinePropertyInfo = Bool
type AttrLabel UriClipAssetIsNestedTimelinePropertyInfo = "is-nested-timeline"
type AttrOrigin UriClipAssetIsNestedTimelinePropertyInfo = UriClipAsset
attrGet = getUriClipAssetIsNestedTimeline
attrSet = undefined
attrTransfer _ = undefined
attrConstruct = undefined
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GES.Objects.UriClipAsset.isNestedTimeline"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.1/docs/GI-GES-Objects-UriClipAsset.html#g:attr:isNestedTimeline"
})
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList UriClipAsset
type instance O.AttributeList UriClipAsset = UriClipAssetAttributeList
type UriClipAssetAttributeList = ('[ '("duration", UriClipAssetDurationPropertyInfo), '("extractableType", GES.Asset.AssetExtractableTypePropertyInfo), '("id", GES.Asset.AssetIdPropertyInfo), '("isNestedTimeline", UriClipAssetIsNestedTimelinePropertyInfo), '("proxy", GES.Asset.AssetProxyPropertyInfo), '("proxyTarget", GES.Asset.AssetProxyTargetPropertyInfo), '("supportedFormats", GES.ClipAsset.ClipAssetSupportedFormatsPropertyInfo)] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
uriClipAssetDuration :: AttrLabelProxy "duration"
uriClipAssetDuration = AttrLabelProxy
uriClipAssetIsNestedTimeline :: AttrLabelProxy "isNestedTimeline"
uriClipAssetIsNestedTimeline = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList UriClipAsset = UriClipAssetSignalList
type UriClipAssetSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo), '("notifyMeta", GES.MetaContainer.MetaContainerNotifyMetaSignalInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "ges_uri_clip_asset_get_duration" ges_uri_clip_asset_get_duration ::
Ptr UriClipAsset ->
IO Word64
uriClipAssetGetDuration ::
(B.CallStack.HasCallStack, MonadIO m, IsUriClipAsset a) =>
a
-> m Word64
uriClipAssetGetDuration :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsUriClipAsset a) =>
a -> m Word64
uriClipAssetGetDuration a
self = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
Ptr UriClipAsset
self' <- forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
Word64
result <- Ptr UriClipAsset -> IO Word64
ges_uri_clip_asset_get_duration Ptr UriClipAsset
self'
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
forall (m :: * -> *) a. Monad m => a -> m a
return Word64
result
#if defined(ENABLE_OVERLOADING)
data UriClipAssetGetDurationMethodInfo
instance (signature ~ (m Word64), MonadIO m, IsUriClipAsset a) => O.OverloadedMethod UriClipAssetGetDurationMethodInfo a signature where
overloadedMethod = uriClipAssetGetDuration
instance O.OverloadedMethodInfo UriClipAssetGetDurationMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GES.Objects.UriClipAsset.uriClipAssetGetDuration",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.1/docs/GI-GES-Objects-UriClipAsset.html#v:uriClipAssetGetDuration"
})
#endif
foreign import ccall "ges_uri_clip_asset_get_info" ges_uri_clip_asset_get_info ::
Ptr UriClipAsset ->
IO (Ptr GstPbutils.DiscovererInfo.DiscovererInfo)
uriClipAssetGetInfo ::
(B.CallStack.HasCallStack, MonadIO m, IsUriClipAsset a) =>
a
-> m GstPbutils.DiscovererInfo.DiscovererInfo
uriClipAssetGetInfo :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsUriClipAsset a) =>
a -> m DiscovererInfo
uriClipAssetGetInfo a
self = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
Ptr UriClipAsset
self' <- forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
Ptr DiscovererInfo
result <- Ptr UriClipAsset -> IO (Ptr DiscovererInfo)
ges_uri_clip_asset_get_info Ptr UriClipAsset
self'
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"uriClipAssetGetInfo" Ptr DiscovererInfo
result
DiscovererInfo
result' <- (forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr DiscovererInfo -> DiscovererInfo
GstPbutils.DiscovererInfo.DiscovererInfo) Ptr DiscovererInfo
result
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
forall (m :: * -> *) a. Monad m => a -> m a
return DiscovererInfo
result'
#if defined(ENABLE_OVERLOADING)
data UriClipAssetGetInfoMethodInfo
instance (signature ~ (m GstPbutils.DiscovererInfo.DiscovererInfo), MonadIO m, IsUriClipAsset a) => O.OverloadedMethod UriClipAssetGetInfoMethodInfo a signature where
overloadedMethod = uriClipAssetGetInfo
instance O.OverloadedMethodInfo UriClipAssetGetInfoMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GES.Objects.UriClipAsset.uriClipAssetGetInfo",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.1/docs/GI-GES-Objects-UriClipAsset.html#v:uriClipAssetGetInfo"
})
#endif
foreign import ccall "ges_uri_clip_asset_get_max_duration" ges_uri_clip_asset_get_max_duration ::
Ptr UriClipAsset ->
IO Word64
uriClipAssetGetMaxDuration ::
(B.CallStack.HasCallStack, MonadIO m, IsUriClipAsset a) =>
a
-> m Word64
uriClipAssetGetMaxDuration :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsUriClipAsset a) =>
a -> m Word64
uriClipAssetGetMaxDuration a
self = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
Ptr UriClipAsset
self' <- forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
Word64
result <- Ptr UriClipAsset -> IO Word64
ges_uri_clip_asset_get_max_duration Ptr UriClipAsset
self'
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
forall (m :: * -> *) a. Monad m => a -> m a
return Word64
result
#if defined(ENABLE_OVERLOADING)
data UriClipAssetGetMaxDurationMethodInfo
instance (signature ~ (m Word64), MonadIO m, IsUriClipAsset a) => O.OverloadedMethod UriClipAssetGetMaxDurationMethodInfo a signature where
overloadedMethod = uriClipAssetGetMaxDuration
instance O.OverloadedMethodInfo UriClipAssetGetMaxDurationMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GES.Objects.UriClipAsset.uriClipAssetGetMaxDuration",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.1/docs/GI-GES-Objects-UriClipAsset.html#v:uriClipAssetGetMaxDuration"
})
#endif
foreign import ccall "ges_uri_clip_asset_get_stream_assets" ges_uri_clip_asset_get_stream_assets ::
Ptr UriClipAsset ->
IO (Ptr (GList (Ptr GES.UriSourceAsset.UriSourceAsset)))
uriClipAssetGetStreamAssets ::
(B.CallStack.HasCallStack, MonadIO m, IsUriClipAsset a) =>
a
-> m [GES.UriSourceAsset.UriSourceAsset]
uriClipAssetGetStreamAssets :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsUriClipAsset a) =>
a -> m [UriSourceAsset]
uriClipAssetGetStreamAssets a
self = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
Ptr UriClipAsset
self' <- forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
Ptr (GList (Ptr UriSourceAsset))
result <- Ptr UriClipAsset -> IO (Ptr (GList (Ptr UriSourceAsset)))
ges_uri_clip_asset_get_stream_assets Ptr UriClipAsset
self'
[Ptr UriSourceAsset]
result' <- forall a. Ptr (GList (Ptr a)) -> IO [Ptr a]
unpackGList Ptr (GList (Ptr UriSourceAsset))
result
[UriSourceAsset]
result'' <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr UriSourceAsset -> UriSourceAsset
GES.UriSourceAsset.UriSourceAsset) [Ptr UriSourceAsset]
result'
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
forall (m :: * -> *) a. Monad m => a -> m a
return [UriSourceAsset]
result''
#if defined(ENABLE_OVERLOADING)
data UriClipAssetGetStreamAssetsMethodInfo
instance (signature ~ (m [GES.UriSourceAsset.UriSourceAsset]), MonadIO m, IsUriClipAsset a) => O.OverloadedMethod UriClipAssetGetStreamAssetsMethodInfo a signature where
overloadedMethod = uriClipAssetGetStreamAssets
instance O.OverloadedMethodInfo UriClipAssetGetStreamAssetsMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GES.Objects.UriClipAsset.uriClipAssetGetStreamAssets",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.1/docs/GI-GES-Objects-UriClipAsset.html#v:uriClipAssetGetStreamAssets"
})
#endif
foreign import ccall "ges_uri_clip_asset_is_image" ges_uri_clip_asset_is_image ::
Ptr UriClipAsset ->
IO CInt
uriClipAssetIsImage ::
(B.CallStack.HasCallStack, MonadIO m, IsUriClipAsset a) =>
a
-> m Bool
uriClipAssetIsImage :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsUriClipAsset a) =>
a -> m Bool
uriClipAssetIsImage a
self = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
Ptr UriClipAsset
self' <- forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
CInt
result <- Ptr UriClipAsset -> IO CInt
ges_uri_clip_asset_is_image Ptr UriClipAsset
self'
let result' :: Bool
result' = (forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data UriClipAssetIsImageMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsUriClipAsset a) => O.OverloadedMethod UriClipAssetIsImageMethodInfo a signature where
overloadedMethod = uriClipAssetIsImage
instance O.OverloadedMethodInfo UriClipAssetIsImageMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GES.Objects.UriClipAsset.uriClipAssetIsImage",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.1/docs/GI-GES-Objects-UriClipAsset.html#v:uriClipAssetIsImage"
})
#endif
foreign import ccall "ges_uri_clip_asset_finish" ges_uri_clip_asset_finish ::
Ptr Gio.AsyncResult.AsyncResult ->
Ptr (Ptr GError) ->
IO (Ptr UriClipAsset)
uriClipAssetFinish ::
(B.CallStack.HasCallStack, MonadIO m, Gio.AsyncResult.IsAsyncResult a) =>
a
-> m UriClipAsset
uriClipAssetFinish :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsAsyncResult a) =>
a -> m UriClipAsset
uriClipAssetFinish a
res = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
Ptr AsyncResult
res' <- forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
res
forall a b. IO a -> IO b -> IO a
onException (do
Ptr UriClipAsset
result <- forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError forall a b. (a -> b) -> a -> b
$ Ptr AsyncResult -> Ptr (Ptr GError) -> IO (Ptr UriClipAsset)
ges_uri_clip_asset_finish Ptr AsyncResult
res'
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"uriClipAssetFinish" Ptr UriClipAsset
result
UriClipAsset
result' <- (forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr UriClipAsset -> UriClipAsset
UriClipAsset) Ptr UriClipAsset
result
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
res
forall (m :: * -> *) a. Monad m => a -> m a
return UriClipAsset
result'
) (do
forall (m :: * -> *) a. Monad m => a -> m a
return ()
)
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "ges_uri_clip_asset_new" ges_uri_clip_asset_new ::
CString ->
Ptr Gio.Cancellable.Cancellable ->
FunPtr Gio.Callbacks.C_AsyncReadyCallback ->
Ptr () ->
IO ()
uriClipAssetNew ::
(B.CallStack.HasCallStack, MonadIO m, Gio.Cancellable.IsCancellable a) =>
T.Text
-> Maybe (a)
-> Maybe (Gio.Callbacks.AsyncReadyCallback)
-> m ()
uriClipAssetNew :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCancellable a) =>
Text -> Maybe a -> Maybe AsyncReadyCallback -> m ()
uriClipAssetNew Text
uri Maybe a
cancellable Maybe AsyncReadyCallback
callback = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
CString
uri' <- Text -> IO CString
textToCString Text
uri
Ptr Cancellable
maybeCancellable <- case Maybe a
cancellable of
Maybe a
Nothing -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Ptr a
nullPtr
Just a
jCancellable -> do
Ptr Cancellable
jCancellable' <- forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
jCancellable
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
FunPtr C_AsyncReadyCallback
maybeCallback <- case Maybe AsyncReadyCallback
callback of
Maybe AsyncReadyCallback
Nothing -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall a b. Ptr a -> FunPtr b
castPtrToFunPtr forall a. Ptr a
nullPtr)
Just AsyncReadyCallback
jCallback -> do
Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback <- forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gio.Callbacks.C_AsyncReadyCallback))
FunPtr C_AsyncReadyCallback
jCallback' <- C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
Gio.Callbacks.mk_AsyncReadyCallback (Maybe (Ptr (FunPtr C_AsyncReadyCallback))
-> AsyncReadyCallback_WithClosures -> C_AsyncReadyCallback
Gio.Callbacks.wrap_AsyncReadyCallback (forall a. a -> Maybe a
Just Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback) (AsyncReadyCallback -> AsyncReadyCallback_WithClosures
Gio.Callbacks.drop_closures_AsyncReadyCallback AsyncReadyCallback
jCallback))
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback FunPtr C_AsyncReadyCallback
jCallback'
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_AsyncReadyCallback
jCallback'
let userData :: Ptr a
userData = forall a. Ptr a
nullPtr
CString
-> Ptr Cancellable
-> FunPtr C_AsyncReadyCallback
-> Ptr ()
-> IO ()
ges_uri_clip_asset_new CString
uri' Ptr Cancellable
maybeCancellable FunPtr C_AsyncReadyCallback
maybeCallback forall a. Ptr a
userData
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe a
cancellable forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
forall a. Ptr a -> IO ()
freeMem CString
uri'
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "ges_uri_clip_asset_request_sync" ges_uri_clip_asset_request_sync ::
CString ->
Ptr (Ptr GError) ->
IO (Ptr UriClipAsset)
uriClipAssetRequestSync ::
(B.CallStack.HasCallStack, MonadIO m) =>
T.Text
-> m UriClipAsset
uriClipAssetRequestSync :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Text -> m UriClipAsset
uriClipAssetRequestSync Text
uri = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
CString
uri' <- Text -> IO CString
textToCString Text
uri
forall a b. IO a -> IO b -> IO a
onException (do
Ptr UriClipAsset
result <- forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError forall a b. (a -> b) -> a -> b
$ CString -> Ptr (Ptr GError) -> IO (Ptr UriClipAsset)
ges_uri_clip_asset_request_sync CString
uri'
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"uriClipAssetRequestSync" Ptr UriClipAsset
result
UriClipAsset
result' <- (forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr UriClipAsset -> UriClipAsset
UriClipAsset) Ptr UriClipAsset
result
forall a. Ptr a -> IO ()
freeMem CString
uri'
forall (m :: * -> *) a. Monad m => a -> m a
return UriClipAsset
result'
) (do
forall a. Ptr a -> IO ()
freeMem CString
uri'
)
#if defined(ENABLE_OVERLOADING)
#endif