{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.GES.Objects.EffectClip
(
EffectClip(..) ,
IsEffectClip ,
toEffectClip ,
#if defined(ENABLE_OVERLOADING)
ResolveEffectClipMethod ,
#endif
effectClipNew ,
#if defined(ENABLE_OVERLOADING)
EffectClipAudioBinDescriptionPropertyInfo,
#endif
constructEffectClipAudioBinDescription ,
#if defined(ENABLE_OVERLOADING)
effectClipAudioBinDescription ,
#endif
getEffectClipAudioBinDescription ,
#if defined(ENABLE_OVERLOADING)
EffectClipVideoBinDescriptionPropertyInfo,
#endif
constructEffectClipVideoBinDescription ,
#if defined(ENABLE_OVERLOADING)
effectClipVideoBinDescription ,
#endif
getEffectClipVideoBinDescription ,
) 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.BaseEffectClip as GES.BaseEffectClip
import {-# SOURCE #-} qualified GI.GES.Objects.Clip as GES.Clip
import {-# SOURCE #-} qualified GI.GES.Objects.Container as GES.Container
import {-# SOURCE #-} qualified GI.GES.Objects.OperationClip as GES.OperationClip
import {-# SOURCE #-} qualified GI.GES.Objects.TimelineElement as GES.TimelineElement
import qualified GI.GObject.Objects.Object as GObject.Object
newtype EffectClip = EffectClip (SP.ManagedPtr EffectClip)
deriving (EffectClip -> EffectClip -> Bool
(EffectClip -> EffectClip -> Bool)
-> (EffectClip -> EffectClip -> Bool) -> Eq EffectClip
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EffectClip -> EffectClip -> Bool
== :: EffectClip -> EffectClip -> Bool
$c/= :: EffectClip -> EffectClip -> Bool
/= :: EffectClip -> EffectClip -> Bool
Eq)
instance SP.ManagedPtrNewtype EffectClip where
toManagedPtr :: EffectClip -> ManagedPtr EffectClip
toManagedPtr (EffectClip ManagedPtr EffectClip
p) = ManagedPtr EffectClip
p
foreign import ccall "ges_effect_clip_get_type"
c_ges_effect_clip_get_type :: IO B.Types.GType
instance B.Types.TypedObject EffectClip where
glibType :: IO GType
glibType = IO GType
c_ges_effect_clip_get_type
instance B.Types.GObject EffectClip
class (SP.GObject o, O.IsDescendantOf EffectClip o) => IsEffectClip o
instance (SP.GObject o, O.IsDescendantOf EffectClip o) => IsEffectClip o
instance O.HasParentTypes EffectClip
type instance O.ParentTypes EffectClip = '[GES.BaseEffectClip.BaseEffectClip, GES.OperationClip.OperationClip, GES.Clip.Clip, GES.Container.Container, GES.TimelineElement.TimelineElement, GObject.Object.Object, GES.Extractable.Extractable, GES.MetaContainer.MetaContainer]
toEffectClip :: (MIO.MonadIO m, IsEffectClip o) => o -> m EffectClip
toEffectClip :: forall (m :: * -> *) o.
(MonadIO m, IsEffectClip o) =>
o -> m EffectClip
toEffectClip = IO EffectClip -> m EffectClip
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO EffectClip -> m EffectClip)
-> (o -> IO EffectClip) -> o -> m EffectClip
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr EffectClip -> EffectClip) -> o -> IO EffectClip
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr EffectClip -> EffectClip
EffectClip
instance B.GValue.IsGValue (Maybe EffectClip) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_ges_effect_clip_get_type
gvalueSet_ :: Ptr GValue -> Maybe EffectClip -> IO ()
gvalueSet_ Ptr GValue
gv Maybe EffectClip
P.Nothing = Ptr GValue -> Ptr EffectClip -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr EffectClip
forall a. Ptr a
FP.nullPtr :: FP.Ptr EffectClip)
gvalueSet_ Ptr GValue
gv (P.Just EffectClip
obj) = EffectClip -> (Ptr EffectClip -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr EffectClip
obj (Ptr GValue -> Ptr EffectClip -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe EffectClip)
gvalueGet_ Ptr GValue
gv = do
Ptr EffectClip
ptr <- Ptr GValue -> IO (Ptr EffectClip)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr EffectClip)
if Ptr EffectClip
ptr Ptr EffectClip -> Ptr EffectClip -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr EffectClip
forall a. Ptr a
FP.nullPtr
then EffectClip -> Maybe EffectClip
forall a. a -> Maybe a
P.Just (EffectClip -> Maybe EffectClip)
-> IO EffectClip -> IO (Maybe EffectClip)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr EffectClip -> EffectClip)
-> Ptr EffectClip -> IO EffectClip
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr EffectClip -> EffectClip
EffectClip Ptr EffectClip
ptr
else Maybe EffectClip -> IO (Maybe EffectClip)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe EffectClip
forall a. Maybe a
P.Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolveEffectClipMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolveEffectClipMethod "add" o = GES.Container.ContainerAddMethodInfo
ResolveEffectClipMethod "addAsset" o = GES.Clip.ClipAddAssetMethodInfo
ResolveEffectClipMethod "addChildProperty" o = GES.TimelineElement.TimelineElementAddChildPropertyMethodInfo
ResolveEffectClipMethod "addChildToTrack" o = GES.Clip.ClipAddChildToTrackMethodInfo
ResolveEffectClipMethod "addMetasFromString" o = GES.MetaContainer.MetaContainerAddMetasFromStringMethodInfo
ResolveEffectClipMethod "addTopEffect" o = GES.Clip.ClipAddTopEffectMethodInfo
ResolveEffectClipMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveEffectClipMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveEffectClipMethod "checkMetaRegistered" o = GES.MetaContainer.MetaContainerCheckMetaRegisteredMethodInfo
ResolveEffectClipMethod "copy" o = GES.TimelineElement.TimelineElementCopyMethodInfo
ResolveEffectClipMethod "edit" o = GES.Container.ContainerEditMethodInfo
ResolveEffectClipMethod "editFull" o = GES.TimelineElement.TimelineElementEditFullMethodInfo
ResolveEffectClipMethod "findTrackElement" o = GES.Clip.ClipFindTrackElementMethodInfo
ResolveEffectClipMethod "findTrackElements" o = GES.Clip.ClipFindTrackElementsMethodInfo
ResolveEffectClipMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveEffectClipMethod "foreach" o = GES.MetaContainer.MetaContainerForeachMethodInfo
ResolveEffectClipMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveEffectClipMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveEffectClipMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveEffectClipMethod "listChildrenProperties" o = GES.TimelineElement.TimelineElementListChildrenPropertiesMethodInfo
ResolveEffectClipMethod "lookupChild" o = GES.TimelineElement.TimelineElementLookupChildMethodInfo
ResolveEffectClipMethod "metasToString" o = GES.MetaContainer.MetaContainerMetasToStringMethodInfo
ResolveEffectClipMethod "moveToLayer" o = GES.Clip.ClipMoveToLayerMethodInfo
ResolveEffectClipMethod "moveToLayerFull" o = GES.Clip.ClipMoveToLayerFullMethodInfo
ResolveEffectClipMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveEffectClipMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveEffectClipMethod "paste" o = GES.TimelineElement.TimelineElementPasteMethodInfo
ResolveEffectClipMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveEffectClipMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveEffectClipMethod "registerMeta" o = GES.MetaContainer.MetaContainerRegisterMetaMethodInfo
ResolveEffectClipMethod "registerMetaBoolean" o = GES.MetaContainer.MetaContainerRegisterMetaBooleanMethodInfo
ResolveEffectClipMethod "registerMetaDate" o = GES.MetaContainer.MetaContainerRegisterMetaDateMethodInfo
ResolveEffectClipMethod "registerMetaDateTime" o = GES.MetaContainer.MetaContainerRegisterMetaDateTimeMethodInfo
ResolveEffectClipMethod "registerMetaDouble" o = GES.MetaContainer.MetaContainerRegisterMetaDoubleMethodInfo
ResolveEffectClipMethod "registerMetaFloat" o = GES.MetaContainer.MetaContainerRegisterMetaFloatMethodInfo
ResolveEffectClipMethod "registerMetaInt" o = GES.MetaContainer.MetaContainerRegisterMetaIntMethodInfo
ResolveEffectClipMethod "registerMetaInt64" o = GES.MetaContainer.MetaContainerRegisterMetaInt64MethodInfo
ResolveEffectClipMethod "registerMetaString" o = GES.MetaContainer.MetaContainerRegisterMetaStringMethodInfo
ResolveEffectClipMethod "registerMetaUint" o = GES.MetaContainer.MetaContainerRegisterMetaUintMethodInfo
ResolveEffectClipMethod "registerMetaUint64" o = GES.MetaContainer.MetaContainerRegisterMetaUint64MethodInfo
ResolveEffectClipMethod "registerStaticMeta" o = GES.MetaContainer.MetaContainerRegisterStaticMetaMethodInfo
ResolveEffectClipMethod "remove" o = GES.Container.ContainerRemoveMethodInfo
ResolveEffectClipMethod "removeChildProperty" o = GES.TimelineElement.TimelineElementRemoveChildPropertyMethodInfo
ResolveEffectClipMethod "removeTopEffect" o = GES.Clip.ClipRemoveTopEffectMethodInfo
ResolveEffectClipMethod "ripple" o = GES.TimelineElement.TimelineElementRippleMethodInfo
ResolveEffectClipMethod "rippleEnd" o = GES.TimelineElement.TimelineElementRippleEndMethodInfo
ResolveEffectClipMethod "rollEnd" o = GES.TimelineElement.TimelineElementRollEndMethodInfo
ResolveEffectClipMethod "rollStart" o = GES.TimelineElement.TimelineElementRollStartMethodInfo
ResolveEffectClipMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveEffectClipMethod "split" o = GES.Clip.ClipSplitMethodInfo
ResolveEffectClipMethod "splitFull" o = GES.Clip.ClipSplitFullMethodInfo
ResolveEffectClipMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveEffectClipMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveEffectClipMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveEffectClipMethod "trim" o = GES.TimelineElement.TimelineElementTrimMethodInfo
ResolveEffectClipMethod "ungroup" o = GES.Container.ContainerUngroupMethodInfo
ResolveEffectClipMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveEffectClipMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveEffectClipMethod "getAsset" o = GES.Extractable.ExtractableGetAssetMethodInfo
ResolveEffectClipMethod "getBoolean" o = GES.MetaContainer.MetaContainerGetBooleanMethodInfo
ResolveEffectClipMethod "getChildProperty" o = GES.TimelineElement.TimelineElementGetChildPropertyMethodInfo
ResolveEffectClipMethod "getChildPropertyByPspec" o = GES.TimelineElement.TimelineElementGetChildPropertyByPspecMethodInfo
ResolveEffectClipMethod "getChildren" o = GES.Container.ContainerGetChildrenMethodInfo
ResolveEffectClipMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveEffectClipMethod "getDate" o = GES.MetaContainer.MetaContainerGetDateMethodInfo
ResolveEffectClipMethod "getDateTime" o = GES.MetaContainer.MetaContainerGetDateTimeMethodInfo
ResolveEffectClipMethod "getDouble" o = GES.MetaContainer.MetaContainerGetDoubleMethodInfo
ResolveEffectClipMethod "getDuration" o = GES.TimelineElement.TimelineElementGetDurationMethodInfo
ResolveEffectClipMethod "getDurationLimit" o = GES.Clip.ClipGetDurationLimitMethodInfo
ResolveEffectClipMethod "getFloat" o = GES.MetaContainer.MetaContainerGetFloatMethodInfo
ResolveEffectClipMethod "getId" o = GES.Extractable.ExtractableGetIdMethodInfo
ResolveEffectClipMethod "getInpoint" o = GES.TimelineElement.TimelineElementGetInpointMethodInfo
ResolveEffectClipMethod "getInt" o = GES.MetaContainer.MetaContainerGetIntMethodInfo
ResolveEffectClipMethod "getInt64" o = GES.MetaContainer.MetaContainerGetInt64MethodInfo
ResolveEffectClipMethod "getInternalTimeFromTimelineTime" o = GES.Clip.ClipGetInternalTimeFromTimelineTimeMethodInfo
ResolveEffectClipMethod "getLayer" o = GES.Clip.ClipGetLayerMethodInfo
ResolveEffectClipMethod "getLayerPriority" o = GES.TimelineElement.TimelineElementGetLayerPriorityMethodInfo
ResolveEffectClipMethod "getMarkerList" o = GES.MetaContainer.MetaContainerGetMarkerListMethodInfo
ResolveEffectClipMethod "getMaxDuration" o = GES.TimelineElement.TimelineElementGetMaxDurationMethodInfo
ResolveEffectClipMethod "getMeta" o = GES.MetaContainer.MetaContainerGetMetaMethodInfo
ResolveEffectClipMethod "getName" o = GES.TimelineElement.TimelineElementGetNameMethodInfo
ResolveEffectClipMethod "getNaturalFramerate" o = GES.TimelineElement.TimelineElementGetNaturalFramerateMethodInfo
ResolveEffectClipMethod "getParent" o = GES.TimelineElement.TimelineElementGetParentMethodInfo
ResolveEffectClipMethod "getPriority" o = GES.TimelineElement.TimelineElementGetPriorityMethodInfo
ResolveEffectClipMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveEffectClipMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveEffectClipMethod "getStart" o = GES.TimelineElement.TimelineElementGetStartMethodInfo
ResolveEffectClipMethod "getString" o = GES.MetaContainer.MetaContainerGetStringMethodInfo
ResolveEffectClipMethod "getSupportedFormats" o = GES.Clip.ClipGetSupportedFormatsMethodInfo
ResolveEffectClipMethod "getTimeline" o = GES.TimelineElement.TimelineElementGetTimelineMethodInfo
ResolveEffectClipMethod "getTimelineTimeFromInternalTime" o = GES.Clip.ClipGetTimelineTimeFromInternalTimeMethodInfo
ResolveEffectClipMethod "getTimelineTimeFromSourceFrame" o = GES.Clip.ClipGetTimelineTimeFromSourceFrameMethodInfo
ResolveEffectClipMethod "getTopEffectIndex" o = GES.Clip.ClipGetTopEffectIndexMethodInfo
ResolveEffectClipMethod "getTopEffectPosition" o = GES.Clip.ClipGetTopEffectPositionMethodInfo
ResolveEffectClipMethod "getTopEffects" o = GES.Clip.ClipGetTopEffectsMethodInfo
ResolveEffectClipMethod "getToplevelParent" o = GES.TimelineElement.TimelineElementGetToplevelParentMethodInfo
ResolveEffectClipMethod "getTrackTypes" o = GES.TimelineElement.TimelineElementGetTrackTypesMethodInfo
ResolveEffectClipMethod "getUint" o = GES.MetaContainer.MetaContainerGetUintMethodInfo
ResolveEffectClipMethod "getUint64" o = GES.MetaContainer.MetaContainerGetUint64MethodInfo
ResolveEffectClipMethod "setAsset" o = GES.Extractable.ExtractableSetAssetMethodInfo
ResolveEffectClipMethod "setBoolean" o = GES.MetaContainer.MetaContainerSetBooleanMethodInfo
ResolveEffectClipMethod "setChildProperty" o = GES.TimelineElement.TimelineElementSetChildPropertyMethodInfo
ResolveEffectClipMethod "setChildPropertyByPspec" o = GES.TimelineElement.TimelineElementSetChildPropertyByPspecMethodInfo
ResolveEffectClipMethod "setChildPropertyFull" o = GES.TimelineElement.TimelineElementSetChildPropertyFullMethodInfo
ResolveEffectClipMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveEffectClipMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveEffectClipMethod "setDate" o = GES.MetaContainer.MetaContainerSetDateMethodInfo
ResolveEffectClipMethod "setDateTime" o = GES.MetaContainer.MetaContainerSetDateTimeMethodInfo
ResolveEffectClipMethod "setDouble" o = GES.MetaContainer.MetaContainerSetDoubleMethodInfo
ResolveEffectClipMethod "setDuration" o = GES.TimelineElement.TimelineElementSetDurationMethodInfo
ResolveEffectClipMethod "setFloat" o = GES.MetaContainer.MetaContainerSetFloatMethodInfo
ResolveEffectClipMethod "setInpoint" o = GES.TimelineElement.TimelineElementSetInpointMethodInfo
ResolveEffectClipMethod "setInt" o = GES.MetaContainer.MetaContainerSetIntMethodInfo
ResolveEffectClipMethod "setInt64" o = GES.MetaContainer.MetaContainerSetInt64MethodInfo
ResolveEffectClipMethod "setMarkerList" o = GES.MetaContainer.MetaContainerSetMarkerListMethodInfo
ResolveEffectClipMethod "setMaxDuration" o = GES.TimelineElement.TimelineElementSetMaxDurationMethodInfo
ResolveEffectClipMethod "setMeta" o = GES.MetaContainer.MetaContainerSetMetaMethodInfo
ResolveEffectClipMethod "setName" o = GES.TimelineElement.TimelineElementSetNameMethodInfo
ResolveEffectClipMethod "setParent" o = GES.TimelineElement.TimelineElementSetParentMethodInfo
ResolveEffectClipMethod "setPriority" o = GES.TimelineElement.TimelineElementSetPriorityMethodInfo
ResolveEffectClipMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveEffectClipMethod "setStart" o = GES.TimelineElement.TimelineElementSetStartMethodInfo
ResolveEffectClipMethod "setString" o = GES.MetaContainer.MetaContainerSetStringMethodInfo
ResolveEffectClipMethod "setSupportedFormats" o = GES.Clip.ClipSetSupportedFormatsMethodInfo
ResolveEffectClipMethod "setTimeline" o = GES.TimelineElement.TimelineElementSetTimelineMethodInfo
ResolveEffectClipMethod "setTopEffectIndex" o = GES.Clip.ClipSetTopEffectIndexMethodInfo
ResolveEffectClipMethod "setTopEffectIndexFull" o = GES.Clip.ClipSetTopEffectIndexFullMethodInfo
ResolveEffectClipMethod "setTopEffectPriority" o = GES.Clip.ClipSetTopEffectPriorityMethodInfo
ResolveEffectClipMethod "setUint" o = GES.MetaContainer.MetaContainerSetUintMethodInfo
ResolveEffectClipMethod "setUint64" o = GES.MetaContainer.MetaContainerSetUint64MethodInfo
ResolveEffectClipMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveEffectClipMethod t EffectClip, O.OverloadedMethod info EffectClip p) => OL.IsLabel t (EffectClip -> 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 ~ ResolveEffectClipMethod t EffectClip, O.OverloadedMethod info EffectClip p, R.HasField t EffectClip p) => R.HasField t EffectClip p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveEffectClipMethod t EffectClip, O.OverloadedMethodInfo info EffectClip) => OL.IsLabel t (O.MethodProxy info EffectClip) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif
getEffectClipAudioBinDescription :: (MonadIO m, IsEffectClip o) => o -> m (Maybe T.Text)
getEffectClipAudioBinDescription :: forall (m :: * -> *) o.
(MonadIO m, IsEffectClip o) =>
o -> m (Maybe Text)
getEffectClipAudioBinDescription 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
"audio-bin-description"
constructEffectClipAudioBinDescription :: (IsEffectClip o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructEffectClipAudioBinDescription :: forall o (m :: * -> *).
(IsEffectClip o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructEffectClipAudioBinDescription 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
"audio-bin-description" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)
#if defined(ENABLE_OVERLOADING)
data EffectClipAudioBinDescriptionPropertyInfo
instance AttrInfo EffectClipAudioBinDescriptionPropertyInfo where
type AttrAllowedOps EffectClipAudioBinDescriptionPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint EffectClipAudioBinDescriptionPropertyInfo = IsEffectClip
type AttrSetTypeConstraint EffectClipAudioBinDescriptionPropertyInfo = (~) T.Text
type AttrTransferTypeConstraint EffectClipAudioBinDescriptionPropertyInfo = (~) T.Text
type AttrTransferType EffectClipAudioBinDescriptionPropertyInfo = T.Text
type AttrGetType EffectClipAudioBinDescriptionPropertyInfo = (Maybe T.Text)
type AttrLabel EffectClipAudioBinDescriptionPropertyInfo = "audio-bin-description"
type AttrOrigin EffectClipAudioBinDescriptionPropertyInfo = EffectClip
attrGet = getEffectClipAudioBinDescription
attrSet = undefined
attrTransfer _ v = do
return v
attrConstruct = constructEffectClipAudioBinDescription
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GES.Objects.EffectClip.audioBinDescription"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.4/docs/GI-GES-Objects-EffectClip.html#g:attr:audioBinDescription"
})
#endif
getEffectClipVideoBinDescription :: (MonadIO m, IsEffectClip o) => o -> m (Maybe T.Text)
getEffectClipVideoBinDescription :: forall (m :: * -> *) o.
(MonadIO m, IsEffectClip o) =>
o -> m (Maybe Text)
getEffectClipVideoBinDescription 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
"video-bin-description"
constructEffectClipVideoBinDescription :: (IsEffectClip o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructEffectClipVideoBinDescription :: forall o (m :: * -> *).
(IsEffectClip o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructEffectClipVideoBinDescription 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
"video-bin-description" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)
#if defined(ENABLE_OVERLOADING)
data EffectClipVideoBinDescriptionPropertyInfo
instance AttrInfo EffectClipVideoBinDescriptionPropertyInfo where
type AttrAllowedOps EffectClipVideoBinDescriptionPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint EffectClipVideoBinDescriptionPropertyInfo = IsEffectClip
type AttrSetTypeConstraint EffectClipVideoBinDescriptionPropertyInfo = (~) T.Text
type AttrTransferTypeConstraint EffectClipVideoBinDescriptionPropertyInfo = (~) T.Text
type AttrTransferType EffectClipVideoBinDescriptionPropertyInfo = T.Text
type AttrGetType EffectClipVideoBinDescriptionPropertyInfo = (Maybe T.Text)
type AttrLabel EffectClipVideoBinDescriptionPropertyInfo = "video-bin-description"
type AttrOrigin EffectClipVideoBinDescriptionPropertyInfo = EffectClip
attrGet = getEffectClipVideoBinDescription
attrSet = undefined
attrTransfer _ v = do
return v
attrConstruct = constructEffectClipVideoBinDescription
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GES.Objects.EffectClip.videoBinDescription"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.4/docs/GI-GES-Objects-EffectClip.html#g:attr:videoBinDescription"
})
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList EffectClip
type instance O.AttributeList EffectClip = EffectClipAttributeList
type EffectClipAttributeList = ('[ '("audioBinDescription", EffectClipAudioBinDescriptionPropertyInfo), '("duration", GES.TimelineElement.TimelineElementDurationPropertyInfo), '("durationLimit", GES.Clip.ClipDurationLimitPropertyInfo), '("height", GES.Container.ContainerHeightPropertyInfo), '("inPoint", GES.TimelineElement.TimelineElementInPointPropertyInfo), '("layer", GES.Clip.ClipLayerPropertyInfo), '("maxDuration", GES.TimelineElement.TimelineElementMaxDurationPropertyInfo), '("name", GES.TimelineElement.TimelineElementNamePropertyInfo), '("parent", GES.TimelineElement.TimelineElementParentPropertyInfo), '("priority", GES.TimelineElement.TimelineElementPriorityPropertyInfo), '("serialize", GES.TimelineElement.TimelineElementSerializePropertyInfo), '("start", GES.TimelineElement.TimelineElementStartPropertyInfo), '("supportedFormats", GES.Clip.ClipSupportedFormatsPropertyInfo), '("timeline", GES.TimelineElement.TimelineElementTimelinePropertyInfo), '("videoBinDescription", EffectClipVideoBinDescriptionPropertyInfo)] :: [(Symbol, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
effectClipAudioBinDescription :: AttrLabelProxy "audioBinDescription"
effectClipAudioBinDescription = AttrLabelProxy
effectClipVideoBinDescription :: AttrLabelProxy "videoBinDescription"
effectClipVideoBinDescription = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList EffectClip = EffectClipSignalList
type EffectClipSignalList = ('[ '("childAdded", GES.Container.ContainerChildAddedSignalInfo), '("childPropertyAdded", GES.TimelineElement.TimelineElementChildPropertyAddedSignalInfo), '("childPropertyRemoved", GES.TimelineElement.TimelineElementChildPropertyRemovedSignalInfo), '("childRemoved", GES.Container.ContainerChildRemovedSignalInfo), '("deepNotify", GES.TimelineElement.TimelineElementDeepNotifySignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("notifyMeta", GES.MetaContainer.MetaContainerNotifyMetaSignalInfo)] :: [(Symbol, DK.Type)])
#endif
foreign import ccall "ges_effect_clip_new" ges_effect_clip_new ::
CString ->
CString ->
IO (Ptr EffectClip)
effectClipNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
Maybe (T.Text)
-> Maybe (T.Text)
-> m (Maybe EffectClip)
effectClipNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Maybe Text -> Maybe Text -> m (Maybe EffectClip)
effectClipNew Maybe Text
videoBinDescription Maybe Text
audioBinDescription = IO (Maybe EffectClip) -> m (Maybe EffectClip)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe EffectClip) -> m (Maybe EffectClip))
-> IO (Maybe EffectClip) -> m (Maybe EffectClip)
forall a b. (a -> b) -> a -> b
$ do
Ptr CChar
maybeVideoBinDescription <- case Maybe Text
videoBinDescription of
Maybe Text
Nothing -> Ptr CChar -> IO (Ptr CChar)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
nullPtr
Just Text
jVideoBinDescription -> do
Ptr CChar
jVideoBinDescription' <- Text -> IO (Ptr CChar)
textToCString Text
jVideoBinDescription
Ptr CChar -> IO (Ptr CChar)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
jVideoBinDescription'
Ptr CChar
maybeAudioBinDescription <- case Maybe Text
audioBinDescription of
Maybe Text
Nothing -> Ptr CChar -> IO (Ptr CChar)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
nullPtr
Just Text
jAudioBinDescription -> do
Ptr CChar
jAudioBinDescription' <- Text -> IO (Ptr CChar)
textToCString Text
jAudioBinDescription
Ptr CChar -> IO (Ptr CChar)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
jAudioBinDescription'
Ptr EffectClip
result <- Ptr CChar -> Ptr CChar -> IO (Ptr EffectClip)
ges_effect_clip_new Ptr CChar
maybeVideoBinDescription Ptr CChar
maybeAudioBinDescription
Maybe EffectClip
maybeResult <- Ptr EffectClip
-> (Ptr EffectClip -> IO EffectClip) -> IO (Maybe EffectClip)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr EffectClip
result ((Ptr EffectClip -> IO EffectClip) -> IO (Maybe EffectClip))
-> (Ptr EffectClip -> IO EffectClip) -> IO (Maybe EffectClip)
forall a b. (a -> b) -> a -> b
$ \Ptr EffectClip
result' -> do
EffectClip
result'' <- ((ManagedPtr EffectClip -> EffectClip)
-> Ptr EffectClip -> IO EffectClip
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr EffectClip -> EffectClip
EffectClip) Ptr EffectClip
result'
EffectClip -> IO EffectClip
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return EffectClip
result''
Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
maybeVideoBinDescription
Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
maybeAudioBinDescription
Maybe EffectClip -> IO (Maybe EffectClip)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe EffectClip
maybeResult
#if defined(ENABLE_OVERLOADING)
#endif