{-# LANGUAGE ImplicitParams, RankNTypes, TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.GES.Objects.Container
(
Container(..) ,
IsContainer ,
toContainer ,
#if defined(ENABLE_OVERLOADING)
ResolveContainerMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
ContainerAddMethodInfo ,
#endif
containerAdd ,
#if defined(ENABLE_OVERLOADING)
ContainerEditMethodInfo ,
#endif
containerEdit ,
#if defined(ENABLE_OVERLOADING)
ContainerGetChildrenMethodInfo ,
#endif
containerGetChildren ,
containerGroup ,
#if defined(ENABLE_OVERLOADING)
ContainerRemoveMethodInfo ,
#endif
containerRemove ,
#if defined(ENABLE_OVERLOADING)
ContainerUngroupMethodInfo ,
#endif
containerUngroup ,
#if defined(ENABLE_OVERLOADING)
ContainerHeightPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
containerHeight ,
#endif
getContainerHeight ,
ContainerChildAddedCallback ,
#if defined(ENABLE_OVERLOADING)
ContainerChildAddedSignalInfo ,
#endif
afterContainerChildAdded ,
onContainerChildAdded ,
ContainerChildRemovedCallback ,
#if defined(ENABLE_OVERLOADING)
ContainerChildRemovedSignalInfo ,
#endif
afterContainerChildRemoved ,
onContainerChildRemoved ,
) 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.Enums as GES.Enums
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.Layer as GES.Layer
import {-# SOURCE #-} qualified GI.GES.Objects.TimelineElement as GES.TimelineElement
import qualified GI.GObject.Objects.Object as GObject.Object
newtype Container = Container (SP.ManagedPtr Container)
deriving (Container -> Container -> Bool
(Container -> Container -> Bool)
-> (Container -> Container -> Bool) -> Eq Container
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Container -> Container -> Bool
== :: Container -> Container -> Bool
$c/= :: Container -> Container -> Bool
/= :: Container -> Container -> Bool
Eq)
instance SP.ManagedPtrNewtype Container where
toManagedPtr :: Container -> ManagedPtr Container
toManagedPtr (Container ManagedPtr Container
p) = ManagedPtr Container
p
foreign import ccall "ges_container_get_type"
c_ges_container_get_type :: IO B.Types.GType
instance B.Types.TypedObject Container where
glibType :: IO GType
glibType = IO GType
c_ges_container_get_type
instance B.Types.GObject Container
class (SP.GObject o, O.IsDescendantOf Container o) => IsContainer o
instance (SP.GObject o, O.IsDescendantOf Container o) => IsContainer o
instance O.HasParentTypes Container
type instance O.ParentTypes Container = '[GES.TimelineElement.TimelineElement, GObject.Object.Object, GES.Extractable.Extractable, GES.MetaContainer.MetaContainer]
toContainer :: (MIO.MonadIO m, IsContainer o) => o -> m Container
toContainer :: forall (m :: * -> *) o.
(MonadIO m, IsContainer o) =>
o -> m Container
toContainer = IO Container -> m Container
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Container -> m Container)
-> (o -> IO Container) -> o -> m Container
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr Container -> Container) -> o -> IO Container
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr Container -> Container
Container
instance B.GValue.IsGValue (Maybe Container) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_ges_container_get_type
gvalueSet_ :: Ptr GValue -> Maybe Container -> IO ()
gvalueSet_ Ptr GValue
gv Maybe Container
P.Nothing = Ptr GValue -> Ptr Container -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr Container
forall a. Ptr a
FP.nullPtr :: FP.Ptr Container)
gvalueSet_ Ptr GValue
gv (P.Just Container
obj) = Container -> (Ptr Container -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Container
obj (Ptr GValue -> Ptr Container -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe Container)
gvalueGet_ Ptr GValue
gv = do
Ptr Container
ptr <- Ptr GValue -> IO (Ptr Container)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr Container)
if Ptr Container
ptr Ptr Container -> Ptr Container -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr Container
forall a. Ptr a
FP.nullPtr
then Container -> Maybe Container
forall a. a -> Maybe a
P.Just (Container -> Maybe Container)
-> IO Container -> IO (Maybe Container)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr Container -> Container)
-> Ptr Container -> IO Container
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr Container -> Container
Container Ptr Container
ptr
else Maybe Container -> IO (Maybe Container)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Container
forall a. Maybe a
P.Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolveContainerMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolveContainerMethod "add" o = ContainerAddMethodInfo
ResolveContainerMethod "addChildProperty" o = GES.TimelineElement.TimelineElementAddChildPropertyMethodInfo
ResolveContainerMethod "addMetasFromString" o = GES.MetaContainer.MetaContainerAddMetasFromStringMethodInfo
ResolveContainerMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveContainerMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveContainerMethod "checkMetaRegistered" o = GES.MetaContainer.MetaContainerCheckMetaRegisteredMethodInfo
ResolveContainerMethod "copy" o = GES.TimelineElement.TimelineElementCopyMethodInfo
ResolveContainerMethod "edit" o = ContainerEditMethodInfo
ResolveContainerMethod "editFull" o = GES.TimelineElement.TimelineElementEditFullMethodInfo
ResolveContainerMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveContainerMethod "foreach" o = GES.MetaContainer.MetaContainerForeachMethodInfo
ResolveContainerMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveContainerMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveContainerMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveContainerMethod "listChildrenProperties" o = GES.TimelineElement.TimelineElementListChildrenPropertiesMethodInfo
ResolveContainerMethod "lookupChild" o = GES.TimelineElement.TimelineElementLookupChildMethodInfo
ResolveContainerMethod "metasToString" o = GES.MetaContainer.MetaContainerMetasToStringMethodInfo
ResolveContainerMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveContainerMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveContainerMethod "paste" o = GES.TimelineElement.TimelineElementPasteMethodInfo
ResolveContainerMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveContainerMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveContainerMethod "registerMeta" o = GES.MetaContainer.MetaContainerRegisterMetaMethodInfo
ResolveContainerMethod "registerMetaBoolean" o = GES.MetaContainer.MetaContainerRegisterMetaBooleanMethodInfo
ResolveContainerMethod "registerMetaDate" o = GES.MetaContainer.MetaContainerRegisterMetaDateMethodInfo
ResolveContainerMethod "registerMetaDateTime" o = GES.MetaContainer.MetaContainerRegisterMetaDateTimeMethodInfo
ResolveContainerMethod "registerMetaDouble" o = GES.MetaContainer.MetaContainerRegisterMetaDoubleMethodInfo
ResolveContainerMethod "registerMetaFloat" o = GES.MetaContainer.MetaContainerRegisterMetaFloatMethodInfo
ResolveContainerMethod "registerMetaInt" o = GES.MetaContainer.MetaContainerRegisterMetaIntMethodInfo
ResolveContainerMethod "registerMetaInt64" o = GES.MetaContainer.MetaContainerRegisterMetaInt64MethodInfo
ResolveContainerMethod "registerMetaString" o = GES.MetaContainer.MetaContainerRegisterMetaStringMethodInfo
ResolveContainerMethod "registerMetaUint" o = GES.MetaContainer.MetaContainerRegisterMetaUintMethodInfo
ResolveContainerMethod "registerMetaUint64" o = GES.MetaContainer.MetaContainerRegisterMetaUint64MethodInfo
ResolveContainerMethod "registerStaticMeta" o = GES.MetaContainer.MetaContainerRegisterStaticMetaMethodInfo
ResolveContainerMethod "remove" o = ContainerRemoveMethodInfo
ResolveContainerMethod "removeChildProperty" o = GES.TimelineElement.TimelineElementRemoveChildPropertyMethodInfo
ResolveContainerMethod "ripple" o = GES.TimelineElement.TimelineElementRippleMethodInfo
ResolveContainerMethod "rippleEnd" o = GES.TimelineElement.TimelineElementRippleEndMethodInfo
ResolveContainerMethod "rollEnd" o = GES.TimelineElement.TimelineElementRollEndMethodInfo
ResolveContainerMethod "rollStart" o = GES.TimelineElement.TimelineElementRollStartMethodInfo
ResolveContainerMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveContainerMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveContainerMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveContainerMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveContainerMethod "trim" o = GES.TimelineElement.TimelineElementTrimMethodInfo
ResolveContainerMethod "ungroup" o = ContainerUngroupMethodInfo
ResolveContainerMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveContainerMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveContainerMethod "getAsset" o = GES.Extractable.ExtractableGetAssetMethodInfo
ResolveContainerMethod "getBoolean" o = GES.MetaContainer.MetaContainerGetBooleanMethodInfo
ResolveContainerMethod "getChildProperty" o = GES.TimelineElement.TimelineElementGetChildPropertyMethodInfo
ResolveContainerMethod "getChildPropertyByPspec" o = GES.TimelineElement.TimelineElementGetChildPropertyByPspecMethodInfo
ResolveContainerMethod "getChildren" o = ContainerGetChildrenMethodInfo
ResolveContainerMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveContainerMethod "getDate" o = GES.MetaContainer.MetaContainerGetDateMethodInfo
ResolveContainerMethod "getDateTime" o = GES.MetaContainer.MetaContainerGetDateTimeMethodInfo
ResolveContainerMethod "getDouble" o = GES.MetaContainer.MetaContainerGetDoubleMethodInfo
ResolveContainerMethod "getDuration" o = GES.TimelineElement.TimelineElementGetDurationMethodInfo
ResolveContainerMethod "getFloat" o = GES.MetaContainer.MetaContainerGetFloatMethodInfo
ResolveContainerMethod "getId" o = GES.Extractable.ExtractableGetIdMethodInfo
ResolveContainerMethod "getInpoint" o = GES.TimelineElement.TimelineElementGetInpointMethodInfo
ResolveContainerMethod "getInt" o = GES.MetaContainer.MetaContainerGetIntMethodInfo
ResolveContainerMethod "getInt64" o = GES.MetaContainer.MetaContainerGetInt64MethodInfo
ResolveContainerMethod "getLayerPriority" o = GES.TimelineElement.TimelineElementGetLayerPriorityMethodInfo
ResolveContainerMethod "getMarkerList" o = GES.MetaContainer.MetaContainerGetMarkerListMethodInfo
ResolveContainerMethod "getMaxDuration" o = GES.TimelineElement.TimelineElementGetMaxDurationMethodInfo
ResolveContainerMethod "getMeta" o = GES.MetaContainer.MetaContainerGetMetaMethodInfo
ResolveContainerMethod "getName" o = GES.TimelineElement.TimelineElementGetNameMethodInfo
ResolveContainerMethod "getNaturalFramerate" o = GES.TimelineElement.TimelineElementGetNaturalFramerateMethodInfo
ResolveContainerMethod "getParent" o = GES.TimelineElement.TimelineElementGetParentMethodInfo
ResolveContainerMethod "getPriority" o = GES.TimelineElement.TimelineElementGetPriorityMethodInfo
ResolveContainerMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveContainerMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveContainerMethod "getStart" o = GES.TimelineElement.TimelineElementGetStartMethodInfo
ResolveContainerMethod "getString" o = GES.MetaContainer.MetaContainerGetStringMethodInfo
ResolveContainerMethod "getTimeline" o = GES.TimelineElement.TimelineElementGetTimelineMethodInfo
ResolveContainerMethod "getToplevelParent" o = GES.TimelineElement.TimelineElementGetToplevelParentMethodInfo
ResolveContainerMethod "getTrackTypes" o = GES.TimelineElement.TimelineElementGetTrackTypesMethodInfo
ResolveContainerMethod "getUint" o = GES.MetaContainer.MetaContainerGetUintMethodInfo
ResolveContainerMethod "getUint64" o = GES.MetaContainer.MetaContainerGetUint64MethodInfo
ResolveContainerMethod "setAsset" o = GES.Extractable.ExtractableSetAssetMethodInfo
ResolveContainerMethod "setBoolean" o = GES.MetaContainer.MetaContainerSetBooleanMethodInfo
ResolveContainerMethod "setChildProperty" o = GES.TimelineElement.TimelineElementSetChildPropertyMethodInfo
ResolveContainerMethod "setChildPropertyByPspec" o = GES.TimelineElement.TimelineElementSetChildPropertyByPspecMethodInfo
ResolveContainerMethod "setChildPropertyFull" o = GES.TimelineElement.TimelineElementSetChildPropertyFullMethodInfo
ResolveContainerMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveContainerMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveContainerMethod "setDate" o = GES.MetaContainer.MetaContainerSetDateMethodInfo
ResolveContainerMethod "setDateTime" o = GES.MetaContainer.MetaContainerSetDateTimeMethodInfo
ResolveContainerMethod "setDouble" o = GES.MetaContainer.MetaContainerSetDoubleMethodInfo
ResolveContainerMethod "setDuration" o = GES.TimelineElement.TimelineElementSetDurationMethodInfo
ResolveContainerMethod "setFloat" o = GES.MetaContainer.MetaContainerSetFloatMethodInfo
ResolveContainerMethod "setInpoint" o = GES.TimelineElement.TimelineElementSetInpointMethodInfo
ResolveContainerMethod "setInt" o = GES.MetaContainer.MetaContainerSetIntMethodInfo
ResolveContainerMethod "setInt64" o = GES.MetaContainer.MetaContainerSetInt64MethodInfo
ResolveContainerMethod "setMarkerList" o = GES.MetaContainer.MetaContainerSetMarkerListMethodInfo
ResolveContainerMethod "setMaxDuration" o = GES.TimelineElement.TimelineElementSetMaxDurationMethodInfo
ResolveContainerMethod "setMeta" o = GES.MetaContainer.MetaContainerSetMetaMethodInfo
ResolveContainerMethod "setName" o = GES.TimelineElement.TimelineElementSetNameMethodInfo
ResolveContainerMethod "setParent" o = GES.TimelineElement.TimelineElementSetParentMethodInfo
ResolveContainerMethod "setPriority" o = GES.TimelineElement.TimelineElementSetPriorityMethodInfo
ResolveContainerMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveContainerMethod "setStart" o = GES.TimelineElement.TimelineElementSetStartMethodInfo
ResolveContainerMethod "setString" o = GES.MetaContainer.MetaContainerSetStringMethodInfo
ResolveContainerMethod "setTimeline" o = GES.TimelineElement.TimelineElementSetTimelineMethodInfo
ResolveContainerMethod "setUint" o = GES.MetaContainer.MetaContainerSetUintMethodInfo
ResolveContainerMethod "setUint64" o = GES.MetaContainer.MetaContainerSetUint64MethodInfo
ResolveContainerMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveContainerMethod t Container, O.OverloadedMethod info Container p) => OL.IsLabel t (Container -> 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 ~ ResolveContainerMethod t Container, O.OverloadedMethod info Container p, R.HasField t Container p) => R.HasField t Container p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveContainerMethod t Container, O.OverloadedMethodInfo info Container) => OL.IsLabel t (O.MethodProxy info Container) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif
type ContainerChildAddedCallback =
GES.TimelineElement.TimelineElement
-> IO ()
type C_ContainerChildAddedCallback =
Ptr Container ->
Ptr GES.TimelineElement.TimelineElement ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_ContainerChildAddedCallback :: C_ContainerChildAddedCallback -> IO (FunPtr C_ContainerChildAddedCallback)
wrap_ContainerChildAddedCallback ::
GObject a => (a -> ContainerChildAddedCallback) ->
C_ContainerChildAddedCallback
wrap_ContainerChildAddedCallback :: forall a.
GObject a =>
(a -> ContainerChildAddedCallback) -> C_ContainerChildAddedCallback
wrap_ContainerChildAddedCallback a -> ContainerChildAddedCallback
gi'cb Ptr Container
gi'selfPtr Ptr TimelineElement
element Ptr ()
_ = do
TimelineElement
element' <- ((ManagedPtr TimelineElement -> TimelineElement)
-> Ptr TimelineElement -> IO TimelineElement
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr TimelineElement -> TimelineElement
GES.TimelineElement.TimelineElement) Ptr TimelineElement
element
Ptr Container -> (Container -> IO ()) -> IO ()
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr Container
gi'selfPtr ((Container -> IO ()) -> IO ()) -> (Container -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Container
gi'self -> a -> ContainerChildAddedCallback
gi'cb (Container -> a
forall a b. Coercible a b => a -> b
Coerce.coerce Container
gi'self) TimelineElement
element'
onContainerChildAdded :: (IsContainer a, MonadIO m) => a -> ((?self :: a) => ContainerChildAddedCallback) -> m SignalHandlerId
onContainerChildAdded :: forall a (m :: * -> *).
(IsContainer a, MonadIO m) =>
a
-> ((?self::a) => ContainerChildAddedCallback) -> m SignalHandlerId
onContainerChildAdded a
obj (?self::a) => ContainerChildAddedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let wrapped :: a -> ContainerChildAddedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => ContainerChildAddedCallback
ContainerChildAddedCallback
cb
let wrapped' :: C_ContainerChildAddedCallback
wrapped' = (a -> ContainerChildAddedCallback) -> C_ContainerChildAddedCallback
forall a.
GObject a =>
(a -> ContainerChildAddedCallback) -> C_ContainerChildAddedCallback
wrap_ContainerChildAddedCallback a -> ContainerChildAddedCallback
wrapped
FunPtr C_ContainerChildAddedCallback
wrapped'' <- C_ContainerChildAddedCallback
-> IO (FunPtr C_ContainerChildAddedCallback)
mk_ContainerChildAddedCallback C_ContainerChildAddedCallback
wrapped'
a
-> Text
-> FunPtr C_ContainerChildAddedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"child-added" FunPtr C_ContainerChildAddedCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterContainerChildAdded :: (IsContainer a, MonadIO m) => a -> ((?self :: a) => ContainerChildAddedCallback) -> m SignalHandlerId
afterContainerChildAdded :: forall a (m :: * -> *).
(IsContainer a, MonadIO m) =>
a
-> ((?self::a) => ContainerChildAddedCallback) -> m SignalHandlerId
afterContainerChildAdded a
obj (?self::a) => ContainerChildAddedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let wrapped :: a -> ContainerChildAddedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => ContainerChildAddedCallback
ContainerChildAddedCallback
cb
let wrapped' :: C_ContainerChildAddedCallback
wrapped' = (a -> ContainerChildAddedCallback) -> C_ContainerChildAddedCallback
forall a.
GObject a =>
(a -> ContainerChildAddedCallback) -> C_ContainerChildAddedCallback
wrap_ContainerChildAddedCallback a -> ContainerChildAddedCallback
wrapped
FunPtr C_ContainerChildAddedCallback
wrapped'' <- C_ContainerChildAddedCallback
-> IO (FunPtr C_ContainerChildAddedCallback)
mk_ContainerChildAddedCallback C_ContainerChildAddedCallback
wrapped'
a
-> Text
-> FunPtr C_ContainerChildAddedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"child-added" FunPtr C_ContainerChildAddedCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data ContainerChildAddedSignalInfo
instance SignalInfo ContainerChildAddedSignalInfo where
type HaskellCallbackType ContainerChildAddedSignalInfo = ContainerChildAddedCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_ContainerChildAddedCallback cb
cb'' <- mk_ContainerChildAddedCallback cb'
connectSignalFunPtr obj "child-added" cb'' connectMode detail
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GES.Objects.Container::child-added"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.4/docs/GI-GES-Objects-Container.html#g:signal:childAdded"})
#endif
type ContainerChildRemovedCallback =
GES.TimelineElement.TimelineElement
-> IO ()
type C_ContainerChildRemovedCallback =
Ptr Container ->
Ptr GES.TimelineElement.TimelineElement ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_ContainerChildRemovedCallback :: C_ContainerChildRemovedCallback -> IO (FunPtr C_ContainerChildRemovedCallback)
wrap_ContainerChildRemovedCallback ::
GObject a => (a -> ContainerChildRemovedCallback) ->
C_ContainerChildRemovedCallback
wrap_ContainerChildRemovedCallback :: forall a.
GObject a =>
(a -> ContainerChildAddedCallback) -> C_ContainerChildAddedCallback
wrap_ContainerChildRemovedCallback a -> ContainerChildAddedCallback
gi'cb Ptr Container
gi'selfPtr Ptr TimelineElement
element Ptr ()
_ = do
TimelineElement
element' <- ((ManagedPtr TimelineElement -> TimelineElement)
-> Ptr TimelineElement -> IO TimelineElement
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr TimelineElement -> TimelineElement
GES.TimelineElement.TimelineElement) Ptr TimelineElement
element
Ptr Container -> (Container -> IO ()) -> IO ()
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr Container
gi'selfPtr ((Container -> IO ()) -> IO ()) -> (Container -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Container
gi'self -> a -> ContainerChildAddedCallback
gi'cb (Container -> a
forall a b. Coercible a b => a -> b
Coerce.coerce Container
gi'self) TimelineElement
element'
onContainerChildRemoved :: (IsContainer a, MonadIO m) => a -> ((?self :: a) => ContainerChildRemovedCallback) -> m SignalHandlerId
onContainerChildRemoved :: forall a (m :: * -> *).
(IsContainer a, MonadIO m) =>
a
-> ((?self::a) => ContainerChildAddedCallback) -> m SignalHandlerId
onContainerChildRemoved a
obj (?self::a) => ContainerChildAddedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let wrapped :: a -> ContainerChildAddedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => ContainerChildAddedCallback
ContainerChildAddedCallback
cb
let wrapped' :: C_ContainerChildAddedCallback
wrapped' = (a -> ContainerChildAddedCallback) -> C_ContainerChildAddedCallback
forall a.
GObject a =>
(a -> ContainerChildAddedCallback) -> C_ContainerChildAddedCallback
wrap_ContainerChildRemovedCallback a -> ContainerChildAddedCallback
wrapped
FunPtr C_ContainerChildAddedCallback
wrapped'' <- C_ContainerChildAddedCallback
-> IO (FunPtr C_ContainerChildAddedCallback)
mk_ContainerChildRemovedCallback C_ContainerChildAddedCallback
wrapped'
a
-> Text
-> FunPtr C_ContainerChildAddedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"child-removed" FunPtr C_ContainerChildAddedCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterContainerChildRemoved :: (IsContainer a, MonadIO m) => a -> ((?self :: a) => ContainerChildRemovedCallback) -> m SignalHandlerId
afterContainerChildRemoved :: forall a (m :: * -> *).
(IsContainer a, MonadIO m) =>
a
-> ((?self::a) => ContainerChildAddedCallback) -> m SignalHandlerId
afterContainerChildRemoved a
obj (?self::a) => ContainerChildAddedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let wrapped :: a -> ContainerChildAddedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => ContainerChildAddedCallback
ContainerChildAddedCallback
cb
let wrapped' :: C_ContainerChildAddedCallback
wrapped' = (a -> ContainerChildAddedCallback) -> C_ContainerChildAddedCallback
forall a.
GObject a =>
(a -> ContainerChildAddedCallback) -> C_ContainerChildAddedCallback
wrap_ContainerChildRemovedCallback a -> ContainerChildAddedCallback
wrapped
FunPtr C_ContainerChildAddedCallback
wrapped'' <- C_ContainerChildAddedCallback
-> IO (FunPtr C_ContainerChildAddedCallback)
mk_ContainerChildRemovedCallback C_ContainerChildAddedCallback
wrapped'
a
-> Text
-> FunPtr C_ContainerChildAddedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"child-removed" FunPtr C_ContainerChildAddedCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data ContainerChildRemovedSignalInfo
instance SignalInfo ContainerChildRemovedSignalInfo where
type HaskellCallbackType ContainerChildRemovedSignalInfo = ContainerChildRemovedCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_ContainerChildRemovedCallback cb
cb'' <- mk_ContainerChildRemovedCallback cb'
connectSignalFunPtr obj "child-removed" cb'' connectMode detail
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GES.Objects.Container::child-removed"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.4/docs/GI-GES-Objects-Container.html#g:signal:childRemoved"})
#endif
getContainerHeight :: (MonadIO m, IsContainer o) => o -> m Word32
getContainerHeight :: forall (m :: * -> *) o. (MonadIO m, IsContainer o) => o -> m Word32
getContainerHeight o
obj = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Word32
forall a. GObject a => a -> String -> IO Word32
B.Properties.getObjectPropertyUInt32 o
obj String
"height"
#if defined(ENABLE_OVERLOADING)
data ContainerHeightPropertyInfo
instance AttrInfo ContainerHeightPropertyInfo where
type AttrAllowedOps ContainerHeightPropertyInfo = '[ 'AttrGet]
type AttrBaseTypeConstraint ContainerHeightPropertyInfo = IsContainer
type AttrSetTypeConstraint ContainerHeightPropertyInfo = (~) ()
type AttrTransferTypeConstraint ContainerHeightPropertyInfo = (~) ()
type AttrTransferType ContainerHeightPropertyInfo = ()
type AttrGetType ContainerHeightPropertyInfo = Word32
type AttrLabel ContainerHeightPropertyInfo = "height"
type AttrOrigin ContainerHeightPropertyInfo = Container
attrGet = getContainerHeight
attrSet = undefined
attrTransfer _ = undefined
attrConstruct = undefined
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GES.Objects.Container.height"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.4/docs/GI-GES-Objects-Container.html#g:attr:height"
})
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Container
type instance O.AttributeList Container = ContainerAttributeList
type ContainerAttributeList = ('[ '("duration", GES.TimelineElement.TimelineElementDurationPropertyInfo), '("height", ContainerHeightPropertyInfo), '("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)] :: [(Symbol, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
containerHeight :: AttrLabelProxy "height"
containerHeight = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Container = ContainerSignalList
type ContainerSignalList = ('[ '("childAdded", ContainerChildAddedSignalInfo), '("childPropertyAdded", GES.TimelineElement.TimelineElementChildPropertyAddedSignalInfo), '("childPropertyRemoved", GES.TimelineElement.TimelineElementChildPropertyRemovedSignalInfo), '("childRemoved", ContainerChildRemovedSignalInfo), '("deepNotify", GES.TimelineElement.TimelineElementDeepNotifySignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("notifyMeta", GES.MetaContainer.MetaContainerNotifyMetaSignalInfo)] :: [(Symbol, DK.Type)])
#endif
foreign import ccall "ges_container_add" ges_container_add ::
Ptr Container ->
Ptr GES.TimelineElement.TimelineElement ->
IO CInt
containerAdd ::
(B.CallStack.HasCallStack, MonadIO m, IsContainer a, GES.TimelineElement.IsTimelineElement b) =>
a
-> b
-> m Bool
containerAdd :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsContainer a, IsTimelineElement b) =>
a -> b -> m Bool
containerAdd a
container b
child = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
Ptr Container
container' <- a -> IO (Ptr Container)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
container
Ptr TimelineElement
child' <- b -> IO (Ptr TimelineElement)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
child
CInt
result <- Ptr Container -> Ptr TimelineElement -> IO CInt
ges_container_add Ptr Container
container' Ptr TimelineElement
child'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
container
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
child
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data ContainerAddMethodInfo
instance (signature ~ (b -> m Bool), MonadIO m, IsContainer a, GES.TimelineElement.IsTimelineElement b) => O.OverloadedMethod ContainerAddMethodInfo a signature where
overloadedMethod = containerAdd
instance O.OverloadedMethodInfo ContainerAddMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GES.Objects.Container.containerAdd",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.4/docs/GI-GES-Objects-Container.html#v:containerAdd"
})
#endif
foreign import ccall "ges_container_edit" ges_container_edit ::
Ptr Container ->
Ptr (GList (Ptr GES.Layer.Layer)) ->
Int32 ->
CUInt ->
CUInt ->
Word64 ->
IO CInt
{-# DEPRECATED containerEdit ["(Since version 1.18)","use @/ges_timeline_element_edit/@ instead."] #-}
containerEdit ::
(B.CallStack.HasCallStack, MonadIO m, IsContainer a, GES.Layer.IsLayer b) =>
a
-> [b]
-> Int32
-> GES.Enums.EditMode
-> GES.Enums.Edge
-> Word64
-> m Bool
containerEdit :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsContainer a, IsLayer b) =>
a -> [b] -> Int32 -> EditMode -> Edge -> Word64 -> m Bool
containerEdit a
container [b]
layers Int32
newLayerPriority EditMode
mode Edge
edge Word64
position = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
Ptr Container
container' <- a -> IO (Ptr Container)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
container
[Ptr Layer]
layers' <- (b -> IO (Ptr Layer)) -> [b] -> IO [Ptr Layer]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM b -> IO (Ptr Layer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr [b]
layers
Ptr (GList (Ptr Layer))
layers'' <- [Ptr Layer] -> IO (Ptr (GList (Ptr Layer)))
forall a. [Ptr a] -> IO (Ptr (GList (Ptr a)))
packGList [Ptr Layer]
layers'
let mode' :: CUInt
mode' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (EditMode -> Int) -> EditMode -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EditMode -> Int
forall a. Enum a => a -> Int
fromEnum) EditMode
mode
let edge' :: CUInt
edge' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (Edge -> Int) -> Edge -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Edge -> Int
forall a. Enum a => a -> Int
fromEnum) Edge
edge
CInt
result <- Ptr Container
-> Ptr (GList (Ptr Layer))
-> Int32
-> CUInt
-> CUInt
-> Word64
-> IO CInt
ges_container_edit Ptr Container
container' Ptr (GList (Ptr Layer))
layers'' Int32
newLayerPriority CUInt
mode' CUInt
edge' Word64
position
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
container
(b -> IO ()) -> [b] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr [b]
layers
Ptr (GList (Ptr Layer)) -> IO ()
forall a. Ptr (GList a) -> IO ()
g_list_free Ptr (GList (Ptr Layer))
layers''
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data ContainerEditMethodInfo
instance (signature ~ ([b] -> Int32 -> GES.Enums.EditMode -> GES.Enums.Edge -> Word64 -> m Bool), MonadIO m, IsContainer a, GES.Layer.IsLayer b) => O.OverloadedMethod ContainerEditMethodInfo a signature where
overloadedMethod = containerEdit
instance O.OverloadedMethodInfo ContainerEditMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GES.Objects.Container.containerEdit",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.4/docs/GI-GES-Objects-Container.html#v:containerEdit"
})
#endif
foreign import ccall "ges_container_get_children" ges_container_get_children ::
Ptr Container ->
CInt ->
IO (Ptr (GList (Ptr GES.TimelineElement.TimelineElement)))
containerGetChildren ::
(B.CallStack.HasCallStack, MonadIO m, IsContainer a) =>
a
-> Bool
-> m [GES.TimelineElement.TimelineElement]
containerGetChildren :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsContainer a) =>
a -> Bool -> m [TimelineElement]
containerGetChildren a
container Bool
recursive = IO [TimelineElement] -> m [TimelineElement]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [TimelineElement] -> m [TimelineElement])
-> IO [TimelineElement] -> m [TimelineElement]
forall a b. (a -> b) -> a -> b
$ do
Ptr Container
container' <- a -> IO (Ptr Container)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
container
let recursive' :: CInt
recursive' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
P.fromEnum) Bool
recursive
Ptr (GList (Ptr TimelineElement))
result <- Ptr Container -> CInt -> IO (Ptr (GList (Ptr TimelineElement)))
ges_container_get_children Ptr Container
container' CInt
recursive'
[Ptr TimelineElement]
result' <- Ptr (GList (Ptr TimelineElement)) -> IO [Ptr TimelineElement]
forall a. Ptr (GList (Ptr a)) -> IO [Ptr a]
unpackGList Ptr (GList (Ptr TimelineElement))
result
[TimelineElement]
result'' <- (Ptr TimelineElement -> IO TimelineElement)
-> [Ptr TimelineElement] -> IO [TimelineElement]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM ((ManagedPtr TimelineElement -> TimelineElement)
-> Ptr TimelineElement -> IO TimelineElement
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr TimelineElement -> TimelineElement
GES.TimelineElement.TimelineElement) [Ptr TimelineElement]
result'
Ptr (GList (Ptr TimelineElement)) -> IO ()
forall a. Ptr (GList a) -> IO ()
g_list_free Ptr (GList (Ptr TimelineElement))
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
container
[TimelineElement] -> IO [TimelineElement]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [TimelineElement]
result''
#if defined(ENABLE_OVERLOADING)
data ContainerGetChildrenMethodInfo
instance (signature ~ (Bool -> m [GES.TimelineElement.TimelineElement]), MonadIO m, IsContainer a) => O.OverloadedMethod ContainerGetChildrenMethodInfo a signature where
overloadedMethod = containerGetChildren
instance O.OverloadedMethodInfo ContainerGetChildrenMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GES.Objects.Container.containerGetChildren",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.4/docs/GI-GES-Objects-Container.html#v:containerGetChildren"
})
#endif
foreign import ccall "ges_container_remove" ges_container_remove ::
Ptr Container ->
Ptr GES.TimelineElement.TimelineElement ->
IO CInt
containerRemove ::
(B.CallStack.HasCallStack, MonadIO m, IsContainer a, GES.TimelineElement.IsTimelineElement b) =>
a
-> b
-> m Bool
containerRemove :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsContainer a, IsTimelineElement b) =>
a -> b -> m Bool
containerRemove a
container b
child = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
Ptr Container
container' <- a -> IO (Ptr Container)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
container
Ptr TimelineElement
child' <- b -> IO (Ptr TimelineElement)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
child
CInt
result <- Ptr Container -> Ptr TimelineElement -> IO CInt
ges_container_remove Ptr Container
container' Ptr TimelineElement
child'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
container
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
child
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data ContainerRemoveMethodInfo
instance (signature ~ (b -> m Bool), MonadIO m, IsContainer a, GES.TimelineElement.IsTimelineElement b) => O.OverloadedMethod ContainerRemoveMethodInfo a signature where
overloadedMethod = containerRemove
instance O.OverloadedMethodInfo ContainerRemoveMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GES.Objects.Container.containerRemove",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.4/docs/GI-GES-Objects-Container.html#v:containerRemove"
})
#endif
foreign import ccall "ges_container_ungroup" ges_container_ungroup ::
Ptr Container ->
CInt ->
IO (Ptr (GList (Ptr Container)))
containerUngroup ::
(B.CallStack.HasCallStack, MonadIO m, IsContainer a) =>
a
-> Bool
-> m [Container]
containerUngroup :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsContainer a) =>
a -> Bool -> m [Container]
containerUngroup a
container Bool
recursive = IO [Container] -> m [Container]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Container] -> m [Container])
-> IO [Container] -> m [Container]
forall a b. (a -> b) -> a -> b
$ do
Ptr Container
container' <- a -> IO (Ptr Container)
forall a b. (HasCallStack, GObject a) => a -> IO (Ptr b)
B.ManagedPtr.disownObject a
container
let recursive' :: CInt
recursive' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
P.fromEnum) Bool
recursive
Ptr (GList (Ptr Container))
result <- Ptr Container -> CInt -> IO (Ptr (GList (Ptr Container)))
ges_container_ungroup Ptr Container
container' CInt
recursive'
[Ptr Container]
result' <- Ptr (GList (Ptr Container)) -> IO [Ptr Container]
forall a. Ptr (GList (Ptr a)) -> IO [Ptr a]
unpackGList Ptr (GList (Ptr Container))
result
[Container]
result'' <- (Ptr Container -> IO Container)
-> [Ptr Container] -> IO [Container]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM ((ManagedPtr Container -> Container)
-> Ptr Container -> IO Container
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Container -> Container
Container) [Ptr Container]
result'
Ptr (GList (Ptr Container)) -> IO ()
forall a. Ptr (GList a) -> IO ()
g_list_free Ptr (GList (Ptr Container))
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
container
[Container] -> IO [Container]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [Container]
result''
#if defined(ENABLE_OVERLOADING)
data ContainerUngroupMethodInfo
instance (signature ~ (Bool -> m [Container]), MonadIO m, IsContainer a) => O.OverloadedMethod ContainerUngroupMethodInfo a signature where
overloadedMethod = containerUngroup
instance O.OverloadedMethodInfo ContainerUngroupMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GES.Objects.Container.containerUngroup",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.4/docs/GI-GES-Objects-Container.html#v:containerUngroup"
})
#endif
foreign import ccall "ges_container_group" ges_container_group ::
Ptr (GList (Ptr Container)) ->
IO (Ptr Container)
containerGroup ::
(B.CallStack.HasCallStack, MonadIO m, IsContainer a) =>
[a]
-> m (Maybe Container)
containerGroup :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsContainer a) =>
[a] -> m (Maybe Container)
containerGroup [a]
containers = IO (Maybe Container) -> m (Maybe Container)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Container) -> m (Maybe Container))
-> IO (Maybe Container) -> m (Maybe Container)
forall a b. (a -> b) -> a -> b
$ do
[Ptr Container]
containers' <- (a -> IO (Ptr Container)) -> [a] -> IO [Ptr Container]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM a -> IO (Ptr Container)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr [a]
containers
Ptr (GList (Ptr Container))
containers'' <- [Ptr Container] -> IO (Ptr (GList (Ptr Container)))
forall a. [Ptr a] -> IO (Ptr (GList (Ptr a)))
packGList [Ptr Container]
containers'
Ptr Container
result <- Ptr (GList (Ptr Container)) -> IO (Ptr Container)
ges_container_group Ptr (GList (Ptr Container))
containers''
Maybe Container
maybeResult <- Ptr Container
-> (Ptr Container -> IO Container) -> IO (Maybe Container)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Container
result ((Ptr Container -> IO Container) -> IO (Maybe Container))
-> (Ptr Container -> IO Container) -> IO (Maybe Container)
forall a b. (a -> b) -> a -> b
$ \Ptr Container
result' -> do
Container
result'' <- ((ManagedPtr Container -> Container)
-> Ptr Container -> IO Container
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Container -> Container
Container) Ptr Container
result'
Container -> IO Container
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Container
result''
(a -> IO ()) -> [a] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr [a]
containers
Ptr (GList (Ptr Container)) -> IO ()
forall a. Ptr (GList a) -> IO ()
g_list_free Ptr (GList (Ptr Container))
containers''
Maybe Container -> IO (Maybe Container)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Container
maybeResult
#if defined(ENABLE_OVERLOADING)
#endif