{-# LANGUAGE ImplicitParams, RankNTypes, TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- t'GI.GES.Objects.Timeline.Timeline' is the central object for any multimedia timeline.
-- 
-- A timeline is composed of a set of t'GI.GES.Objects.Track.Track'-s and a set of
-- t'GI.GES.Objects.Layer.Layer'-s, which are added to the timeline using
-- 'GI.GES.Objects.Timeline.timelineAddTrack' and 'GI.GES.Objects.Timeline.timelineAppendLayer', respectively.
-- 
-- The contained tracks define the supported types of the timeline
-- and provide the media output. Essentially, each track provides an
-- additional source t'GI.Gst.Objects.Pad.Pad'.
-- 
-- Most usage of a timeline will likely only need a single t'GI.GES.Objects.AudioTrack.AudioTrack'
-- and\/or a single t'GI.GES.Objects.VideoTrack.VideoTrack'. You can create such a timeline with
-- 'GI.GES.Objects.Timeline.timelineNewAudioVideo'. After this, you are unlikely to need to
-- work with the tracks directly.
-- 
-- A timeline\'s layers contain t'GI.GES.Objects.Clip.Clip'-s, which in turn control the
-- creation of t'GI.GES.Objects.TrackElement.TrackElement'-s, which are added to the timeline\'s
-- tracks. See [Timeline::selectTracksForObject]("GI.GES.Objects.Timeline#g:signal:selectTracksForObject") if you wish to have
-- more control over which track a clip\'s elements are added to.
-- 
-- The layers are ordered, with higher priority layers having their
-- content prioritised in the tracks. This ordering can be changed using
-- 'GI.GES.Objects.Timeline.timelineMoveLayer'.
-- 
-- == Editing
-- 
-- See t'GI.GES.Objects.TimelineElement.TimelineElement' for the various ways the elements of a timeline
-- can be edited.
-- 
-- If you change the timing or ordering of a timeline\'s
-- t'GI.GES.Objects.TimelineElement.TimelineElement'-s, then these changes will not actually be taken
-- into account in the output of the timeline\'s tracks until the
-- 'GI.GES.Objects.Timeline.timelineCommit' method is called. This allows you to move its
-- elements around, say, in response to an end user\'s mouse dragging, with
-- little expense before finalising their effect on the produced data.
-- 
-- == Overlaps and Auto-Transitions
-- 
-- There are certain restrictions placed on how t'GI.GES.Objects.Source.Source'-s may overlap
-- in a t'GI.GES.Objects.Track.Track' that belongs to a timeline. These will be enforced by
-- GES, so the user will not need to keep track of them, but they should
-- be aware that certain edits will be refused as a result if the overlap
-- rules would be broken.
-- 
-- Consider two t'GI.GES.Objects.Source.Source'-s, @A@ and @B@, with start times @startA@ and
-- @startB@, and end times @endA@ and @endB@, respectively. The start
-- time refers to their [TimelineElement:start]("GI.GES.Objects.TimelineElement#g:attr:start"), and the end time is
-- their [TimelineElement:start]("GI.GES.Objects.TimelineElement#g:attr:start") + [TimelineElement:duration]("GI.GES.Objects.TimelineElement#g:attr:duration"). These
-- two sources *overlap* if:
-- 
-- + they share the same [TrackElement:track]("GI.GES.Objects.TrackElement#g:attr:track") (non 'P.Nothing'), which belongs
--   to the timeline;
-- + they share the same @/GES_TIMELINE_ELEMENT_LAYER_PRIORITY/@; and
-- + @startA \< endB@ and @startB \< endA @.
-- 
-- Note that when @startA = endB@ or @startB = endA@ then the two sources
-- will *touch* at their edges, but are not considered overlapping.
-- 
-- If, in addition, @startA \< startB \< endA@, then we can say that the
-- end of @A@ overlaps the start of @B@.
-- 
-- If, instead, @startA \<= startB@ and @endA >= endB@, then we can say
-- that @A@ fully overlaps @B@.
-- 
-- The overlap rules for a timeline are that:
-- 
-- 1. One source cannot fully overlap another source.
-- 2. A source can only overlap the end of up to one other source at its
--    start.
-- 3. A source can only overlap the start of up to one other source at its
--    end.
-- 
-- The last two rules combined essentially mean that at any given timeline
-- position, only up to two t'GI.GES.Objects.Source.Source'-s may overlap at that position. So
-- triple or more overlaps are not allowed.
-- 
-- If you switch on [Timeline:autoTransition]("GI.GES.Objects.Timeline#g:attr:autoTransition"), then at any moment when
-- the end of one source (the first source) overlaps the start of another
-- (the second source), a t'GI.GES.Objects.TransitionClip.TransitionClip' will be automatically created
-- for the pair in the same layer and it will cover their overlap. If the
-- two elements are edited in a way such that the end of the first source
-- no longer overlaps the start of the second, the transition will be
-- automatically removed from the timeline. However, if the two sources
-- still overlap at the same edges after the edit, then the same
-- transition object will be kept, but with its timing and layer adjusted
-- accordingly.
-- 
-- == Saving
-- 
-- To save\/load a timeline, you can use the 'GI.GES.Objects.Timeline.timelineLoadFromUri'
-- and 'GI.GES.Objects.Timeline.timelineSaveToUri' methods that use the default format.
-- 
-- == Playing
-- 
-- A timeline is a t'GI.Gst.Objects.Bin.Bin' with a source t'GI.Gst.Objects.Pad.Pad' for each of its
-- tracks, which you can fetch with 'GI.GES.Objects.Timeline.timelineGetPadForTrack'. You
-- will likely want to link these to some compatible sink t'GI.Gst.Objects.Element.Element'-s to
-- be able to play or capture the content of the timeline.
-- 
-- You can use a t'GI.GES.Objects.Pipeline.Pipeline' to easily preview\/play the timeline\'s
-- content, or render it to a file.

#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif

module GI.GES.Objects.Timeline
    ( 

-- * Exported types
    Timeline(..)                            ,
    IsTimeline                              ,
    toTimeline                              ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [abortState]("GI.Gst.Objects.Element#g:method:abortState"), [add]("GI.Gst.Objects.Bin#g:method:add"), [addControlBinding]("GI.Gst.Objects.Object#g:method:addControlBinding"), [addLayer]("GI.GES.Objects.Timeline#g:method:addLayer"), [addMetasFromString]("GI.GES.Interfaces.MetaContainer#g:method:addMetasFromString"), [addPad]("GI.Gst.Objects.Element#g:method:addPad"), [addPropertyDeepNotifyWatch]("GI.Gst.Objects.Element#g:method:addPropertyDeepNotifyWatch"), [addPropertyNotifyWatch]("GI.Gst.Objects.Element#g:method:addPropertyNotifyWatch"), [addTrack]("GI.GES.Objects.Timeline#g:method:addTrack"), [appendLayer]("GI.GES.Objects.Timeline#g:method:appendLayer"), [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [callAsync]("GI.Gst.Objects.Element#g:method:callAsync"), [changeState]("GI.Gst.Objects.Element#g:method:changeState"), [checkMetaRegistered]("GI.GES.Interfaces.MetaContainer#g:method:checkMetaRegistered"), [childAdded]("GI.Gst.Interfaces.ChildProxy#g:method:childAdded"), [childRemoved]("GI.Gst.Interfaces.ChildProxy#g:method:childRemoved"), [commit]("GI.GES.Objects.Timeline#g:method:commit"), [commitSync]("GI.GES.Objects.Timeline#g:method:commitSync"), [continueState]("GI.Gst.Objects.Element#g:method:continueState"), [createAllPads]("GI.Gst.Objects.Element#g:method:createAllPads"), [defaultError]("GI.Gst.Objects.Object#g:method:defaultError"), [findUnlinkedPad]("GI.Gst.Objects.Bin#g:method:findUnlinkedPad"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [foreach]("GI.GES.Interfaces.MetaContainer#g:method:foreach"), [foreachPad]("GI.Gst.Objects.Element#g:method:foreachPad"), [foreachSinkPad]("GI.Gst.Objects.Element#g:method:foreachSinkPad"), [foreachSrcPad]("GI.Gst.Objects.Element#g:method:foreachSrcPad"), [freezeCommit]("GI.GES.Objects.Timeline#g:method:freezeCommit"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [hasActiveControlBindings]("GI.Gst.Objects.Object#g:method:hasActiveControlBindings"), [hasAncestor]("GI.Gst.Objects.Object#g:method:hasAncestor"), [hasAsAncestor]("GI.Gst.Objects.Object#g:method:hasAsAncestor"), [hasAsParent]("GI.Gst.Objects.Object#g:method:hasAsParent"), [isEmpty]("GI.GES.Objects.Timeline#g:method:isEmpty"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [isLockedState]("GI.Gst.Objects.Element#g:method:isLockedState"), [iterateAllByElementFactoryName]("GI.Gst.Objects.Bin#g:method:iterateAllByElementFactoryName"), [iterateAllByInterface]("GI.Gst.Objects.Bin#g:method:iterateAllByInterface"), [iterateElements]("GI.Gst.Objects.Bin#g:method:iterateElements"), [iteratePads]("GI.Gst.Objects.Element#g:method:iteratePads"), [iterateRecurse]("GI.Gst.Objects.Bin#g:method:iterateRecurse"), [iterateSinkPads]("GI.Gst.Objects.Element#g:method:iterateSinkPads"), [iterateSinks]("GI.Gst.Objects.Bin#g:method:iterateSinks"), [iterateSorted]("GI.Gst.Objects.Bin#g:method:iterateSorted"), [iterateSources]("GI.Gst.Objects.Bin#g:method:iterateSources"), [iterateSrcPads]("GI.Gst.Objects.Element#g:method:iterateSrcPads"), [link]("GI.Gst.Objects.Element#g:method:link"), [linkFiltered]("GI.Gst.Objects.Element#g:method:linkFiltered"), [linkPads]("GI.Gst.Objects.Element#g:method:linkPads"), [linkPadsFiltered]("GI.Gst.Objects.Element#g:method:linkPadsFiltered"), [linkPadsFull]("GI.Gst.Objects.Element#g:method:linkPadsFull"), [loadFromUri]("GI.GES.Objects.Timeline#g:method:loadFromUri"), [lookup]("GI.Gst.Interfaces.ChildProxy#g:method:lookup"), [lostState]("GI.Gst.Objects.Element#g:method:lostState"), [messageFull]("GI.Gst.Objects.Element#g:method:messageFull"), [messageFullWithDetails]("GI.Gst.Objects.Element#g:method:messageFullWithDetails"), [metasToString]("GI.GES.Interfaces.MetaContainer#g:method:metasToString"), [moveLayer]("GI.GES.Objects.Timeline#g:method:moveLayer"), [noMorePads]("GI.Gst.Objects.Element#g:method:noMorePads"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [pasteElement]("GI.GES.Objects.Timeline#g:method:pasteElement"), [postMessage]("GI.Gst.Objects.Element#g:method:postMessage"), [provideClock]("GI.Gst.Objects.Element#g:method:provideClock"), [query]("GI.Gst.Objects.Element#g:method:query"), [queryConvert]("GI.Gst.Objects.Element#g:method:queryConvert"), [queryDuration]("GI.Gst.Objects.Element#g:method:queryDuration"), [queryPosition]("GI.Gst.Objects.Element#g:method:queryPosition"), [recalculateLatency]("GI.Gst.Objects.Bin#g:method:recalculateLatency"), [ref]("GI.Gst.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [registerMeta]("GI.GES.Interfaces.MetaContainer#g:method:registerMeta"), [registerMetaBoolean]("GI.GES.Interfaces.MetaContainer#g:method:registerMetaBoolean"), [registerMetaDate]("GI.GES.Interfaces.MetaContainer#g:method:registerMetaDate"), [registerMetaDateTime]("GI.GES.Interfaces.MetaContainer#g:method:registerMetaDateTime"), [registerMetaDouble]("GI.GES.Interfaces.MetaContainer#g:method:registerMetaDouble"), [registerMetaFloat]("GI.GES.Interfaces.MetaContainer#g:method:registerMetaFloat"), [registerMetaInt]("GI.GES.Interfaces.MetaContainer#g:method:registerMetaInt"), [registerMetaInt64]("GI.GES.Interfaces.MetaContainer#g:method:registerMetaInt64"), [registerMetaString]("GI.GES.Interfaces.MetaContainer#g:method:registerMetaString"), [registerMetaUint]("GI.GES.Interfaces.MetaContainer#g:method:registerMetaUint"), [registerMetaUint64]("GI.GES.Interfaces.MetaContainer#g:method:registerMetaUint64"), [registerStaticMeta]("GI.GES.Interfaces.MetaContainer#g:method:registerStaticMeta"), [releaseRequestPad]("GI.Gst.Objects.Element#g:method:releaseRequestPad"), [remove]("GI.Gst.Objects.Bin#g:method:remove"), [removeControlBinding]("GI.Gst.Objects.Object#g:method:removeControlBinding"), [removeLayer]("GI.GES.Objects.Timeline#g:method:removeLayer"), [removePad]("GI.Gst.Objects.Element#g:method:removePad"), [removePropertyNotifyWatch]("GI.Gst.Objects.Element#g:method:removePropertyNotifyWatch"), [removeTrack]("GI.GES.Objects.Timeline#g:method:removeTrack"), [requestPad]("GI.Gst.Objects.Element#g:method:requestPad"), [requestPadSimple]("GI.Gst.Objects.Element#g:method:requestPadSimple"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [saveToUri]("GI.GES.Objects.Timeline#g:method:saveToUri"), [seek]("GI.Gst.Objects.Element#g:method:seek"), [seekSimple]("GI.Gst.Objects.Element#g:method:seekSimple"), [sendEvent]("GI.Gst.Objects.Element#g:method:sendEvent"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [suggestNextSync]("GI.Gst.Objects.Object#g:method:suggestNextSync"), [syncChildrenStates]("GI.Gst.Objects.Bin#g:method:syncChildrenStates"), [syncStateWithParent]("GI.Gst.Objects.Element#g:method:syncStateWithParent"), [syncValues]("GI.Gst.Objects.Object#g:method:syncValues"), [thawCommit]("GI.GES.Objects.Timeline#g:method:thawCommit"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unlink]("GI.Gst.Objects.Element#g:method:unlink"), [unlinkPads]("GI.Gst.Objects.Element#g:method:unlinkPads"), [unparent]("GI.Gst.Objects.Object#g:method:unparent"), [unref]("GI.Gst.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getAsset]("GI.GES.Interfaces.Extractable#g:method:getAsset"), [getAutoTransition]("GI.GES.Objects.Timeline#g:method:getAutoTransition"), [getBaseTime]("GI.Gst.Objects.Element#g:method:getBaseTime"), [getBoolean]("GI.GES.Interfaces.MetaContainer#g:method:getBoolean"), [getBus]("GI.Gst.Objects.Element#g:method:getBus"), [getByInterface]("GI.Gst.Objects.Bin#g:method:getByInterface"), [getByName]("GI.Gst.Objects.Bin#g:method:getByName"), [getByNameRecurseUp]("GI.Gst.Objects.Bin#g:method:getByNameRecurseUp"), [getChildByIndex]("GI.Gst.Interfaces.ChildProxy#g:method:getChildByIndex"), [getChildByName]("GI.Gst.Interfaces.ChildProxy#g:method:getChildByName"), [getChildrenCount]("GI.Gst.Interfaces.ChildProxy#g:method:getChildrenCount"), [getClock]("GI.Gst.Objects.Element#g:method:getClock"), [getCompatiblePad]("GI.Gst.Objects.Element#g:method:getCompatiblePad"), [getCompatiblePadTemplate]("GI.Gst.Objects.Element#g:method:getCompatiblePadTemplate"), [getContext]("GI.Gst.Objects.Element#g:method:getContext"), [getContextUnlocked]("GI.Gst.Objects.Element#g:method:getContextUnlocked"), [getContexts]("GI.Gst.Objects.Element#g:method:getContexts"), [getControlBinding]("GI.Gst.Objects.Object#g:method:getControlBinding"), [getControlRate]("GI.Gst.Objects.Object#g:method:getControlRate"), [getCurrentClockTime]("GI.Gst.Objects.Element#g:method:getCurrentClockTime"), [getCurrentRunningTime]("GI.Gst.Objects.Element#g:method:getCurrentRunningTime"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getDate]("GI.GES.Interfaces.MetaContainer#g:method:getDate"), [getDateTime]("GI.GES.Interfaces.MetaContainer#g:method:getDateTime"), [getDouble]("GI.GES.Interfaces.MetaContainer#g:method:getDouble"), [getDuration]("GI.GES.Objects.Timeline#g:method:getDuration"), [getElement]("GI.GES.Objects.Timeline#g:method:getElement"), [getFactory]("GI.Gst.Objects.Element#g:method:getFactory"), [getFloat]("GI.GES.Interfaces.MetaContainer#g:method:getFloat"), [getFrameAt]("GI.GES.Objects.Timeline#g:method:getFrameAt"), [getFrameTime]("GI.GES.Objects.Timeline#g:method:getFrameTime"), [getGValueArray]("GI.Gst.Objects.Object#g:method:getGValueArray"), [getGroups]("GI.GES.Objects.Timeline#g:method:getGroups"), [getId]("GI.GES.Interfaces.Extractable#g:method:getId"), [getInt]("GI.GES.Interfaces.MetaContainer#g:method:getInt"), [getInt64]("GI.GES.Interfaces.MetaContainer#g:method:getInt64"), [getLayer]("GI.GES.Objects.Timeline#g:method:getLayer"), [getLayers]("GI.GES.Objects.Timeline#g:method:getLayers"), [getMarkerList]("GI.GES.Interfaces.MetaContainer#g:method:getMarkerList"), [getMeta]("GI.GES.Interfaces.MetaContainer#g:method:getMeta"), [getMetadata]("GI.Gst.Objects.Element#g:method:getMetadata"), [getName]("GI.Gst.Objects.Object#g:method:getName"), [getPadForTrack]("GI.GES.Objects.Timeline#g:method:getPadForTrack"), [getPadTemplate]("GI.Gst.Objects.Element#g:method:getPadTemplate"), [getPadTemplateList]("GI.Gst.Objects.Element#g:method:getPadTemplateList"), [getParent]("GI.Gst.Objects.Object#g:method:getParent"), [getPathString]("GI.Gst.Objects.Object#g:method:getPathString"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getRequestPad]("GI.Gst.Objects.Element#g:method:getRequestPad"), [getSnappingDistance]("GI.GES.Objects.Timeline#g:method:getSnappingDistance"), [getStartTime]("GI.Gst.Objects.Element#g:method:getStartTime"), [getState]("GI.Gst.Objects.Element#g:method:getState"), [getStaticPad]("GI.Gst.Objects.Element#g:method:getStaticPad"), [getString]("GI.GES.Interfaces.MetaContainer#g:method:getString"), [getSuppressedFlags]("GI.Gst.Objects.Bin#g:method:getSuppressedFlags"), [getTrackForPad]("GI.GES.Objects.Timeline#g:method:getTrackForPad"), [getTracks]("GI.GES.Objects.Timeline#g:method:getTracks"), [getUint]("GI.GES.Interfaces.MetaContainer#g:method:getUint"), [getUint64]("GI.GES.Interfaces.MetaContainer#g:method:getUint64"), [getValue]("GI.Gst.Objects.Object#g:method:getValue").
-- 
-- ==== Setters
-- [setAsset]("GI.GES.Interfaces.Extractable#g:method:setAsset"), [setAutoTransition]("GI.GES.Objects.Timeline#g:method:setAutoTransition"), [setBaseTime]("GI.Gst.Objects.Element#g:method:setBaseTime"), [setBoolean]("GI.GES.Interfaces.MetaContainer#g:method:setBoolean"), [setBus]("GI.Gst.Objects.Element#g:method:setBus"), [setClock]("GI.Gst.Objects.Element#g:method:setClock"), [setContext]("GI.Gst.Objects.Element#g:method:setContext"), [setControlBindingDisabled]("GI.Gst.Objects.Object#g:method:setControlBindingDisabled"), [setControlBindingsDisabled]("GI.Gst.Objects.Object#g:method:setControlBindingsDisabled"), [setControlRate]("GI.Gst.Objects.Object#g:method:setControlRate"), [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setDate]("GI.GES.Interfaces.MetaContainer#g:method:setDate"), [setDateTime]("GI.GES.Interfaces.MetaContainer#g:method:setDateTime"), [setDouble]("GI.GES.Interfaces.MetaContainer#g:method:setDouble"), [setFloat]("GI.GES.Interfaces.MetaContainer#g:method:setFloat"), [setInt]("GI.GES.Interfaces.MetaContainer#g:method:setInt"), [setInt64]("GI.GES.Interfaces.MetaContainer#g:method:setInt64"), [setLockedState]("GI.Gst.Objects.Element#g:method:setLockedState"), [setMarkerList]("GI.GES.Interfaces.MetaContainer#g:method:setMarkerList"), [setMeta]("GI.GES.Interfaces.MetaContainer#g:method:setMeta"), [setName]("GI.Gst.Objects.Object#g:method:setName"), [setParent]("GI.Gst.Objects.Object#g:method:setParent"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setSnappingDistance]("GI.GES.Objects.Timeline#g:method:setSnappingDistance"), [setStartTime]("GI.Gst.Objects.Element#g:method:setStartTime"), [setState]("GI.Gst.Objects.Element#g:method:setState"), [setString]("GI.GES.Interfaces.MetaContainer#g:method:setString"), [setSuppressedFlags]("GI.Gst.Objects.Bin#g:method:setSuppressedFlags"), [setUint]("GI.GES.Interfaces.MetaContainer#g:method:setUint"), [setUint64]("GI.GES.Interfaces.MetaContainer#g:method:setUint64").

#if defined(ENABLE_OVERLOADING)
    ResolveTimelineMethod                   ,
#endif

-- ** addLayer #method:addLayer#

#if defined(ENABLE_OVERLOADING)
    TimelineAddLayerMethodInfo              ,
#endif
    timelineAddLayer                        ,


-- ** addTrack #method:addTrack#

#if defined(ENABLE_OVERLOADING)
    TimelineAddTrackMethodInfo              ,
#endif
    timelineAddTrack                        ,


-- ** appendLayer #method:appendLayer#

#if defined(ENABLE_OVERLOADING)
    TimelineAppendLayerMethodInfo           ,
#endif
    timelineAppendLayer                     ,


-- ** commit #method:commit#

#if defined(ENABLE_OVERLOADING)
    TimelineCommitMethodInfo                ,
#endif
    timelineCommit                          ,


-- ** commitSync #method:commitSync#

#if defined(ENABLE_OVERLOADING)
    TimelineCommitSyncMethodInfo            ,
#endif
    timelineCommitSync                      ,


-- ** freezeCommit #method:freezeCommit#

#if defined(ENABLE_OVERLOADING)
    TimelineFreezeCommitMethodInfo          ,
#endif
    timelineFreezeCommit                    ,


-- ** getAutoTransition #method:getAutoTransition#

#if defined(ENABLE_OVERLOADING)
    TimelineGetAutoTransitionMethodInfo     ,
#endif
    timelineGetAutoTransition               ,


-- ** getDuration #method:getDuration#

#if defined(ENABLE_OVERLOADING)
    TimelineGetDurationMethodInfo           ,
#endif
    timelineGetDuration                     ,


-- ** getElement #method:getElement#

#if defined(ENABLE_OVERLOADING)
    TimelineGetElementMethodInfo            ,
#endif
    timelineGetElement                      ,


-- ** getFrameAt #method:getFrameAt#

#if defined(ENABLE_OVERLOADING)
    TimelineGetFrameAtMethodInfo            ,
#endif
    timelineGetFrameAt                      ,


-- ** getFrameTime #method:getFrameTime#

#if defined(ENABLE_OVERLOADING)
    TimelineGetFrameTimeMethodInfo          ,
#endif
    timelineGetFrameTime                    ,


-- ** getGroups #method:getGroups#

#if defined(ENABLE_OVERLOADING)
    TimelineGetGroupsMethodInfo             ,
#endif
    timelineGetGroups                       ,


-- ** getLayer #method:getLayer#

#if defined(ENABLE_OVERLOADING)
    TimelineGetLayerMethodInfo              ,
#endif
    timelineGetLayer                        ,


-- ** getLayers #method:getLayers#

#if defined(ENABLE_OVERLOADING)
    TimelineGetLayersMethodInfo             ,
#endif
    timelineGetLayers                       ,


-- ** getPadForTrack #method:getPadForTrack#

#if defined(ENABLE_OVERLOADING)
    TimelineGetPadForTrackMethodInfo        ,
#endif
    timelineGetPadForTrack                  ,


-- ** getSnappingDistance #method:getSnappingDistance#

#if defined(ENABLE_OVERLOADING)
    TimelineGetSnappingDistanceMethodInfo   ,
#endif
    timelineGetSnappingDistance             ,


-- ** getTrackForPad #method:getTrackForPad#

#if defined(ENABLE_OVERLOADING)
    TimelineGetTrackForPadMethodInfo        ,
#endif
    timelineGetTrackForPad                  ,


-- ** getTracks #method:getTracks#

#if defined(ENABLE_OVERLOADING)
    TimelineGetTracksMethodInfo             ,
#endif
    timelineGetTracks                       ,


-- ** isEmpty #method:isEmpty#

#if defined(ENABLE_OVERLOADING)
    TimelineIsEmptyMethodInfo               ,
#endif
    timelineIsEmpty                         ,


-- ** loadFromUri #method:loadFromUri#

#if defined(ENABLE_OVERLOADING)
    TimelineLoadFromUriMethodInfo           ,
#endif
    timelineLoadFromUri                     ,


-- ** moveLayer #method:moveLayer#

#if defined(ENABLE_OVERLOADING)
    TimelineMoveLayerMethodInfo             ,
#endif
    timelineMoveLayer                       ,


-- ** new #method:new#

    timelineNew                             ,


-- ** newAudioVideo #method:newAudioVideo#

    timelineNewAudioVideo                   ,


-- ** newFromUri #method:newFromUri#

    timelineNewFromUri                      ,


-- ** pasteElement #method:pasteElement#

#if defined(ENABLE_OVERLOADING)
    TimelinePasteElementMethodInfo          ,
#endif
    timelinePasteElement                    ,


-- ** removeLayer #method:removeLayer#

#if defined(ENABLE_OVERLOADING)
    TimelineRemoveLayerMethodInfo           ,
#endif
    timelineRemoveLayer                     ,


-- ** removeTrack #method:removeTrack#

#if defined(ENABLE_OVERLOADING)
    TimelineRemoveTrackMethodInfo           ,
#endif
    timelineRemoveTrack                     ,


-- ** saveToUri #method:saveToUri#

#if defined(ENABLE_OVERLOADING)
    TimelineSaveToUriMethodInfo             ,
#endif
    timelineSaveToUri                       ,


-- ** setAutoTransition #method:setAutoTransition#

#if defined(ENABLE_OVERLOADING)
    TimelineSetAutoTransitionMethodInfo     ,
#endif
    timelineSetAutoTransition               ,


-- ** setSnappingDistance #method:setSnappingDistance#

#if defined(ENABLE_OVERLOADING)
    TimelineSetSnappingDistanceMethodInfo   ,
#endif
    timelineSetSnappingDistance             ,


-- ** thawCommit #method:thawCommit#

#if defined(ENABLE_OVERLOADING)
    TimelineThawCommitMethodInfo            ,
#endif
    timelineThawCommit                      ,




 -- * Properties


-- ** autoTransition #attr:autoTransition#
-- | Whether to automatically create a transition whenever two
-- t'GI.GES.Objects.Source.Source'-s overlap in a track of the timeline. See
-- [Layer:autoTransition]("GI.GES.Objects.Layer#g:attr:autoTransition") if you want this to only happen in some
-- layers.

#if defined(ENABLE_OVERLOADING)
    TimelineAutoTransitionPropertyInfo      ,
#endif
    constructTimelineAutoTransition         ,
    getTimelineAutoTransition               ,
    setTimelineAutoTransition               ,
#if defined(ENABLE_OVERLOADING)
    timelineAutoTransition                  ,
#endif


-- ** duration #attr:duration#
-- | The current duration (in nanoseconds) of the timeline. A timeline
-- \'starts\' at time 0, so this is the maximum end time of all of its
-- t'GI.GES.Objects.TimelineElement.TimelineElement'-s.

#if defined(ENABLE_OVERLOADING)
    TimelineDurationPropertyInfo            ,
#endif
    getTimelineDuration                     ,
#if defined(ENABLE_OVERLOADING)
    timelineDuration                        ,
#endif


-- ** snappingDistance #attr:snappingDistance#
-- | The distance (in nanoseconds) at which a t'GI.GES.Objects.TimelineElement.TimelineElement' being
-- moved within the timeline should snap one of its t'GI.GES.Objects.Source.Source'-s with
-- another t'GI.GES.Objects.Source.Source'-s edge. See t'GI.GES.Enums.EditMode' for which edges can
-- snap during an edit. 0 means no snapping.

#if defined(ENABLE_OVERLOADING)
    TimelineSnappingDistancePropertyInfo    ,
#endif
    constructTimelineSnappingDistance       ,
    getTimelineSnappingDistance             ,
    setTimelineSnappingDistance             ,
#if defined(ENABLE_OVERLOADING)
    timelineSnappingDistance                ,
#endif




 -- * Signals


-- ** commited #signal:commited#

    TimelineCommitedCallback                ,
#if defined(ENABLE_OVERLOADING)
    TimelineCommitedSignalInfo              ,
#endif
    afterTimelineCommited                   ,
    onTimelineCommited                      ,


-- ** groupAdded #signal:groupAdded#

    TimelineGroupAddedCallback              ,
#if defined(ENABLE_OVERLOADING)
    TimelineGroupAddedSignalInfo            ,
#endif
    afterTimelineGroupAdded                 ,
    onTimelineGroupAdded                    ,


-- ** groupRemoved #signal:groupRemoved#

    TimelineGroupRemovedCallback            ,
#if defined(ENABLE_OVERLOADING)
    TimelineGroupRemovedSignalInfo          ,
#endif
    afterTimelineGroupRemoved               ,
    onTimelineGroupRemoved                  ,


-- ** layerAdded #signal:layerAdded#

    TimelineLayerAddedCallback              ,
#if defined(ENABLE_OVERLOADING)
    TimelineLayerAddedSignalInfo            ,
#endif
    afterTimelineLayerAdded                 ,
    onTimelineLayerAdded                    ,


-- ** layerRemoved #signal:layerRemoved#

    TimelineLayerRemovedCallback            ,
#if defined(ENABLE_OVERLOADING)
    TimelineLayerRemovedSignalInfo          ,
#endif
    afterTimelineLayerRemoved               ,
    onTimelineLayerRemoved                  ,


-- ** selectElementTrack #signal:selectElementTrack#

    TimelineSelectElementTrackCallback      ,
#if defined(ENABLE_OVERLOADING)
    TimelineSelectElementTrackSignalInfo    ,
#endif
    afterTimelineSelectElementTrack         ,
    onTimelineSelectElementTrack            ,


-- ** selectTracksForObject #signal:selectTracksForObject#

    TimelineSelectTracksForObjectCallback   ,
#if defined(ENABLE_OVERLOADING)
    TimelineSelectTracksForObjectSignalInfo ,
#endif
    afterTimelineSelectTracksForObject      ,
    onTimelineSelectTracksForObject         ,


-- ** snappingEnded #signal:snappingEnded#

    TimelineSnappingEndedCallback           ,
#if defined(ENABLE_OVERLOADING)
    TimelineSnappingEndedSignalInfo         ,
#endif
    afterTimelineSnappingEnded              ,
    onTimelineSnappingEnded                 ,


-- ** snappingStarted #signal:snappingStarted#

    TimelineSnappingStartedCallback         ,
#if defined(ENABLE_OVERLOADING)
    TimelineSnappingStartedSignalInfo       ,
#endif
    afterTimelineSnappingStarted            ,
    onTimelineSnappingStarted               ,


-- ** trackAdded #signal:trackAdded#

    TimelineTrackAddedCallback              ,
#if defined(ENABLE_OVERLOADING)
    TimelineTrackAddedSignalInfo            ,
#endif
    afterTimelineTrackAdded                 ,
    onTimelineTrackAdded                    ,


-- ** trackRemoved #signal:trackRemoved#

    TimelineTrackRemovedCallback            ,
#if defined(ENABLE_OVERLOADING)
    TimelineTrackRemovedSignalInfo          ,
#endif
    afterTimelineTrackRemoved               ,
    onTimelineTrackRemoved                  ,




    ) 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.Extractable as GES.Extractable
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.Clip as GES.Clip
import {-# SOURCE #-} qualified GI.GES.Objects.Container as GES.Container
import {-# SOURCE #-} qualified GI.GES.Objects.Group as GES.Group
import {-# SOURCE #-} qualified GI.GES.Objects.Layer as GES.Layer
import {-# SOURCE #-} qualified GI.GES.Objects.TimelineElement as GES.TimelineElement
import {-# SOURCE #-} qualified GI.GES.Objects.Track as GES.Track
import {-# SOURCE #-} qualified GI.GES.Objects.TrackElement as GES.TrackElement
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gst.Interfaces.ChildProxy as Gst.ChildProxy
import qualified GI.Gst.Objects.Bin as Gst.Bin
import qualified GI.Gst.Objects.Element as Gst.Element
import qualified GI.Gst.Objects.Object as Gst.Object
import qualified GI.Gst.Objects.Pad as Gst.Pad

-- | Memory-managed wrapper type.
newtype Timeline = Timeline (SP.ManagedPtr Timeline)
    deriving (Timeline -> Timeline -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Timeline -> Timeline -> Bool
$c/= :: Timeline -> Timeline -> Bool
== :: Timeline -> Timeline -> Bool
$c== :: Timeline -> Timeline -> Bool
Eq)

instance SP.ManagedPtrNewtype Timeline where
    toManagedPtr :: Timeline -> ManagedPtr Timeline
toManagedPtr (Timeline ManagedPtr Timeline
p) = ManagedPtr Timeline
p

foreign import ccall "ges_timeline_get_type"
    c_ges_timeline_get_type :: IO B.Types.GType

instance B.Types.TypedObject Timeline where
    glibType :: IO GType
glibType = IO GType
c_ges_timeline_get_type

instance B.Types.GObject Timeline

-- | Type class for types which can be safely cast to `Timeline`, for instance with `toTimeline`.
class (SP.GObject o, O.IsDescendantOf Timeline o) => IsTimeline o
instance (SP.GObject o, O.IsDescendantOf Timeline o) => IsTimeline o

instance O.HasParentTypes Timeline
type instance O.ParentTypes Timeline = '[Gst.Bin.Bin, Gst.Element.Element, Gst.Object.Object, GObject.Object.Object, GES.Extractable.Extractable, GES.MetaContainer.MetaContainer, Gst.ChildProxy.ChildProxy]

-- | Cast to `Timeline`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toTimeline :: (MIO.MonadIO m, IsTimeline o) => o -> m Timeline
toTimeline :: forall (m :: * -> *) o.
(MonadIO m, IsTimeline o) =>
o -> m Timeline
toTimeline = 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 Timeline -> Timeline
Timeline

-- | Convert 'Timeline' to and from 'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue (Maybe Timeline) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_ges_timeline_get_type
    gvalueSet_ :: Ptr GValue -> Maybe Timeline -> IO ()
gvalueSet_ Ptr GValue
gv Maybe Timeline
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 Timeline)
    gvalueSet_ Ptr GValue
gv (P.Just Timeline
obj) = forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Timeline
obj (forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe Timeline)
gvalueGet_ Ptr GValue
gv = do
        Ptr Timeline
ptr <- forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr Timeline)
        if Ptr Timeline
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 Timeline -> Timeline
Timeline Ptr Timeline
ptr
        else forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
type family ResolveTimelineMethod (t :: Symbol) (o :: *) :: * where
    ResolveTimelineMethod "abortState" o = Gst.Element.ElementAbortStateMethodInfo
    ResolveTimelineMethod "add" o = Gst.Bin.BinAddMethodInfo
    ResolveTimelineMethod "addControlBinding" o = Gst.Object.ObjectAddControlBindingMethodInfo
    ResolveTimelineMethod "addLayer" o = TimelineAddLayerMethodInfo
    ResolveTimelineMethod "addMetasFromString" o = GES.MetaContainer.MetaContainerAddMetasFromStringMethodInfo
    ResolveTimelineMethod "addPad" o = Gst.Element.ElementAddPadMethodInfo
    ResolveTimelineMethod "addPropertyDeepNotifyWatch" o = Gst.Element.ElementAddPropertyDeepNotifyWatchMethodInfo
    ResolveTimelineMethod "addPropertyNotifyWatch" o = Gst.Element.ElementAddPropertyNotifyWatchMethodInfo
    ResolveTimelineMethod "addTrack" o = TimelineAddTrackMethodInfo
    ResolveTimelineMethod "appendLayer" o = TimelineAppendLayerMethodInfo
    ResolveTimelineMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveTimelineMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveTimelineMethod "callAsync" o = Gst.Element.ElementCallAsyncMethodInfo
    ResolveTimelineMethod "changeState" o = Gst.Element.ElementChangeStateMethodInfo
    ResolveTimelineMethod "checkMetaRegistered" o = GES.MetaContainer.MetaContainerCheckMetaRegisteredMethodInfo
    ResolveTimelineMethod "childAdded" o = Gst.ChildProxy.ChildProxyChildAddedMethodInfo
    ResolveTimelineMethod "childRemoved" o = Gst.ChildProxy.ChildProxyChildRemovedMethodInfo
    ResolveTimelineMethod "commit" o = TimelineCommitMethodInfo
    ResolveTimelineMethod "commitSync" o = TimelineCommitSyncMethodInfo
    ResolveTimelineMethod "continueState" o = Gst.Element.ElementContinueStateMethodInfo
    ResolveTimelineMethod "createAllPads" o = Gst.Element.ElementCreateAllPadsMethodInfo
    ResolveTimelineMethod "defaultError" o = Gst.Object.ObjectDefaultErrorMethodInfo
    ResolveTimelineMethod "findUnlinkedPad" o = Gst.Bin.BinFindUnlinkedPadMethodInfo
    ResolveTimelineMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveTimelineMethod "foreach" o = GES.MetaContainer.MetaContainerForeachMethodInfo
    ResolveTimelineMethod "foreachPad" o = Gst.Element.ElementForeachPadMethodInfo
    ResolveTimelineMethod "foreachSinkPad" o = Gst.Element.ElementForeachSinkPadMethodInfo
    ResolveTimelineMethod "foreachSrcPad" o = Gst.Element.ElementForeachSrcPadMethodInfo
    ResolveTimelineMethod "freezeCommit" o = TimelineFreezeCommitMethodInfo
    ResolveTimelineMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveTimelineMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveTimelineMethod "hasActiveControlBindings" o = Gst.Object.ObjectHasActiveControlBindingsMethodInfo
    ResolveTimelineMethod "hasAncestor" o = Gst.Object.ObjectHasAncestorMethodInfo
    ResolveTimelineMethod "hasAsAncestor" o = Gst.Object.ObjectHasAsAncestorMethodInfo
    ResolveTimelineMethod "hasAsParent" o = Gst.Object.ObjectHasAsParentMethodInfo
    ResolveTimelineMethod "isEmpty" o = TimelineIsEmptyMethodInfo
    ResolveTimelineMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveTimelineMethod "isLockedState" o = Gst.Element.ElementIsLockedStateMethodInfo
    ResolveTimelineMethod "iterateAllByElementFactoryName" o = Gst.Bin.BinIterateAllByElementFactoryNameMethodInfo
    ResolveTimelineMethod "iterateAllByInterface" o = Gst.Bin.BinIterateAllByInterfaceMethodInfo
    ResolveTimelineMethod "iterateElements" o = Gst.Bin.BinIterateElementsMethodInfo
    ResolveTimelineMethod "iteratePads" o = Gst.Element.ElementIteratePadsMethodInfo
    ResolveTimelineMethod "iterateRecurse" o = Gst.Bin.BinIterateRecurseMethodInfo
    ResolveTimelineMethod "iterateSinkPads" o = Gst.Element.ElementIterateSinkPadsMethodInfo
    ResolveTimelineMethod "iterateSinks" o = Gst.Bin.BinIterateSinksMethodInfo
    ResolveTimelineMethod "iterateSorted" o = Gst.Bin.BinIterateSortedMethodInfo
    ResolveTimelineMethod "iterateSources" o = Gst.Bin.BinIterateSourcesMethodInfo
    ResolveTimelineMethod "iterateSrcPads" o = Gst.Element.ElementIterateSrcPadsMethodInfo
    ResolveTimelineMethod "link" o = Gst.Element.ElementLinkMethodInfo
    ResolveTimelineMethod "linkFiltered" o = Gst.Element.ElementLinkFilteredMethodInfo
    ResolveTimelineMethod "linkPads" o = Gst.Element.ElementLinkPadsMethodInfo
    ResolveTimelineMethod "linkPadsFiltered" o = Gst.Element.ElementLinkPadsFilteredMethodInfo
    ResolveTimelineMethod "linkPadsFull" o = Gst.Element.ElementLinkPadsFullMethodInfo
    ResolveTimelineMethod "loadFromUri" o = TimelineLoadFromUriMethodInfo
    ResolveTimelineMethod "lookup" o = Gst.ChildProxy.ChildProxyLookupMethodInfo
    ResolveTimelineMethod "lostState" o = Gst.Element.ElementLostStateMethodInfo
    ResolveTimelineMethod "messageFull" o = Gst.Element.ElementMessageFullMethodInfo
    ResolveTimelineMethod "messageFullWithDetails" o = Gst.Element.ElementMessageFullWithDetailsMethodInfo
    ResolveTimelineMethod "metasToString" o = GES.MetaContainer.MetaContainerMetasToStringMethodInfo
    ResolveTimelineMethod "moveLayer" o = TimelineMoveLayerMethodInfo
    ResolveTimelineMethod "noMorePads" o = Gst.Element.ElementNoMorePadsMethodInfo
    ResolveTimelineMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveTimelineMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveTimelineMethod "pasteElement" o = TimelinePasteElementMethodInfo
    ResolveTimelineMethod "postMessage" o = Gst.Element.ElementPostMessageMethodInfo
    ResolveTimelineMethod "provideClock" o = Gst.Element.ElementProvideClockMethodInfo
    ResolveTimelineMethod "query" o = Gst.Element.ElementQueryMethodInfo
    ResolveTimelineMethod "queryConvert" o = Gst.Element.ElementQueryConvertMethodInfo
    ResolveTimelineMethod "queryDuration" o = Gst.Element.ElementQueryDurationMethodInfo
    ResolveTimelineMethod "queryPosition" o = Gst.Element.ElementQueryPositionMethodInfo
    ResolveTimelineMethod "recalculateLatency" o = Gst.Bin.BinRecalculateLatencyMethodInfo
    ResolveTimelineMethod "ref" o = Gst.Object.ObjectRefMethodInfo
    ResolveTimelineMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveTimelineMethod "registerMeta" o = GES.MetaContainer.MetaContainerRegisterMetaMethodInfo
    ResolveTimelineMethod "registerMetaBoolean" o = GES.MetaContainer.MetaContainerRegisterMetaBooleanMethodInfo
    ResolveTimelineMethod "registerMetaDate" o = GES.MetaContainer.MetaContainerRegisterMetaDateMethodInfo
    ResolveTimelineMethod "registerMetaDateTime" o = GES.MetaContainer.MetaContainerRegisterMetaDateTimeMethodInfo
    ResolveTimelineMethod "registerMetaDouble" o = GES.MetaContainer.MetaContainerRegisterMetaDoubleMethodInfo
    ResolveTimelineMethod "registerMetaFloat" o = GES.MetaContainer.MetaContainerRegisterMetaFloatMethodInfo
    ResolveTimelineMethod "registerMetaInt" o = GES.MetaContainer.MetaContainerRegisterMetaIntMethodInfo
    ResolveTimelineMethod "registerMetaInt64" o = GES.MetaContainer.MetaContainerRegisterMetaInt64MethodInfo
    ResolveTimelineMethod "registerMetaString" o = GES.MetaContainer.MetaContainerRegisterMetaStringMethodInfo
    ResolveTimelineMethod "registerMetaUint" o = GES.MetaContainer.MetaContainerRegisterMetaUintMethodInfo
    ResolveTimelineMethod "registerMetaUint64" o = GES.MetaContainer.MetaContainerRegisterMetaUint64MethodInfo
    ResolveTimelineMethod "registerStaticMeta" o = GES.MetaContainer.MetaContainerRegisterStaticMetaMethodInfo
    ResolveTimelineMethod "releaseRequestPad" o = Gst.Element.ElementReleaseRequestPadMethodInfo
    ResolveTimelineMethod "remove" o = Gst.Bin.BinRemoveMethodInfo
    ResolveTimelineMethod "removeControlBinding" o = Gst.Object.ObjectRemoveControlBindingMethodInfo
    ResolveTimelineMethod "removeLayer" o = TimelineRemoveLayerMethodInfo
    ResolveTimelineMethod "removePad" o = Gst.Element.ElementRemovePadMethodInfo
    ResolveTimelineMethod "removePropertyNotifyWatch" o = Gst.Element.ElementRemovePropertyNotifyWatchMethodInfo
    ResolveTimelineMethod "removeTrack" o = TimelineRemoveTrackMethodInfo
    ResolveTimelineMethod "requestPad" o = Gst.Element.ElementRequestPadMethodInfo
    ResolveTimelineMethod "requestPadSimple" o = Gst.Element.ElementRequestPadSimpleMethodInfo
    ResolveTimelineMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveTimelineMethod "saveToUri" o = TimelineSaveToUriMethodInfo
    ResolveTimelineMethod "seek" o = Gst.Element.ElementSeekMethodInfo
    ResolveTimelineMethod "seekSimple" o = Gst.Element.ElementSeekSimpleMethodInfo
    ResolveTimelineMethod "sendEvent" o = Gst.Element.ElementSendEventMethodInfo
    ResolveTimelineMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveTimelineMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveTimelineMethod "suggestNextSync" o = Gst.Object.ObjectSuggestNextSyncMethodInfo
    ResolveTimelineMethod "syncChildrenStates" o = Gst.Bin.BinSyncChildrenStatesMethodInfo
    ResolveTimelineMethod "syncStateWithParent" o = Gst.Element.ElementSyncStateWithParentMethodInfo
    ResolveTimelineMethod "syncValues" o = Gst.Object.ObjectSyncValuesMethodInfo
    ResolveTimelineMethod "thawCommit" o = TimelineThawCommitMethodInfo
    ResolveTimelineMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveTimelineMethod "unlink" o = Gst.Element.ElementUnlinkMethodInfo
    ResolveTimelineMethod "unlinkPads" o = Gst.Element.ElementUnlinkPadsMethodInfo
    ResolveTimelineMethod "unparent" o = Gst.Object.ObjectUnparentMethodInfo
    ResolveTimelineMethod "unref" o = Gst.Object.ObjectUnrefMethodInfo
    ResolveTimelineMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveTimelineMethod "getAsset" o = GES.Extractable.ExtractableGetAssetMethodInfo
    ResolveTimelineMethod "getAutoTransition" o = TimelineGetAutoTransitionMethodInfo
    ResolveTimelineMethod "getBaseTime" o = Gst.Element.ElementGetBaseTimeMethodInfo
    ResolveTimelineMethod "getBoolean" o = GES.MetaContainer.MetaContainerGetBooleanMethodInfo
    ResolveTimelineMethod "getBus" o = Gst.Element.ElementGetBusMethodInfo
    ResolveTimelineMethod "getByInterface" o = Gst.Bin.BinGetByInterfaceMethodInfo
    ResolveTimelineMethod "getByName" o = Gst.Bin.BinGetByNameMethodInfo
    ResolveTimelineMethod "getByNameRecurseUp" o = Gst.Bin.BinGetByNameRecurseUpMethodInfo
    ResolveTimelineMethod "getChildByIndex" o = Gst.ChildProxy.ChildProxyGetChildByIndexMethodInfo
    ResolveTimelineMethod "getChildByName" o = Gst.ChildProxy.ChildProxyGetChildByNameMethodInfo
    ResolveTimelineMethod "getChildrenCount" o = Gst.ChildProxy.ChildProxyGetChildrenCountMethodInfo
    ResolveTimelineMethod "getClock" o = Gst.Element.ElementGetClockMethodInfo
    ResolveTimelineMethod "getCompatiblePad" o = Gst.Element.ElementGetCompatiblePadMethodInfo
    ResolveTimelineMethod "getCompatiblePadTemplate" o = Gst.Element.ElementGetCompatiblePadTemplateMethodInfo
    ResolveTimelineMethod "getContext" o = Gst.Element.ElementGetContextMethodInfo
    ResolveTimelineMethod "getContextUnlocked" o = Gst.Element.ElementGetContextUnlockedMethodInfo
    ResolveTimelineMethod "getContexts" o = Gst.Element.ElementGetContextsMethodInfo
    ResolveTimelineMethod "getControlBinding" o = Gst.Object.ObjectGetControlBindingMethodInfo
    ResolveTimelineMethod "getControlRate" o = Gst.Object.ObjectGetControlRateMethodInfo
    ResolveTimelineMethod "getCurrentClockTime" o = Gst.Element.ElementGetCurrentClockTimeMethodInfo
    ResolveTimelineMethod "getCurrentRunningTime" o = Gst.Element.ElementGetCurrentRunningTimeMethodInfo
    ResolveTimelineMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveTimelineMethod "getDate" o = GES.MetaContainer.MetaContainerGetDateMethodInfo
    ResolveTimelineMethod "getDateTime" o = GES.MetaContainer.MetaContainerGetDateTimeMethodInfo
    ResolveTimelineMethod "getDouble" o = GES.MetaContainer.MetaContainerGetDoubleMethodInfo
    ResolveTimelineMethod "getDuration" o = TimelineGetDurationMethodInfo
    ResolveTimelineMethod "getElement" o = TimelineGetElementMethodInfo
    ResolveTimelineMethod "getFactory" o = Gst.Element.ElementGetFactoryMethodInfo
    ResolveTimelineMethod "getFloat" o = GES.MetaContainer.MetaContainerGetFloatMethodInfo
    ResolveTimelineMethod "getFrameAt" o = TimelineGetFrameAtMethodInfo
    ResolveTimelineMethod "getFrameTime" o = TimelineGetFrameTimeMethodInfo
    ResolveTimelineMethod "getGValueArray" o = Gst.Object.ObjectGetGValueArrayMethodInfo
    ResolveTimelineMethod "getGroups" o = TimelineGetGroupsMethodInfo
    ResolveTimelineMethod "getId" o = GES.Extractable.ExtractableGetIdMethodInfo
    ResolveTimelineMethod "getInt" o = GES.MetaContainer.MetaContainerGetIntMethodInfo
    ResolveTimelineMethod "getInt64" o = GES.MetaContainer.MetaContainerGetInt64MethodInfo
    ResolveTimelineMethod "getLayer" o = TimelineGetLayerMethodInfo
    ResolveTimelineMethod "getLayers" o = TimelineGetLayersMethodInfo
    ResolveTimelineMethod "getMarkerList" o = GES.MetaContainer.MetaContainerGetMarkerListMethodInfo
    ResolveTimelineMethod "getMeta" o = GES.MetaContainer.MetaContainerGetMetaMethodInfo
    ResolveTimelineMethod "getMetadata" o = Gst.Element.ElementGetMetadataMethodInfo
    ResolveTimelineMethod "getName" o = Gst.Object.ObjectGetNameMethodInfo
    ResolveTimelineMethod "getPadForTrack" o = TimelineGetPadForTrackMethodInfo
    ResolveTimelineMethod "getPadTemplate" o = Gst.Element.ElementGetPadTemplateMethodInfo
    ResolveTimelineMethod "getPadTemplateList" o = Gst.Element.ElementGetPadTemplateListMethodInfo
    ResolveTimelineMethod "getParent" o = Gst.Object.ObjectGetParentMethodInfo
    ResolveTimelineMethod "getPathString" o = Gst.Object.ObjectGetPathStringMethodInfo
    ResolveTimelineMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveTimelineMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveTimelineMethod "getRequestPad" o = Gst.Element.ElementGetRequestPadMethodInfo
    ResolveTimelineMethod "getSnappingDistance" o = TimelineGetSnappingDistanceMethodInfo
    ResolveTimelineMethod "getStartTime" o = Gst.Element.ElementGetStartTimeMethodInfo
    ResolveTimelineMethod "getState" o = Gst.Element.ElementGetStateMethodInfo
    ResolveTimelineMethod "getStaticPad" o = Gst.Element.ElementGetStaticPadMethodInfo
    ResolveTimelineMethod "getString" o = GES.MetaContainer.MetaContainerGetStringMethodInfo
    ResolveTimelineMethod "getSuppressedFlags" o = Gst.Bin.BinGetSuppressedFlagsMethodInfo
    ResolveTimelineMethod "getTrackForPad" o = TimelineGetTrackForPadMethodInfo
    ResolveTimelineMethod "getTracks" o = TimelineGetTracksMethodInfo
    ResolveTimelineMethod "getUint" o = GES.MetaContainer.MetaContainerGetUintMethodInfo
    ResolveTimelineMethod "getUint64" o = GES.MetaContainer.MetaContainerGetUint64MethodInfo
    ResolveTimelineMethod "getValue" o = Gst.Object.ObjectGetValueMethodInfo
    ResolveTimelineMethod "setAsset" o = GES.Extractable.ExtractableSetAssetMethodInfo
    ResolveTimelineMethod "setAutoTransition" o = TimelineSetAutoTransitionMethodInfo
    ResolveTimelineMethod "setBaseTime" o = Gst.Element.ElementSetBaseTimeMethodInfo
    ResolveTimelineMethod "setBoolean" o = GES.MetaContainer.MetaContainerSetBooleanMethodInfo
    ResolveTimelineMethod "setBus" o = Gst.Element.ElementSetBusMethodInfo
    ResolveTimelineMethod "setClock" o = Gst.Element.ElementSetClockMethodInfo
    ResolveTimelineMethod "setContext" o = Gst.Element.ElementSetContextMethodInfo
    ResolveTimelineMethod "setControlBindingDisabled" o = Gst.Object.ObjectSetControlBindingDisabledMethodInfo
    ResolveTimelineMethod "setControlBindingsDisabled" o = Gst.Object.ObjectSetControlBindingsDisabledMethodInfo
    ResolveTimelineMethod "setControlRate" o = Gst.Object.ObjectSetControlRateMethodInfo
    ResolveTimelineMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveTimelineMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveTimelineMethod "setDate" o = GES.MetaContainer.MetaContainerSetDateMethodInfo
    ResolveTimelineMethod "setDateTime" o = GES.MetaContainer.MetaContainerSetDateTimeMethodInfo
    ResolveTimelineMethod "setDouble" o = GES.MetaContainer.MetaContainerSetDoubleMethodInfo
    ResolveTimelineMethod "setFloat" o = GES.MetaContainer.MetaContainerSetFloatMethodInfo
    ResolveTimelineMethod "setInt" o = GES.MetaContainer.MetaContainerSetIntMethodInfo
    ResolveTimelineMethod "setInt64" o = GES.MetaContainer.MetaContainerSetInt64MethodInfo
    ResolveTimelineMethod "setLockedState" o = Gst.Element.ElementSetLockedStateMethodInfo
    ResolveTimelineMethod "setMarkerList" o = GES.MetaContainer.MetaContainerSetMarkerListMethodInfo
    ResolveTimelineMethod "setMeta" o = GES.MetaContainer.MetaContainerSetMetaMethodInfo
    ResolveTimelineMethod "setName" o = Gst.Object.ObjectSetNameMethodInfo
    ResolveTimelineMethod "setParent" o = Gst.Object.ObjectSetParentMethodInfo
    ResolveTimelineMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveTimelineMethod "setSnappingDistance" o = TimelineSetSnappingDistanceMethodInfo
    ResolveTimelineMethod "setStartTime" o = Gst.Element.ElementSetStartTimeMethodInfo
    ResolveTimelineMethod "setState" o = Gst.Element.ElementSetStateMethodInfo
    ResolveTimelineMethod "setString" o = GES.MetaContainer.MetaContainerSetStringMethodInfo
    ResolveTimelineMethod "setSuppressedFlags" o = Gst.Bin.BinSetSuppressedFlagsMethodInfo
    ResolveTimelineMethod "setUint" o = GES.MetaContainer.MetaContainerSetUintMethodInfo
    ResolveTimelineMethod "setUint64" o = GES.MetaContainer.MetaContainerSetUint64MethodInfo
    ResolveTimelineMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveTimelineMethod t Timeline, O.OverloadedMethod info Timeline p) => OL.IsLabel t (Timeline -> 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 ~ ResolveTimelineMethod t Timeline, O.OverloadedMethod info Timeline p, R.HasField t Timeline p) => R.HasField t Timeline p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolveTimelineMethod t Timeline, O.OverloadedMethodInfo info Timeline) => OL.IsLabel t (O.MethodProxy info Timeline) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif

#endif

-- signal Timeline::commited
-- | This signal will be emitted once the changes initiated by
-- 'GI.GES.Objects.Timeline.timelineCommit' have been executed in the backend. Use
-- 'GI.GES.Objects.Timeline.timelineCommitSync' if you do not want to have to connect
-- to this signal.
type TimelineCommitedCallback =
    IO ()

type C_TimelineCommitedCallback =
    Ptr Timeline ->                         -- object
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_TimelineCommitedCallback`.
foreign import ccall "wrapper"
    mk_TimelineCommitedCallback :: C_TimelineCommitedCallback -> IO (FunPtr C_TimelineCommitedCallback)

wrap_TimelineCommitedCallback :: 
    GObject a => (a -> TimelineCommitedCallback) ->
    C_TimelineCommitedCallback
wrap_TimelineCommitedCallback :: forall a. GObject a => (a -> IO ()) -> C_TimelineCommitedCallback
wrap_TimelineCommitedCallback a -> IO ()
gi'cb Ptr Timeline
gi'selfPtr Ptr ()
_ = do
    forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr Timeline
gi'selfPtr forall a b. (a -> b) -> a -> b
$ \Timeline
gi'self -> a -> IO ()
gi'cb (coerce :: forall a b. Coercible a b => a -> b
Coerce.coerce Timeline
gi'self) 


-- | Connect a signal handler for the [commited](#signal:commited) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' timeline #commited callback
-- @
-- 
-- 
onTimelineCommited :: (IsTimeline a, MonadIO m) => a -> ((?self :: a) => TimelineCommitedCallback) -> m SignalHandlerId
onTimelineCommited :: forall a (m :: * -> *).
(IsTimeline a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
onTimelineCommited a
obj (?self::a) => IO ()
cb = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> IO ()
wrapped a
self = let ?self = a
self in (?self::a) => IO ()
cb
    let wrapped' :: C_TimelineCommitedCallback
wrapped' = forall a. GObject a => (a -> IO ()) -> C_TimelineCommitedCallback
wrap_TimelineCommitedCallback a -> IO ()
wrapped
    FunPtr C_TimelineCommitedCallback
wrapped'' <- C_TimelineCommitedCallback
-> IO (FunPtr C_TimelineCommitedCallback)
mk_TimelineCommitedCallback C_TimelineCommitedCallback
wrapped'
    forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"commited" FunPtr C_TimelineCommitedCallback
wrapped'' SignalConnectMode
SignalConnectBefore forall a. Maybe a
Nothing

-- | Connect a signal handler for the [commited](#signal:commited) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' timeline #commited callback
-- @
-- 
-- 
-- 
-- By default the object invoking the signal is not passed to the callback.
-- If you need to access it, you can use the implit @?self@ parameter.
-- Note that this requires activating the @ImplicitParams@ GHC extension.
-- 
afterTimelineCommited :: (IsTimeline a, MonadIO m) => a -> ((?self :: a) => TimelineCommitedCallback) -> m SignalHandlerId
afterTimelineCommited :: forall a (m :: * -> *).
(IsTimeline a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
afterTimelineCommited a
obj (?self::a) => IO ()
cb = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> IO ()
wrapped a
self = let ?self = a
self in (?self::a) => IO ()
cb
    let wrapped' :: C_TimelineCommitedCallback
wrapped' = forall a. GObject a => (a -> IO ()) -> C_TimelineCommitedCallback
wrap_TimelineCommitedCallback a -> IO ()
wrapped
    FunPtr C_TimelineCommitedCallback
wrapped'' <- C_TimelineCommitedCallback
-> IO (FunPtr C_TimelineCommitedCallback)
mk_TimelineCommitedCallback C_TimelineCommitedCallback
wrapped'
    forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"commited" FunPtr C_TimelineCommitedCallback
wrapped'' SignalConnectMode
SignalConnectAfter forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data TimelineCommitedSignalInfo
instance SignalInfo TimelineCommitedSignalInfo where
    type HaskellCallbackType TimelineCommitedSignalInfo = TimelineCommitedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_TimelineCommitedCallback cb
        cb'' <- mk_TimelineCommitedCallback cb'
        connectSignalFunPtr obj "commited" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GES.Objects.Timeline::commited"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.1/docs/GI-GES-Objects-Timeline.html#g:signal:commited"})

#endif

-- signal Timeline::group-added
-- | Will be emitted after the group is added to to the timeline. This can
-- happen when grouping with @ges_container_group@, or by adding
-- containers to a newly created group.
-- 
-- Note that this should not be emitted whilst a timeline is being
-- loaded from its t'GI.GES.Objects.Project.Project' asset. You should connect to the
-- project\'s [Project::loaded]("GI.GES.Objects.Project#g:signal:loaded") signal if you want to know which groups
-- were created for the timeline.
type TimelineGroupAddedCallback =
    GES.Group.Group
    -- ^ /@group@/: The group that was added to /@timeline@/
    -> IO ()

type C_TimelineGroupAddedCallback =
    Ptr Timeline ->                         -- object
    Ptr GES.Group.Group ->
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_TimelineGroupAddedCallback`.
foreign import ccall "wrapper"
    mk_TimelineGroupAddedCallback :: C_TimelineGroupAddedCallback -> IO (FunPtr C_TimelineGroupAddedCallback)

wrap_TimelineGroupAddedCallback :: 
    GObject a => (a -> TimelineGroupAddedCallback) ->
    C_TimelineGroupAddedCallback
wrap_TimelineGroupAddedCallback :: forall a.
GObject a =>
(a -> TimelineGroupAddedCallback) -> C_TimelineGroupAddedCallback
wrap_TimelineGroupAddedCallback a -> TimelineGroupAddedCallback
gi'cb Ptr Timeline
gi'selfPtr Ptr Group
group Ptr ()
_ = do
    Group
group' <- (forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Group -> Group
GES.Group.Group) Ptr Group
group
    forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr Timeline
gi'selfPtr forall a b. (a -> b) -> a -> b
$ \Timeline
gi'self -> a -> TimelineGroupAddedCallback
gi'cb (coerce :: forall a b. Coercible a b => a -> b
Coerce.coerce Timeline
gi'self)  Group
group'


-- | Connect a signal handler for the [groupAdded](#signal:groupAdded) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' timeline #groupAdded callback
-- @
-- 
-- 
onTimelineGroupAdded :: (IsTimeline a, MonadIO m) => a -> ((?self :: a) => TimelineGroupAddedCallback) -> m SignalHandlerId
onTimelineGroupAdded :: forall a (m :: * -> *).
(IsTimeline a, MonadIO m) =>
a
-> ((?self::a) => TimelineGroupAddedCallback) -> m SignalHandlerId
onTimelineGroupAdded a
obj (?self::a) => TimelineGroupAddedCallback
cb = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> TimelineGroupAddedCallback
wrapped a
self = let ?self = a
self in (?self::a) => TimelineGroupAddedCallback
cb
    let wrapped' :: C_TimelineGroupAddedCallback
wrapped' = forall a.
GObject a =>
(a -> TimelineGroupAddedCallback) -> C_TimelineGroupAddedCallback
wrap_TimelineGroupAddedCallback a -> TimelineGroupAddedCallback
wrapped
    FunPtr C_TimelineGroupAddedCallback
wrapped'' <- C_TimelineGroupAddedCallback
-> IO (FunPtr C_TimelineGroupAddedCallback)
mk_TimelineGroupAddedCallback C_TimelineGroupAddedCallback
wrapped'
    forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"group-added" FunPtr C_TimelineGroupAddedCallback
wrapped'' SignalConnectMode
SignalConnectBefore forall a. Maybe a
Nothing

-- | Connect a signal handler for the [groupAdded](#signal:groupAdded) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' timeline #groupAdded callback
-- @
-- 
-- 
-- 
-- By default the object invoking the signal is not passed to the callback.
-- If you need to access it, you can use the implit @?self@ parameter.
-- Note that this requires activating the @ImplicitParams@ GHC extension.
-- 
afterTimelineGroupAdded :: (IsTimeline a, MonadIO m) => a -> ((?self :: a) => TimelineGroupAddedCallback) -> m SignalHandlerId
afterTimelineGroupAdded :: forall a (m :: * -> *).
(IsTimeline a, MonadIO m) =>
a
-> ((?self::a) => TimelineGroupAddedCallback) -> m SignalHandlerId
afterTimelineGroupAdded a
obj (?self::a) => TimelineGroupAddedCallback
cb = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> TimelineGroupAddedCallback
wrapped a
self = let ?self = a
self in (?self::a) => TimelineGroupAddedCallback
cb
    let wrapped' :: C_TimelineGroupAddedCallback
wrapped' = forall a.
GObject a =>
(a -> TimelineGroupAddedCallback) -> C_TimelineGroupAddedCallback
wrap_TimelineGroupAddedCallback a -> TimelineGroupAddedCallback
wrapped
    FunPtr C_TimelineGroupAddedCallback
wrapped'' <- C_TimelineGroupAddedCallback
-> IO (FunPtr C_TimelineGroupAddedCallback)
mk_TimelineGroupAddedCallback C_TimelineGroupAddedCallback
wrapped'
    forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"group-added" FunPtr C_TimelineGroupAddedCallback
wrapped'' SignalConnectMode
SignalConnectAfter forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data TimelineGroupAddedSignalInfo
instance SignalInfo TimelineGroupAddedSignalInfo where
    type HaskellCallbackType TimelineGroupAddedSignalInfo = TimelineGroupAddedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_TimelineGroupAddedCallback cb
        cb'' <- mk_TimelineGroupAddedCallback cb'
        connectSignalFunPtr obj "group-added" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GES.Objects.Timeline::group-added"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.1/docs/GI-GES-Objects-Timeline.html#g:signal:groupAdded"})

#endif

-- signal Timeline::group-removed
-- | Will be emitted after the group is removed from the timeline through
-- @ges_container_ungroup@. Note that /@group@/ will no longer contain its
-- former children, these are held in /@children@/.
-- 
-- Note that if a group is emptied, then it will no longer belong to the
-- timeline, but this signal will **not** be emitted in such a case.
type TimelineGroupRemovedCallback =
    GES.Group.Group
    -- ^ /@group@/: The group that was removed from /@timeline@/
    -> [GES.Container.Container]
    -- ^ /@children@/: A list
    -- of t'GI.GES.Objects.Container.Container'-s that _were_ the children of the removed /@group@/
    -> IO ()

type C_TimelineGroupRemovedCallback =
    Ptr Timeline ->                         -- object
    Ptr GES.Group.Group ->
    Ptr (GPtrArray (Ptr GES.Container.Container)) ->
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_TimelineGroupRemovedCallback`.
foreign import ccall "wrapper"
    mk_TimelineGroupRemovedCallback :: C_TimelineGroupRemovedCallback -> IO (FunPtr C_TimelineGroupRemovedCallback)

wrap_TimelineGroupRemovedCallback :: 
    GObject a => (a -> TimelineGroupRemovedCallback) ->
    C_TimelineGroupRemovedCallback
wrap_TimelineGroupRemovedCallback :: forall a.
GObject a =>
(a -> TimelineGroupRemovedCallback)
-> C_TimelineGroupRemovedCallback
wrap_TimelineGroupRemovedCallback a -> TimelineGroupRemovedCallback
gi'cb Ptr Timeline
gi'selfPtr Ptr Group
group Ptr (GPtrArray (Ptr Container))
children Ptr ()
_ = do
    Group
group' <- (forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Group -> Group
GES.Group.Group) Ptr Group
group
    [Ptr Container]
children' <- forall a. Ptr (GPtrArray (Ptr a)) -> IO [Ptr a]
unpackGPtrArray Ptr (GPtrArray (Ptr Container))
children
    [Container]
children'' <- 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 Container -> Container
GES.Container.Container) [Ptr Container]
children'
    forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr Timeline
gi'selfPtr forall a b. (a -> b) -> a -> b
$ \Timeline
gi'self -> a -> TimelineGroupRemovedCallback
gi'cb (coerce :: forall a b. Coercible a b => a -> b
Coerce.coerce Timeline
gi'self)  Group
group' [Container]
children''


-- | Connect a signal handler for the [groupRemoved](#signal:groupRemoved) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' timeline #groupRemoved callback
-- @
-- 
-- 
onTimelineGroupRemoved :: (IsTimeline a, MonadIO m) => a -> ((?self :: a) => TimelineGroupRemovedCallback) -> m SignalHandlerId
onTimelineGroupRemoved :: forall a (m :: * -> *).
(IsTimeline a, MonadIO m) =>
a
-> ((?self::a) => TimelineGroupRemovedCallback)
-> m SignalHandlerId
onTimelineGroupRemoved a
obj (?self::a) => TimelineGroupRemovedCallback
cb = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> TimelineGroupRemovedCallback
wrapped a
self = let ?self = a
self in (?self::a) => TimelineGroupRemovedCallback
cb
    let wrapped' :: C_TimelineGroupRemovedCallback
wrapped' = forall a.
GObject a =>
(a -> TimelineGroupRemovedCallback)
-> C_TimelineGroupRemovedCallback
wrap_TimelineGroupRemovedCallback a -> TimelineGroupRemovedCallback
wrapped
    FunPtr C_TimelineGroupRemovedCallback
wrapped'' <- C_TimelineGroupRemovedCallback
-> IO (FunPtr C_TimelineGroupRemovedCallback)
mk_TimelineGroupRemovedCallback C_TimelineGroupRemovedCallback
wrapped'
    forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"group-removed" FunPtr C_TimelineGroupRemovedCallback
wrapped'' SignalConnectMode
SignalConnectBefore forall a. Maybe a
Nothing

-- | Connect a signal handler for the [groupRemoved](#signal:groupRemoved) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' timeline #groupRemoved callback
-- @
-- 
-- 
-- 
-- By default the object invoking the signal is not passed to the callback.
-- If you need to access it, you can use the implit @?self@ parameter.
-- Note that this requires activating the @ImplicitParams@ GHC extension.
-- 
afterTimelineGroupRemoved :: (IsTimeline a, MonadIO m) => a -> ((?self :: a) => TimelineGroupRemovedCallback) -> m SignalHandlerId
afterTimelineGroupRemoved :: forall a (m :: * -> *).
(IsTimeline a, MonadIO m) =>
a
-> ((?self::a) => TimelineGroupRemovedCallback)
-> m SignalHandlerId
afterTimelineGroupRemoved a
obj (?self::a) => TimelineGroupRemovedCallback
cb = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> TimelineGroupRemovedCallback
wrapped a
self = let ?self = a
self in (?self::a) => TimelineGroupRemovedCallback
cb
    let wrapped' :: C_TimelineGroupRemovedCallback
wrapped' = forall a.
GObject a =>
(a -> TimelineGroupRemovedCallback)
-> C_TimelineGroupRemovedCallback
wrap_TimelineGroupRemovedCallback a -> TimelineGroupRemovedCallback
wrapped
    FunPtr C_TimelineGroupRemovedCallback
wrapped'' <- C_TimelineGroupRemovedCallback
-> IO (FunPtr C_TimelineGroupRemovedCallback)
mk_TimelineGroupRemovedCallback C_TimelineGroupRemovedCallback
wrapped'
    forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"group-removed" FunPtr C_TimelineGroupRemovedCallback
wrapped'' SignalConnectMode
SignalConnectAfter forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data TimelineGroupRemovedSignalInfo
instance SignalInfo TimelineGroupRemovedSignalInfo where
    type HaskellCallbackType TimelineGroupRemovedSignalInfo = TimelineGroupRemovedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_TimelineGroupRemovedCallback cb
        cb'' <- mk_TimelineGroupRemovedCallback cb'
        connectSignalFunPtr obj "group-removed" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GES.Objects.Timeline::group-removed"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.1/docs/GI-GES-Objects-Timeline.html#g:signal:groupRemoved"})

#endif

-- signal Timeline::layer-added
-- | Will be emitted after the layer is added to the timeline.
-- 
-- Note that this should not be emitted whilst a timeline is being
-- loaded from its t'GI.GES.Objects.Project.Project' asset. You should connect to the
-- project\'s [Project::loaded]("GI.GES.Objects.Project#g:signal:loaded") signal if you want to know which
-- layers were created for the timeline.
type TimelineLayerAddedCallback =
    GES.Layer.Layer
    -- ^ /@layer@/: The layer that was added to /@timeline@/
    -> IO ()

type C_TimelineLayerAddedCallback =
    Ptr Timeline ->                         -- object
    Ptr GES.Layer.Layer ->
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_TimelineLayerAddedCallback`.
foreign import ccall "wrapper"
    mk_TimelineLayerAddedCallback :: C_TimelineLayerAddedCallback -> IO (FunPtr C_TimelineLayerAddedCallback)

wrap_TimelineLayerAddedCallback :: 
    GObject a => (a -> TimelineLayerAddedCallback) ->
    C_TimelineLayerAddedCallback
wrap_TimelineLayerAddedCallback :: forall a.
GObject a =>
(a -> TimelineLayerAddedCallback) -> C_TimelineLayerAddedCallback
wrap_TimelineLayerAddedCallback a -> TimelineLayerAddedCallback
gi'cb Ptr Timeline
gi'selfPtr Ptr Layer
layer Ptr ()
_ = do
    Layer
layer' <- (forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Layer -> Layer
GES.Layer.Layer) Ptr Layer
layer
    forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr Timeline
gi'selfPtr forall a b. (a -> b) -> a -> b
$ \Timeline
gi'self -> a -> TimelineLayerAddedCallback
gi'cb (coerce :: forall a b. Coercible a b => a -> b
Coerce.coerce Timeline
gi'self)  Layer
layer'


-- | Connect a signal handler for the [layerAdded](#signal:layerAdded) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' timeline #layerAdded callback
-- @
-- 
-- 
onTimelineLayerAdded :: (IsTimeline a, MonadIO m) => a -> ((?self :: a) => TimelineLayerAddedCallback) -> m SignalHandlerId
onTimelineLayerAdded :: forall a (m :: * -> *).
(IsTimeline a, MonadIO m) =>
a
-> ((?self::a) => TimelineLayerAddedCallback) -> m SignalHandlerId
onTimelineLayerAdded a
obj (?self::a) => TimelineLayerAddedCallback
cb = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> TimelineLayerAddedCallback
wrapped a
self = let ?self = a
self in (?self::a) => TimelineLayerAddedCallback
cb
    let wrapped' :: C_TimelineLayerAddedCallback
wrapped' = forall a.
GObject a =>
(a -> TimelineLayerAddedCallback) -> C_TimelineLayerAddedCallback
wrap_TimelineLayerAddedCallback a -> TimelineLayerAddedCallback
wrapped
    FunPtr C_TimelineLayerAddedCallback
wrapped'' <- C_TimelineLayerAddedCallback
-> IO (FunPtr C_TimelineLayerAddedCallback)
mk_TimelineLayerAddedCallback C_TimelineLayerAddedCallback
wrapped'
    forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"layer-added" FunPtr C_TimelineLayerAddedCallback
wrapped'' SignalConnectMode
SignalConnectBefore forall a. Maybe a
Nothing

-- | Connect a signal handler for the [layerAdded](#signal:layerAdded) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' timeline #layerAdded callback
-- @
-- 
-- 
-- 
-- By default the object invoking the signal is not passed to the callback.
-- If you need to access it, you can use the implit @?self@ parameter.
-- Note that this requires activating the @ImplicitParams@ GHC extension.
-- 
afterTimelineLayerAdded :: (IsTimeline a, MonadIO m) => a -> ((?self :: a) => TimelineLayerAddedCallback) -> m SignalHandlerId
afterTimelineLayerAdded :: forall a (m :: * -> *).
(IsTimeline a, MonadIO m) =>
a
-> ((?self::a) => TimelineLayerAddedCallback) -> m SignalHandlerId
afterTimelineLayerAdded a
obj (?self::a) => TimelineLayerAddedCallback
cb = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> TimelineLayerAddedCallback
wrapped a
self = let ?self = a
self in (?self::a) => TimelineLayerAddedCallback
cb
    let wrapped' :: C_TimelineLayerAddedCallback
wrapped' = forall a.
GObject a =>
(a -> TimelineLayerAddedCallback) -> C_TimelineLayerAddedCallback
wrap_TimelineLayerAddedCallback a -> TimelineLayerAddedCallback
wrapped
    FunPtr C_TimelineLayerAddedCallback
wrapped'' <- C_TimelineLayerAddedCallback
-> IO (FunPtr C_TimelineLayerAddedCallback)
mk_TimelineLayerAddedCallback C_TimelineLayerAddedCallback
wrapped'
    forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"layer-added" FunPtr C_TimelineLayerAddedCallback
wrapped'' SignalConnectMode
SignalConnectAfter forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data TimelineLayerAddedSignalInfo
instance SignalInfo TimelineLayerAddedSignalInfo where
    type HaskellCallbackType TimelineLayerAddedSignalInfo = TimelineLayerAddedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_TimelineLayerAddedCallback cb
        cb'' <- mk_TimelineLayerAddedCallback cb'
        connectSignalFunPtr obj "layer-added" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GES.Objects.Timeline::layer-added"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.1/docs/GI-GES-Objects-Timeline.html#g:signal:layerAdded"})

#endif

-- signal Timeline::layer-removed
-- | Will be emitted after the layer is removed from the timeline.
type TimelineLayerRemovedCallback =
    GES.Layer.Layer
    -- ^ /@layer@/: The layer that was removed from /@timeline@/
    -> IO ()

type C_TimelineLayerRemovedCallback =
    Ptr Timeline ->                         -- object
    Ptr GES.Layer.Layer ->
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_TimelineLayerRemovedCallback`.
foreign import ccall "wrapper"
    mk_TimelineLayerRemovedCallback :: C_TimelineLayerRemovedCallback -> IO (FunPtr C_TimelineLayerRemovedCallback)

wrap_TimelineLayerRemovedCallback :: 
    GObject a => (a -> TimelineLayerRemovedCallback) ->
    C_TimelineLayerRemovedCallback
wrap_TimelineLayerRemovedCallback :: forall a.
GObject a =>
(a -> TimelineLayerAddedCallback) -> C_TimelineLayerAddedCallback
wrap_TimelineLayerRemovedCallback a -> TimelineLayerAddedCallback
gi'cb Ptr Timeline
gi'selfPtr Ptr Layer
layer Ptr ()
_ = do
    Layer
layer' <- (forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Layer -> Layer
GES.Layer.Layer) Ptr Layer
layer
    forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr Timeline
gi'selfPtr forall a b. (a -> b) -> a -> b
$ \Timeline
gi'self -> a -> TimelineLayerAddedCallback
gi'cb (coerce :: forall a b. Coercible a b => a -> b
Coerce.coerce Timeline
gi'self)  Layer
layer'


-- | Connect a signal handler for the [layerRemoved](#signal:layerRemoved) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' timeline #layerRemoved callback
-- @
-- 
-- 
onTimelineLayerRemoved :: (IsTimeline a, MonadIO m) => a -> ((?self :: a) => TimelineLayerRemovedCallback) -> m SignalHandlerId
onTimelineLayerRemoved :: forall a (m :: * -> *).
(IsTimeline a, MonadIO m) =>
a
-> ((?self::a) => TimelineLayerAddedCallback) -> m SignalHandlerId
onTimelineLayerRemoved a
obj (?self::a) => TimelineLayerAddedCallback
cb = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> TimelineLayerAddedCallback
wrapped a
self = let ?self = a
self in (?self::a) => TimelineLayerAddedCallback
cb
    let wrapped' :: C_TimelineLayerAddedCallback
wrapped' = forall a.
GObject a =>
(a -> TimelineLayerAddedCallback) -> C_TimelineLayerAddedCallback
wrap_TimelineLayerRemovedCallback a -> TimelineLayerAddedCallback
wrapped
    FunPtr C_TimelineLayerAddedCallback
wrapped'' <- C_TimelineLayerAddedCallback
-> IO (FunPtr C_TimelineLayerAddedCallback)
mk_TimelineLayerRemovedCallback C_TimelineLayerAddedCallback
wrapped'
    forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"layer-removed" FunPtr C_TimelineLayerAddedCallback
wrapped'' SignalConnectMode
SignalConnectBefore forall a. Maybe a
Nothing

-- | Connect a signal handler for the [layerRemoved](#signal:layerRemoved) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' timeline #layerRemoved callback
-- @
-- 
-- 
-- 
-- By default the object invoking the signal is not passed to the callback.
-- If you need to access it, you can use the implit @?self@ parameter.
-- Note that this requires activating the @ImplicitParams@ GHC extension.
-- 
afterTimelineLayerRemoved :: (IsTimeline a, MonadIO m) => a -> ((?self :: a) => TimelineLayerRemovedCallback) -> m SignalHandlerId
afterTimelineLayerRemoved :: forall a (m :: * -> *).
(IsTimeline a, MonadIO m) =>
a
-> ((?self::a) => TimelineLayerAddedCallback) -> m SignalHandlerId
afterTimelineLayerRemoved a
obj (?self::a) => TimelineLayerAddedCallback
cb = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> TimelineLayerAddedCallback
wrapped a
self = let ?self = a
self in (?self::a) => TimelineLayerAddedCallback
cb
    let wrapped' :: C_TimelineLayerAddedCallback
wrapped' = forall a.
GObject a =>
(a -> TimelineLayerAddedCallback) -> C_TimelineLayerAddedCallback
wrap_TimelineLayerRemovedCallback a -> TimelineLayerAddedCallback
wrapped
    FunPtr C_TimelineLayerAddedCallback
wrapped'' <- C_TimelineLayerAddedCallback
-> IO (FunPtr C_TimelineLayerAddedCallback)
mk_TimelineLayerRemovedCallback C_TimelineLayerAddedCallback
wrapped'
    forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"layer-removed" FunPtr C_TimelineLayerAddedCallback
wrapped'' SignalConnectMode
SignalConnectAfter forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data TimelineLayerRemovedSignalInfo
instance SignalInfo TimelineLayerRemovedSignalInfo where
    type HaskellCallbackType TimelineLayerRemovedSignalInfo = TimelineLayerRemovedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_TimelineLayerRemovedCallback cb
        cb'' <- mk_TimelineLayerRemovedCallback cb'
        connectSignalFunPtr obj "layer-removed" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GES.Objects.Timeline::layer-removed"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.1/docs/GI-GES-Objects-Timeline.html#g:signal:layerRemoved"})

#endif

-- signal Timeline::select-element-track
-- | Simplified version of [Timeline::selectTracksForObject]("GI.GES.Objects.Timeline#g:signal:selectTracksForObject") which only
-- allows /@trackElement@/ to be added to a single t'GI.GES.Objects.Track.Track'.
-- 
-- /Since: 1.18/
type TimelineSelectElementTrackCallback =
    GES.Clip.Clip
    -- ^ /@clip@/: The clip that /@trackElement@/ is being added to
    -> GES.TrackElement.TrackElement
    -- ^ /@trackElement@/: The element being added
    -> IO GES.Track.Track
    -- ^ __Returns:__ A track to put /@trackElement@/ into, or 'P.Nothing' if
    -- it should be discarded.

type C_TimelineSelectElementTrackCallback =
    Ptr Timeline ->                         -- object
    Ptr GES.Clip.Clip ->
    Ptr GES.TrackElement.TrackElement ->
    Ptr () ->                               -- user_data
    IO (Ptr GES.Track.Track)

-- | Generate a function pointer callable from C code, from a `C_TimelineSelectElementTrackCallback`.
foreign import ccall "wrapper"
    mk_TimelineSelectElementTrackCallback :: C_TimelineSelectElementTrackCallback -> IO (FunPtr C_TimelineSelectElementTrackCallback)

wrap_TimelineSelectElementTrackCallback :: 
    GObject a => (a -> TimelineSelectElementTrackCallback) ->
    C_TimelineSelectElementTrackCallback
wrap_TimelineSelectElementTrackCallback :: forall a.
GObject a =>
(a -> TimelineSelectElementTrackCallback)
-> C_TimelineSelectElementTrackCallback
wrap_TimelineSelectElementTrackCallback a -> TimelineSelectElementTrackCallback
gi'cb Ptr Timeline
gi'selfPtr Ptr Clip
clip Ptr TrackElement
trackElement Ptr ()
_ = do
    Clip
clip' <- (forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Clip -> Clip
GES.Clip.Clip) Ptr Clip
clip
    TrackElement
trackElement' <- (forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr TrackElement -> TrackElement
GES.TrackElement.TrackElement) Ptr TrackElement
trackElement
    Track
result <- forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr Timeline
gi'selfPtr forall a b. (a -> b) -> a -> b
$ \Timeline
gi'self -> a -> TimelineSelectElementTrackCallback
gi'cb (coerce :: forall a b. Coercible a b => a -> b
Coerce.coerce Timeline
gi'self)  Clip
clip' TrackElement
trackElement'
    Ptr Track
result' <- forall a b. (HasCallStack, GObject a) => a -> IO (Ptr b)
B.ManagedPtr.disownObject Track
result
    forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Track
result'


-- | Connect a signal handler for the [selectElementTrack](#signal:selectElementTrack) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' timeline #selectElementTrack callback
-- @
-- 
-- 
onTimelineSelectElementTrack :: (IsTimeline a, MonadIO m) => a -> ((?self :: a) => TimelineSelectElementTrackCallback) -> m SignalHandlerId
onTimelineSelectElementTrack :: forall a (m :: * -> *).
(IsTimeline a, MonadIO m) =>
a
-> ((?self::a) => TimelineSelectElementTrackCallback)
-> m SignalHandlerId
onTimelineSelectElementTrack a
obj (?self::a) => TimelineSelectElementTrackCallback
cb = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> TimelineSelectElementTrackCallback
wrapped a
self = let ?self = a
self in (?self::a) => TimelineSelectElementTrackCallback
cb
    let wrapped' :: C_TimelineSelectElementTrackCallback
wrapped' = forall a.
GObject a =>
(a -> TimelineSelectElementTrackCallback)
-> C_TimelineSelectElementTrackCallback
wrap_TimelineSelectElementTrackCallback a -> TimelineSelectElementTrackCallback
wrapped
    FunPtr C_TimelineSelectElementTrackCallback
wrapped'' <- C_TimelineSelectElementTrackCallback
-> IO (FunPtr C_TimelineSelectElementTrackCallback)
mk_TimelineSelectElementTrackCallback C_TimelineSelectElementTrackCallback
wrapped'
    forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"select-element-track" FunPtr C_TimelineSelectElementTrackCallback
wrapped'' SignalConnectMode
SignalConnectBefore forall a. Maybe a
Nothing

-- | Connect a signal handler for the [selectElementTrack](#signal:selectElementTrack) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' timeline #selectElementTrack callback
-- @
-- 
-- 
-- 
-- By default the object invoking the signal is not passed to the callback.
-- If you need to access it, you can use the implit @?self@ parameter.
-- Note that this requires activating the @ImplicitParams@ GHC extension.
-- 
afterTimelineSelectElementTrack :: (IsTimeline a, MonadIO m) => a -> ((?self :: a) => TimelineSelectElementTrackCallback) -> m SignalHandlerId
afterTimelineSelectElementTrack :: forall a (m :: * -> *).
(IsTimeline a, MonadIO m) =>
a
-> ((?self::a) => TimelineSelectElementTrackCallback)
-> m SignalHandlerId
afterTimelineSelectElementTrack a
obj (?self::a) => TimelineSelectElementTrackCallback
cb = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> TimelineSelectElementTrackCallback
wrapped a
self = let ?self = a
self in (?self::a) => TimelineSelectElementTrackCallback
cb
    let wrapped' :: C_TimelineSelectElementTrackCallback
wrapped' = forall a.
GObject a =>
(a -> TimelineSelectElementTrackCallback)
-> C_TimelineSelectElementTrackCallback
wrap_TimelineSelectElementTrackCallback a -> TimelineSelectElementTrackCallback
wrapped
    FunPtr C_TimelineSelectElementTrackCallback
wrapped'' <- C_TimelineSelectElementTrackCallback
-> IO (FunPtr C_TimelineSelectElementTrackCallback)
mk_TimelineSelectElementTrackCallback C_TimelineSelectElementTrackCallback
wrapped'
    forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"select-element-track" FunPtr C_TimelineSelectElementTrackCallback
wrapped'' SignalConnectMode
SignalConnectAfter forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data TimelineSelectElementTrackSignalInfo
instance SignalInfo TimelineSelectElementTrackSignalInfo where
    type HaskellCallbackType TimelineSelectElementTrackSignalInfo = TimelineSelectElementTrackCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_TimelineSelectElementTrackCallback cb
        cb'' <- mk_TimelineSelectElementTrackCallback cb'
        connectSignalFunPtr obj "select-element-track" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GES.Objects.Timeline::select-element-track"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.1/docs/GI-GES-Objects-Timeline.html#g:signal:selectElementTrack"})

#endif

-- signal Timeline::select-tracks-for-object
-- | This will be emitted whenever the timeline needs to determine which
-- tracks a clip\'s children should be added to. The track element will
-- be added to each of the tracks given in the return. If a track
-- element is selected to go into multiple tracks, it will be copied
-- into the additional tracks, under the same clip. Note that the copy
-- will *not* keep its properties or state in sync with the original.
-- 
-- Connect to this signal once if you wish to control which element
-- should be added to which track. Doing so will overwrite the default
-- behaviour, which adds /@trackElement@/ to all tracks whose
-- [Track:trackType]("GI.GES.Objects.Track#g:attr:trackType") includes the /@trackElement@/\'s
-- [TrackElement:trackType]("GI.GES.Objects.TrackElement#g:attr:trackType").
-- 
-- Note that under the default track selection, if a clip would produce
-- multiple core children of the same t'GI.GES.Flags.TrackType', it will choose
-- one of the core children arbitrarily to place in the corresponding
-- tracks, with a warning for the other core children that are not
-- placed in the track. For example, this would happen for a t'GI.GES.Objects.UriClip.UriClip'
-- that points to a file that contains multiple audio streams. If you
-- wish to choose the stream, you could connect to this signal, and use,
-- say, 'GI.GES.Objects.UriSourceAsset.uriSourceAssetGetStreamInfo' to choose which core
-- source to add.
-- 
-- When a clip is first added to a timeline, its core elements will
-- be created for the current tracks in the timeline if they have not
-- already been created. Then this will be emitted for each of these
-- core children to select which tracks, if any, they should be added
-- to. It will then be called for any non-core children in the clip.
-- 
-- In addition, if a new track element is ever added to a clip in a
-- timeline (and it is not already part of a track) this will be emitted
-- to select which tracks the element should be added to.
-- 
-- Finally, as a special case, if a track is added to the timeline
-- *after* it already contains clips, then it will request the creation
-- of the clips\' core elements of the corresponding type, if they have
-- not already been created, and this signal will be emitted for each of
-- these newly created elements. In addition, this will also be released
-- for all other track elements in the timeline\'s clips that have not
-- yet been assigned a track. However, in this final case, the timeline
-- will only check whether the newly added track appears in the track
-- list. If it does appear, the track element will be added to the newly
-- added track. All other tracks in the returned track list are ignored.
-- 
-- In this latter case, track elements that are already part of a track
-- will not be asked if they want to be copied into the new track. If
-- you wish to do this, you can use 'GI.GES.Objects.Clip.clipAddChildToTrack'.
-- 
-- Note that the returned t'GI.GLib.Structs.PtrArray.PtrArray' should own a new reference to each
-- of its contained t'GI.GES.Objects.Track.Track'. The timeline will set the t'GI.GLib.Callbacks.DestroyNotify'
-- free function on the t'GI.GLib.Structs.PtrArray.PtrArray' to dereference the elements.
type TimelineSelectTracksForObjectCallback =
    GES.Clip.Clip
    -- ^ /@clip@/: The clip that /@trackElement@/ is being added to
    -> GES.TrackElement.TrackElement
    -- ^ /@trackElement@/: The element being added
    -> IO [GES.Track.Track]
    -- ^ __Returns:__ An array of
    -- t'GI.GES.Objects.Track.Track'-s that /@trackElement@/ should be added to, or 'P.Nothing' to
    -- not add the element to any track.

type C_TimelineSelectTracksForObjectCallback =
    Ptr Timeline ->                         -- object
    Ptr GES.Clip.Clip ->
    Ptr GES.TrackElement.TrackElement ->
    Ptr () ->                               -- user_data
    IO (Ptr (GPtrArray (Ptr GES.Track.Track)))

-- | Generate a function pointer callable from C code, from a `C_TimelineSelectTracksForObjectCallback`.
foreign import ccall "wrapper"
    mk_TimelineSelectTracksForObjectCallback :: C_TimelineSelectTracksForObjectCallback -> IO (FunPtr C_TimelineSelectTracksForObjectCallback)

wrap_TimelineSelectTracksForObjectCallback :: 
    GObject a => (a -> TimelineSelectTracksForObjectCallback) ->
    C_TimelineSelectTracksForObjectCallback
wrap_TimelineSelectTracksForObjectCallback :: forall a.
GObject a =>
(a -> TimelineSelectTracksForObjectCallback)
-> C_TimelineSelectTracksForObjectCallback
wrap_TimelineSelectTracksForObjectCallback a -> TimelineSelectTracksForObjectCallback
gi'cb Ptr Timeline
gi'selfPtr Ptr Clip
clip Ptr TrackElement
trackElement Ptr ()
_ = do
    Clip
clip' <- (forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Clip -> Clip
GES.Clip.Clip) Ptr Clip
clip
    TrackElement
trackElement' <- (forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr TrackElement -> TrackElement
GES.TrackElement.TrackElement) Ptr TrackElement
trackElement
    [Track]
result <- forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr Timeline
gi'selfPtr forall a b. (a -> b) -> a -> b
$ \Timeline
gi'self -> a -> TimelineSelectTracksForObjectCallback
gi'cb (coerce :: forall a b. Coercible a b => a -> b
Coerce.coerce Timeline
gi'self)  Clip
clip' TrackElement
trackElement'
    [Ptr Track]
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) => a -> IO (Ptr b)
B.ManagedPtr.disownObject [Track]
result
    Ptr (GPtrArray (Ptr Track))
result'' <- forall a. [Ptr a] -> IO (Ptr (GPtrArray (Ptr a)))
packGPtrArray [Ptr Track]
result'
    forall (m :: * -> *) a. Monad m => a -> m a
return Ptr (GPtrArray (Ptr Track))
result''


-- | Connect a signal handler for the [selectTracksForObject](#signal:selectTracksForObject) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' timeline #selectTracksForObject callback
-- @
-- 
-- 
onTimelineSelectTracksForObject :: (IsTimeline a, MonadIO m) => a -> ((?self :: a) => TimelineSelectTracksForObjectCallback) -> m SignalHandlerId
onTimelineSelectTracksForObject :: forall a (m :: * -> *).
(IsTimeline a, MonadIO m) =>
a
-> ((?self::a) => TimelineSelectTracksForObjectCallback)
-> m SignalHandlerId
onTimelineSelectTracksForObject a
obj (?self::a) => TimelineSelectTracksForObjectCallback
cb = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> TimelineSelectTracksForObjectCallback
wrapped a
self = let ?self = a
self in (?self::a) => TimelineSelectTracksForObjectCallback
cb
    let wrapped' :: C_TimelineSelectTracksForObjectCallback
wrapped' = forall a.
GObject a =>
(a -> TimelineSelectTracksForObjectCallback)
-> C_TimelineSelectTracksForObjectCallback
wrap_TimelineSelectTracksForObjectCallback a -> TimelineSelectTracksForObjectCallback
wrapped
    FunPtr C_TimelineSelectTracksForObjectCallback
wrapped'' <- C_TimelineSelectTracksForObjectCallback
-> IO (FunPtr C_TimelineSelectTracksForObjectCallback)
mk_TimelineSelectTracksForObjectCallback C_TimelineSelectTracksForObjectCallback
wrapped'
    forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"select-tracks-for-object" FunPtr C_TimelineSelectTracksForObjectCallback
wrapped'' SignalConnectMode
SignalConnectBefore forall a. Maybe a
Nothing

-- | Connect a signal handler for the [selectTracksForObject](#signal:selectTracksForObject) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' timeline #selectTracksForObject callback
-- @
-- 
-- 
-- 
-- By default the object invoking the signal is not passed to the callback.
-- If you need to access it, you can use the implit @?self@ parameter.
-- Note that this requires activating the @ImplicitParams@ GHC extension.
-- 
afterTimelineSelectTracksForObject :: (IsTimeline a, MonadIO m) => a -> ((?self :: a) => TimelineSelectTracksForObjectCallback) -> m SignalHandlerId
afterTimelineSelectTracksForObject :: forall a (m :: * -> *).
(IsTimeline a, MonadIO m) =>
a
-> ((?self::a) => TimelineSelectTracksForObjectCallback)
-> m SignalHandlerId
afterTimelineSelectTracksForObject a
obj (?self::a) => TimelineSelectTracksForObjectCallback
cb = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> TimelineSelectTracksForObjectCallback
wrapped a
self = let ?self = a
self in (?self::a) => TimelineSelectTracksForObjectCallback
cb
    let wrapped' :: C_TimelineSelectTracksForObjectCallback
wrapped' = forall a.
GObject a =>
(a -> TimelineSelectTracksForObjectCallback)
-> C_TimelineSelectTracksForObjectCallback
wrap_TimelineSelectTracksForObjectCallback a -> TimelineSelectTracksForObjectCallback
wrapped
    FunPtr C_TimelineSelectTracksForObjectCallback
wrapped'' <- C_TimelineSelectTracksForObjectCallback
-> IO (FunPtr C_TimelineSelectTracksForObjectCallback)
mk_TimelineSelectTracksForObjectCallback C_TimelineSelectTracksForObjectCallback
wrapped'
    forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"select-tracks-for-object" FunPtr C_TimelineSelectTracksForObjectCallback
wrapped'' SignalConnectMode
SignalConnectAfter forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data TimelineSelectTracksForObjectSignalInfo
instance SignalInfo TimelineSelectTracksForObjectSignalInfo where
    type HaskellCallbackType TimelineSelectTracksForObjectSignalInfo = TimelineSelectTracksForObjectCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_TimelineSelectTracksForObjectCallback cb
        cb'' <- mk_TimelineSelectTracksForObjectCallback cb'
        connectSignalFunPtr obj "select-tracks-for-object" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GES.Objects.Timeline::select-tracks-for-object"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.1/docs/GI-GES-Objects-Timeline.html#g:signal:selectTracksForObject"})

#endif

-- signal Timeline::snapping-ended
-- | Will be emitted whenever a snapping event ends. After a snap event
-- has started (see [Timeline::snappingStarted]("GI.GES.Objects.Timeline#g:signal:snappingStarted")), it can later end
-- because either another timeline edit has occurred (which may or may
-- not have created a new snapping event), or because the timeline has
-- been committed.
type TimelineSnappingEndedCallback =
    GES.TrackElement.TrackElement
    -- ^ /@obj1@/: The first element that was snapping
    -> GES.TrackElement.TrackElement
    -- ^ /@obj2@/: The second element that was snapping
    -> Word64
    -- ^ /@position@/: The position where the two objects were to be snapped to
    -> IO ()

type C_TimelineSnappingEndedCallback =
    Ptr Timeline ->                         -- object
    Ptr GES.TrackElement.TrackElement ->
    Ptr GES.TrackElement.TrackElement ->
    Word64 ->
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_TimelineSnappingEndedCallback`.
foreign import ccall "wrapper"
    mk_TimelineSnappingEndedCallback :: C_TimelineSnappingEndedCallback -> IO (FunPtr C_TimelineSnappingEndedCallback)

wrap_TimelineSnappingEndedCallback :: 
    GObject a => (a -> TimelineSnappingEndedCallback) ->
    C_TimelineSnappingEndedCallback
wrap_TimelineSnappingEndedCallback :: forall a.
GObject a =>
(a -> TimelineSnappingEndedCallback)
-> C_TimelineSnappingEndedCallback
wrap_TimelineSnappingEndedCallback a -> TimelineSnappingEndedCallback
gi'cb Ptr Timeline
gi'selfPtr Ptr TrackElement
obj1 Ptr TrackElement
obj2 Word64
position Ptr ()
_ = do
    TrackElement
obj1' <- (forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr TrackElement -> TrackElement
GES.TrackElement.TrackElement) Ptr TrackElement
obj1
    TrackElement
obj2' <- (forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr TrackElement -> TrackElement
GES.TrackElement.TrackElement) Ptr TrackElement
obj2
    forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr Timeline
gi'selfPtr forall a b. (a -> b) -> a -> b
$ \Timeline
gi'self -> a -> TimelineSnappingEndedCallback
gi'cb (coerce :: forall a b. Coercible a b => a -> b
Coerce.coerce Timeline
gi'self)  TrackElement
obj1' TrackElement
obj2' Word64
position


-- | Connect a signal handler for the [snappingEnded](#signal:snappingEnded) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' timeline #snappingEnded callback
-- @
-- 
-- 
onTimelineSnappingEnded :: (IsTimeline a, MonadIO m) => a -> ((?self :: a) => TimelineSnappingEndedCallback) -> m SignalHandlerId
onTimelineSnappingEnded :: forall a (m :: * -> *).
(IsTimeline a, MonadIO m) =>
a
-> ((?self::a) => TimelineSnappingEndedCallback)
-> m SignalHandlerId
onTimelineSnappingEnded a
obj (?self::a) => TimelineSnappingEndedCallback
cb = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> TimelineSnappingEndedCallback
wrapped a
self = let ?self = a
self in (?self::a) => TimelineSnappingEndedCallback
cb
    let wrapped' :: C_TimelineSnappingEndedCallback
wrapped' = forall a.
GObject a =>
(a -> TimelineSnappingEndedCallback)
-> C_TimelineSnappingEndedCallback
wrap_TimelineSnappingEndedCallback a -> TimelineSnappingEndedCallback
wrapped
    FunPtr C_TimelineSnappingEndedCallback
wrapped'' <- C_TimelineSnappingEndedCallback
-> IO (FunPtr C_TimelineSnappingEndedCallback)
mk_TimelineSnappingEndedCallback C_TimelineSnappingEndedCallback
wrapped'
    forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"snapping-ended" FunPtr C_TimelineSnappingEndedCallback
wrapped'' SignalConnectMode
SignalConnectBefore forall a. Maybe a
Nothing

-- | Connect a signal handler for the [snappingEnded](#signal:snappingEnded) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' timeline #snappingEnded callback
-- @
-- 
-- 
-- 
-- By default the object invoking the signal is not passed to the callback.
-- If you need to access it, you can use the implit @?self@ parameter.
-- Note that this requires activating the @ImplicitParams@ GHC extension.
-- 
afterTimelineSnappingEnded :: (IsTimeline a, MonadIO m) => a -> ((?self :: a) => TimelineSnappingEndedCallback) -> m SignalHandlerId
afterTimelineSnappingEnded :: forall a (m :: * -> *).
(IsTimeline a, MonadIO m) =>
a
-> ((?self::a) => TimelineSnappingEndedCallback)
-> m SignalHandlerId
afterTimelineSnappingEnded a
obj (?self::a) => TimelineSnappingEndedCallback
cb = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> TimelineSnappingEndedCallback
wrapped a
self = let ?self = a
self in (?self::a) => TimelineSnappingEndedCallback
cb
    let wrapped' :: C_TimelineSnappingEndedCallback
wrapped' = forall a.
GObject a =>
(a -> TimelineSnappingEndedCallback)
-> C_TimelineSnappingEndedCallback
wrap_TimelineSnappingEndedCallback a -> TimelineSnappingEndedCallback
wrapped
    FunPtr C_TimelineSnappingEndedCallback
wrapped'' <- C_TimelineSnappingEndedCallback
-> IO (FunPtr C_TimelineSnappingEndedCallback)
mk_TimelineSnappingEndedCallback C_TimelineSnappingEndedCallback
wrapped'
    forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"snapping-ended" FunPtr C_TimelineSnappingEndedCallback
wrapped'' SignalConnectMode
SignalConnectAfter forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data TimelineSnappingEndedSignalInfo
instance SignalInfo TimelineSnappingEndedSignalInfo where
    type HaskellCallbackType TimelineSnappingEndedSignalInfo = TimelineSnappingEndedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_TimelineSnappingEndedCallback cb
        cb'' <- mk_TimelineSnappingEndedCallback cb'
        connectSignalFunPtr obj "snapping-ended" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GES.Objects.Timeline::snapping-ended"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.1/docs/GI-GES-Objects-Timeline.html#g:signal:snappingEnded"})

#endif

-- signal Timeline::snapping-started
-- | Will be emitted whenever an element\'s movement invokes a snapping
-- event during an edit (usually of one of its ancestors) because its
-- start or end point lies within the [Timeline:snappingDistance]("GI.GES.Objects.Timeline#g:attr:snappingDistance") of
-- another element\'s start or end point.
-- 
-- See t'GI.GES.Enums.EditMode' to see what can snap during an edit.
-- 
-- Note that only up to one snapping-started signal will be emitted per
-- element edit within a timeline.
type TimelineSnappingStartedCallback =
    GES.TrackElement.TrackElement
    -- ^ /@obj1@/: The first element that is snapping
    -> GES.TrackElement.TrackElement
    -- ^ /@obj2@/: The second element that is snapping
    -> Word64
    -- ^ /@position@/: The position where the two objects will snap to
    -> IO ()

type C_TimelineSnappingStartedCallback =
    Ptr Timeline ->                         -- object
    Ptr GES.TrackElement.TrackElement ->
    Ptr GES.TrackElement.TrackElement ->
    Word64 ->
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_TimelineSnappingStartedCallback`.
foreign import ccall "wrapper"
    mk_TimelineSnappingStartedCallback :: C_TimelineSnappingStartedCallback -> IO (FunPtr C_TimelineSnappingStartedCallback)

wrap_TimelineSnappingStartedCallback :: 
    GObject a => (a -> TimelineSnappingStartedCallback) ->
    C_TimelineSnappingStartedCallback
wrap_TimelineSnappingStartedCallback :: forall a.
GObject a =>
(a -> TimelineSnappingEndedCallback)
-> C_TimelineSnappingEndedCallback
wrap_TimelineSnappingStartedCallback a -> TimelineSnappingEndedCallback
gi'cb Ptr Timeline
gi'selfPtr Ptr TrackElement
obj1 Ptr TrackElement
obj2 Word64
position Ptr ()
_ = do
    TrackElement
obj1' <- (forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr TrackElement -> TrackElement
GES.TrackElement.TrackElement) Ptr TrackElement
obj1
    TrackElement
obj2' <- (forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr TrackElement -> TrackElement
GES.TrackElement.TrackElement) Ptr TrackElement
obj2
    forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr Timeline
gi'selfPtr forall a b. (a -> b) -> a -> b
$ \Timeline
gi'self -> a -> TimelineSnappingEndedCallback
gi'cb (coerce :: forall a b. Coercible a b => a -> b
Coerce.coerce Timeline
gi'self)  TrackElement
obj1' TrackElement
obj2' Word64
position


-- | Connect a signal handler for the [snappingStarted](#signal:snappingStarted) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' timeline #snappingStarted callback
-- @
-- 
-- 
onTimelineSnappingStarted :: (IsTimeline a, MonadIO m) => a -> ((?self :: a) => TimelineSnappingStartedCallback) -> m SignalHandlerId
onTimelineSnappingStarted :: forall a (m :: * -> *).
(IsTimeline a, MonadIO m) =>
a
-> ((?self::a) => TimelineSnappingEndedCallback)
-> m SignalHandlerId
onTimelineSnappingStarted a
obj (?self::a) => TimelineSnappingEndedCallback
cb = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> TimelineSnappingEndedCallback
wrapped a
self = let ?self = a
self in (?self::a) => TimelineSnappingEndedCallback
cb
    let wrapped' :: C_TimelineSnappingEndedCallback
wrapped' = forall a.
GObject a =>
(a -> TimelineSnappingEndedCallback)
-> C_TimelineSnappingEndedCallback
wrap_TimelineSnappingStartedCallback a -> TimelineSnappingEndedCallback
wrapped
    FunPtr C_TimelineSnappingEndedCallback
wrapped'' <- C_TimelineSnappingEndedCallback
-> IO (FunPtr C_TimelineSnappingEndedCallback)
mk_TimelineSnappingStartedCallback C_TimelineSnappingEndedCallback
wrapped'
    forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"snapping-started" FunPtr C_TimelineSnappingEndedCallback
wrapped'' SignalConnectMode
SignalConnectBefore forall a. Maybe a
Nothing

-- | Connect a signal handler for the [snappingStarted](#signal:snappingStarted) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' timeline #snappingStarted callback
-- @
-- 
-- 
-- 
-- By default the object invoking the signal is not passed to the callback.
-- If you need to access it, you can use the implit @?self@ parameter.
-- Note that this requires activating the @ImplicitParams@ GHC extension.
-- 
afterTimelineSnappingStarted :: (IsTimeline a, MonadIO m) => a -> ((?self :: a) => TimelineSnappingStartedCallback) -> m SignalHandlerId
afterTimelineSnappingStarted :: forall a (m :: * -> *).
(IsTimeline a, MonadIO m) =>
a
-> ((?self::a) => TimelineSnappingEndedCallback)
-> m SignalHandlerId
afterTimelineSnappingStarted a
obj (?self::a) => TimelineSnappingEndedCallback
cb = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> TimelineSnappingEndedCallback
wrapped a
self = let ?self = a
self in (?self::a) => TimelineSnappingEndedCallback
cb
    let wrapped' :: C_TimelineSnappingEndedCallback
wrapped' = forall a.
GObject a =>
(a -> TimelineSnappingEndedCallback)
-> C_TimelineSnappingEndedCallback
wrap_TimelineSnappingStartedCallback a -> TimelineSnappingEndedCallback
wrapped
    FunPtr C_TimelineSnappingEndedCallback
wrapped'' <- C_TimelineSnappingEndedCallback
-> IO (FunPtr C_TimelineSnappingEndedCallback)
mk_TimelineSnappingStartedCallback C_TimelineSnappingEndedCallback
wrapped'
    forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"snapping-started" FunPtr C_TimelineSnappingEndedCallback
wrapped'' SignalConnectMode
SignalConnectAfter forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data TimelineSnappingStartedSignalInfo
instance SignalInfo TimelineSnappingStartedSignalInfo where
    type HaskellCallbackType TimelineSnappingStartedSignalInfo = TimelineSnappingStartedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_TimelineSnappingStartedCallback cb
        cb'' <- mk_TimelineSnappingStartedCallback cb'
        connectSignalFunPtr obj "snapping-started" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GES.Objects.Timeline::snapping-started"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.1/docs/GI-GES-Objects-Timeline.html#g:signal:snappingStarted"})

#endif

-- signal Timeline::track-added
-- | Will be emitted after the track is added to the timeline.
-- 
-- Note that this should not be emitted whilst a timeline is being
-- loaded from its t'GI.GES.Objects.Project.Project' asset. You should connect to the
-- project\'s [Project::loaded]("GI.GES.Objects.Project#g:signal:loaded") signal if you want to know which
-- tracks were created for the timeline.
type TimelineTrackAddedCallback =
    GES.Track.Track
    -- ^ /@track@/: The track that was added to /@timeline@/
    -> IO ()

type C_TimelineTrackAddedCallback =
    Ptr Timeline ->                         -- object
    Ptr GES.Track.Track ->
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_TimelineTrackAddedCallback`.
foreign import ccall "wrapper"
    mk_TimelineTrackAddedCallback :: C_TimelineTrackAddedCallback -> IO (FunPtr C_TimelineTrackAddedCallback)

wrap_TimelineTrackAddedCallback :: 
    GObject a => (a -> TimelineTrackAddedCallback) ->
    C_TimelineTrackAddedCallback
wrap_TimelineTrackAddedCallback :: forall a.
GObject a =>
(a -> TimelineTrackAddedCallback) -> C_TimelineTrackAddedCallback
wrap_TimelineTrackAddedCallback a -> TimelineTrackAddedCallback
gi'cb Ptr Timeline
gi'selfPtr Ptr Track
track Ptr ()
_ = do
    Track
track' <- (forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Track -> Track
GES.Track.Track) Ptr Track
track
    forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr Timeline
gi'selfPtr forall a b. (a -> b) -> a -> b
$ \Timeline
gi'self -> a -> TimelineTrackAddedCallback
gi'cb (coerce :: forall a b. Coercible a b => a -> b
Coerce.coerce Timeline
gi'self)  Track
track'


-- | Connect a signal handler for the [trackAdded](#signal:trackAdded) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' timeline #trackAdded callback
-- @
-- 
-- 
onTimelineTrackAdded :: (IsTimeline a, MonadIO m) => a -> ((?self :: a) => TimelineTrackAddedCallback) -> m SignalHandlerId
onTimelineTrackAdded :: forall a (m :: * -> *).
(IsTimeline a, MonadIO m) =>
a
-> ((?self::a) => TimelineTrackAddedCallback) -> m SignalHandlerId
onTimelineTrackAdded a
obj (?self::a) => TimelineTrackAddedCallback
cb = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> TimelineTrackAddedCallback
wrapped a
self = let ?self = a
self in (?self::a) => TimelineTrackAddedCallback
cb
    let wrapped' :: C_TimelineTrackAddedCallback
wrapped' = forall a.
GObject a =>
(a -> TimelineTrackAddedCallback) -> C_TimelineTrackAddedCallback
wrap_TimelineTrackAddedCallback a -> TimelineTrackAddedCallback
wrapped
    FunPtr C_TimelineTrackAddedCallback
wrapped'' <- C_TimelineTrackAddedCallback
-> IO (FunPtr C_TimelineTrackAddedCallback)
mk_TimelineTrackAddedCallback C_TimelineTrackAddedCallback
wrapped'
    forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"track-added" FunPtr C_TimelineTrackAddedCallback
wrapped'' SignalConnectMode
SignalConnectBefore forall a. Maybe a
Nothing

-- | Connect a signal handler for the [trackAdded](#signal:trackAdded) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' timeline #trackAdded callback
-- @
-- 
-- 
-- 
-- By default the object invoking the signal is not passed to the callback.
-- If you need to access it, you can use the implit @?self@ parameter.
-- Note that this requires activating the @ImplicitParams@ GHC extension.
-- 
afterTimelineTrackAdded :: (IsTimeline a, MonadIO m) => a -> ((?self :: a) => TimelineTrackAddedCallback) -> m SignalHandlerId
afterTimelineTrackAdded :: forall a (m :: * -> *).
(IsTimeline a, MonadIO m) =>
a
-> ((?self::a) => TimelineTrackAddedCallback) -> m SignalHandlerId
afterTimelineTrackAdded a
obj (?self::a) => TimelineTrackAddedCallback
cb = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> TimelineTrackAddedCallback
wrapped a
self = let ?self = a
self in (?self::a) => TimelineTrackAddedCallback
cb
    let wrapped' :: C_TimelineTrackAddedCallback
wrapped' = forall a.
GObject a =>
(a -> TimelineTrackAddedCallback) -> C_TimelineTrackAddedCallback
wrap_TimelineTrackAddedCallback a -> TimelineTrackAddedCallback
wrapped
    FunPtr C_TimelineTrackAddedCallback
wrapped'' <- C_TimelineTrackAddedCallback
-> IO (FunPtr C_TimelineTrackAddedCallback)
mk_TimelineTrackAddedCallback C_TimelineTrackAddedCallback
wrapped'
    forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"track-added" FunPtr C_TimelineTrackAddedCallback
wrapped'' SignalConnectMode
SignalConnectAfter forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data TimelineTrackAddedSignalInfo
instance SignalInfo TimelineTrackAddedSignalInfo where
    type HaskellCallbackType TimelineTrackAddedSignalInfo = TimelineTrackAddedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_TimelineTrackAddedCallback cb
        cb'' <- mk_TimelineTrackAddedCallback cb'
        connectSignalFunPtr obj "track-added" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GES.Objects.Timeline::track-added"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.1/docs/GI-GES-Objects-Timeline.html#g:signal:trackAdded"})

#endif

-- signal Timeline::track-removed
-- | Will be emitted after the track is removed from the timeline.
type TimelineTrackRemovedCallback =
    GES.Track.Track
    -- ^ /@track@/: The track that was removed from /@timeline@/
    -> IO ()

type C_TimelineTrackRemovedCallback =
    Ptr Timeline ->                         -- object
    Ptr GES.Track.Track ->
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_TimelineTrackRemovedCallback`.
foreign import ccall "wrapper"
    mk_TimelineTrackRemovedCallback :: C_TimelineTrackRemovedCallback -> IO (FunPtr C_TimelineTrackRemovedCallback)

wrap_TimelineTrackRemovedCallback :: 
    GObject a => (a -> TimelineTrackRemovedCallback) ->
    C_TimelineTrackRemovedCallback
wrap_TimelineTrackRemovedCallback :: forall a.
GObject a =>
(a -> TimelineTrackAddedCallback) -> C_TimelineTrackAddedCallback
wrap_TimelineTrackRemovedCallback a -> TimelineTrackAddedCallback
gi'cb Ptr Timeline
gi'selfPtr Ptr Track
track Ptr ()
_ = do
    Track
track' <- (forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Track -> Track
GES.Track.Track) Ptr Track
track
    forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr Timeline
gi'selfPtr forall a b. (a -> b) -> a -> b
$ \Timeline
gi'self -> a -> TimelineTrackAddedCallback
gi'cb (coerce :: forall a b. Coercible a b => a -> b
Coerce.coerce Timeline
gi'self)  Track
track'


-- | Connect a signal handler for the [trackRemoved](#signal:trackRemoved) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' timeline #trackRemoved callback
-- @
-- 
-- 
onTimelineTrackRemoved :: (IsTimeline a, MonadIO m) => a -> ((?self :: a) => TimelineTrackRemovedCallback) -> m SignalHandlerId
onTimelineTrackRemoved :: forall a (m :: * -> *).
(IsTimeline a, MonadIO m) =>
a
-> ((?self::a) => TimelineTrackAddedCallback) -> m SignalHandlerId
onTimelineTrackRemoved a
obj (?self::a) => TimelineTrackAddedCallback
cb = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> TimelineTrackAddedCallback
wrapped a
self = let ?self = a
self in (?self::a) => TimelineTrackAddedCallback
cb
    let wrapped' :: C_TimelineTrackAddedCallback
wrapped' = forall a.
GObject a =>
(a -> TimelineTrackAddedCallback) -> C_TimelineTrackAddedCallback
wrap_TimelineTrackRemovedCallback a -> TimelineTrackAddedCallback
wrapped
    FunPtr C_TimelineTrackAddedCallback
wrapped'' <- C_TimelineTrackAddedCallback
-> IO (FunPtr C_TimelineTrackAddedCallback)
mk_TimelineTrackRemovedCallback C_TimelineTrackAddedCallback
wrapped'
    forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"track-removed" FunPtr C_TimelineTrackAddedCallback
wrapped'' SignalConnectMode
SignalConnectBefore forall a. Maybe a
Nothing

-- | Connect a signal handler for the [trackRemoved](#signal:trackRemoved) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' timeline #trackRemoved callback
-- @
-- 
-- 
-- 
-- By default the object invoking the signal is not passed to the callback.
-- If you need to access it, you can use the implit @?self@ parameter.
-- Note that this requires activating the @ImplicitParams@ GHC extension.
-- 
afterTimelineTrackRemoved :: (IsTimeline a, MonadIO m) => a -> ((?self :: a) => TimelineTrackRemovedCallback) -> m SignalHandlerId
afterTimelineTrackRemoved :: forall a (m :: * -> *).
(IsTimeline a, MonadIO m) =>
a
-> ((?self::a) => TimelineTrackAddedCallback) -> m SignalHandlerId
afterTimelineTrackRemoved a
obj (?self::a) => TimelineTrackAddedCallback
cb = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> TimelineTrackAddedCallback
wrapped a
self = let ?self = a
self in (?self::a) => TimelineTrackAddedCallback
cb
    let wrapped' :: C_TimelineTrackAddedCallback
wrapped' = forall a.
GObject a =>
(a -> TimelineTrackAddedCallback) -> C_TimelineTrackAddedCallback
wrap_TimelineTrackRemovedCallback a -> TimelineTrackAddedCallback
wrapped
    FunPtr C_TimelineTrackAddedCallback
wrapped'' <- C_TimelineTrackAddedCallback
-> IO (FunPtr C_TimelineTrackAddedCallback)
mk_TimelineTrackRemovedCallback C_TimelineTrackAddedCallback
wrapped'
    forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"track-removed" FunPtr C_TimelineTrackAddedCallback
wrapped'' SignalConnectMode
SignalConnectAfter forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data TimelineTrackRemovedSignalInfo
instance SignalInfo TimelineTrackRemovedSignalInfo where
    type HaskellCallbackType TimelineTrackRemovedSignalInfo = TimelineTrackRemovedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_TimelineTrackRemovedCallback cb
        cb'' <- mk_TimelineTrackRemovedCallback cb'
        connectSignalFunPtr obj "track-removed" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GES.Objects.Timeline::track-removed"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.1/docs/GI-GES-Objects-Timeline.html#g:signal:trackRemoved"})

#endif

-- VVV Prop "auto-transition"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@auto-transition@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' timeline #autoTransition
-- @
getTimelineAutoTransition :: (MonadIO m, IsTimeline o) => o -> m Bool
getTimelineAutoTransition :: forall (m :: * -> *) o. (MonadIO m, IsTimeline o) => o -> m Bool
getTimelineAutoTransition 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
"auto-transition"

-- | Set the value of the “@auto-transition@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' timeline [ #autoTransition 'Data.GI.Base.Attributes.:=' value ]
-- @
setTimelineAutoTransition :: (MonadIO m, IsTimeline o) => o -> Bool -> m ()
setTimelineAutoTransition :: forall (m :: * -> *) o.
(MonadIO m, IsTimeline o) =>
o -> Bool -> m ()
setTimelineAutoTransition o
obj Bool
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 -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"auto-transition" Bool
val

-- | Construct a `GValueConstruct` with valid value for the “@auto-transition@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructTimelineAutoTransition :: (IsTimeline o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructTimelineAutoTransition :: forall o (m :: * -> *).
(IsTimeline o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructTimelineAutoTransition Bool
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 -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"auto-transition" Bool
val

#if defined(ENABLE_OVERLOADING)
data TimelineAutoTransitionPropertyInfo
instance AttrInfo TimelineAutoTransitionPropertyInfo where
    type AttrAllowedOps TimelineAutoTransitionPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint TimelineAutoTransitionPropertyInfo = IsTimeline
    type AttrSetTypeConstraint TimelineAutoTransitionPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint TimelineAutoTransitionPropertyInfo = (~) Bool
    type AttrTransferType TimelineAutoTransitionPropertyInfo = Bool
    type AttrGetType TimelineAutoTransitionPropertyInfo = Bool
    type AttrLabel TimelineAutoTransitionPropertyInfo = "auto-transition"
    type AttrOrigin TimelineAutoTransitionPropertyInfo = Timeline
    attrGet = getTimelineAutoTransition
    attrSet = setTimelineAutoTransition
    attrTransfer _ v = do
        return v
    attrConstruct = constructTimelineAutoTransition
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GES.Objects.Timeline.autoTransition"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.1/docs/GI-GES-Objects-Timeline.html#g:attr:autoTransition"
        })
#endif

-- VVV Prop "duration"
   -- Type: TBasicType TUInt64
   -- Flags: [PropertyReadable]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@duration@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' timeline #duration
-- @
getTimelineDuration :: (MonadIO m, IsTimeline o) => o -> m Word64
getTimelineDuration :: forall (m :: * -> *) o. (MonadIO m, IsTimeline o) => o -> m Word64
getTimelineDuration 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"

#if defined(ENABLE_OVERLOADING)
data TimelineDurationPropertyInfo
instance AttrInfo TimelineDurationPropertyInfo where
    type AttrAllowedOps TimelineDurationPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint TimelineDurationPropertyInfo = IsTimeline
    type AttrSetTypeConstraint TimelineDurationPropertyInfo = (~) ()
    type AttrTransferTypeConstraint TimelineDurationPropertyInfo = (~) ()
    type AttrTransferType TimelineDurationPropertyInfo = ()
    type AttrGetType TimelineDurationPropertyInfo = Word64
    type AttrLabel TimelineDurationPropertyInfo = "duration"
    type AttrOrigin TimelineDurationPropertyInfo = Timeline
    attrGet = getTimelineDuration
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GES.Objects.Timeline.duration"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.1/docs/GI-GES-Objects-Timeline.html#g:attr:duration"
        })
#endif

-- VVV Prop "snapping-distance"
   -- Type: TBasicType TUInt64
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@snapping-distance@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' timeline #snappingDistance
-- @
getTimelineSnappingDistance :: (MonadIO m, IsTimeline o) => o -> m Word64
getTimelineSnappingDistance :: forall (m :: * -> *) o. (MonadIO m, IsTimeline o) => o -> m Word64
getTimelineSnappingDistance 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
"snapping-distance"

-- | Set the value of the “@snapping-distance@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' timeline [ #snappingDistance 'Data.GI.Base.Attributes.:=' value ]
-- @
setTimelineSnappingDistance :: (MonadIO m, IsTimeline o) => o -> Word64 -> m ()
setTimelineSnappingDistance :: forall (m :: * -> *) o.
(MonadIO m, IsTimeline o) =>
o -> Word64 -> m ()
setTimelineSnappingDistance 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
"snapping-distance" Word64
val

-- | Construct a `GValueConstruct` with valid value for the “@snapping-distance@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructTimelineSnappingDistance :: (IsTimeline o, MIO.MonadIO m) => Word64 -> m (GValueConstruct o)
constructTimelineSnappingDistance :: forall o (m :: * -> *).
(IsTimeline o, MonadIO m) =>
Word64 -> m (GValueConstruct o)
constructTimelineSnappingDistance 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
"snapping-distance" Word64
val

#if defined(ENABLE_OVERLOADING)
data TimelineSnappingDistancePropertyInfo
instance AttrInfo TimelineSnappingDistancePropertyInfo where
    type AttrAllowedOps TimelineSnappingDistancePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint TimelineSnappingDistancePropertyInfo = IsTimeline
    type AttrSetTypeConstraint TimelineSnappingDistancePropertyInfo = (~) Word64
    type AttrTransferTypeConstraint TimelineSnappingDistancePropertyInfo = (~) Word64
    type AttrTransferType TimelineSnappingDistancePropertyInfo = Word64
    type AttrGetType TimelineSnappingDistancePropertyInfo = Word64
    type AttrLabel TimelineSnappingDistancePropertyInfo = "snapping-distance"
    type AttrOrigin TimelineSnappingDistancePropertyInfo = Timeline
    attrGet = getTimelineSnappingDistance
    attrSet = setTimelineSnappingDistance
    attrTransfer _ v = do
        return v
    attrConstruct = constructTimelineSnappingDistance
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GES.Objects.Timeline.snappingDistance"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.1/docs/GI-GES-Objects-Timeline.html#g:attr:snappingDistance"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Timeline
type instance O.AttributeList Timeline = TimelineAttributeList
type TimelineAttributeList = ('[ '("asyncHandling", Gst.Bin.BinAsyncHandlingPropertyInfo), '("autoTransition", TimelineAutoTransitionPropertyInfo), '("duration", TimelineDurationPropertyInfo), '("messageForward", Gst.Bin.BinMessageForwardPropertyInfo), '("name", Gst.Object.ObjectNamePropertyInfo), '("parent", Gst.Object.ObjectParentPropertyInfo), '("snappingDistance", TimelineSnappingDistancePropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
timelineAutoTransition :: AttrLabelProxy "autoTransition"
timelineAutoTransition = AttrLabelProxy

timelineDuration :: AttrLabelProxy "duration"
timelineDuration = AttrLabelProxy

timelineSnappingDistance :: AttrLabelProxy "snappingDistance"
timelineSnappingDistance = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Timeline = TimelineSignalList
type TimelineSignalList = ('[ '("childAdded", Gst.ChildProxy.ChildProxyChildAddedSignalInfo), '("childRemoved", Gst.ChildProxy.ChildProxyChildRemovedSignalInfo), '("commited", TimelineCommitedSignalInfo), '("deepElementAdded", Gst.Bin.BinDeepElementAddedSignalInfo), '("deepElementRemoved", Gst.Bin.BinDeepElementRemovedSignalInfo), '("deepNotify", Gst.Object.ObjectDeepNotifySignalInfo), '("doLatency", Gst.Bin.BinDoLatencySignalInfo), '("elementAdded", Gst.Bin.BinElementAddedSignalInfo), '("elementRemoved", Gst.Bin.BinElementRemovedSignalInfo), '("groupAdded", TimelineGroupAddedSignalInfo), '("groupRemoved", TimelineGroupRemovedSignalInfo), '("layerAdded", TimelineLayerAddedSignalInfo), '("layerRemoved", TimelineLayerRemovedSignalInfo), '("noMorePads", Gst.Element.ElementNoMorePadsSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("notifyMeta", GES.MetaContainer.MetaContainerNotifyMetaSignalInfo), '("padAdded", Gst.Element.ElementPadAddedSignalInfo), '("padRemoved", Gst.Element.ElementPadRemovedSignalInfo), '("selectElementTrack", TimelineSelectElementTrackSignalInfo), '("selectTracksForObject", TimelineSelectTracksForObjectSignalInfo), '("snappingEnded", TimelineSnappingEndedSignalInfo), '("snappingStarted", TimelineSnappingStartedSignalInfo), '("trackAdded", TimelineTrackAddedSignalInfo), '("trackRemoved", TimelineTrackRemovedSignalInfo)] :: [(Symbol, *)])

#endif

-- method Timeline::new
-- method type : Constructor
-- Args: []
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GES" , name = "Timeline" })
-- throws : False
-- Skip return : False

foreign import ccall "ges_timeline_new" ges_timeline_new :: 
    IO (Ptr Timeline)

-- | Creates a new empty timeline.
timelineNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m Timeline
    -- ^ __Returns:__ The new timeline.
timelineNew :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m Timeline
timelineNew  = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
    Ptr Timeline
result <- IO (Ptr Timeline)
ges_timeline_new
    forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"timelineNew" Ptr Timeline
result
    Timeline
result' <- (forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Timeline -> Timeline
Timeline) Ptr Timeline
result
    forall (m :: * -> *) a. Monad m => a -> m a
return Timeline
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Timeline::new_audio_video
-- method type : Constructor
-- Args: []
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GES" , name = "Timeline" })
-- throws : False
-- Skip return : False

foreign import ccall "ges_timeline_new_audio_video" ges_timeline_new_audio_video :: 
    IO (Ptr Timeline)

-- | Creates a new timeline containing a single t'GI.GES.Objects.AudioTrack.AudioTrack' and a
-- single t'GI.GES.Objects.VideoTrack.VideoTrack'.
timelineNewAudioVideo ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m Timeline
    -- ^ __Returns:__ The new timeline, or 'P.Nothing' if the tracks
    -- could not be created and added.
timelineNewAudioVideo :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m Timeline
timelineNewAudioVideo  = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
    Ptr Timeline
result <- IO (Ptr Timeline)
ges_timeline_new_audio_video
    forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"timelineNewAudioVideo" Ptr Timeline
result
    Timeline
result' <- (forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Timeline -> Timeline
Timeline) Ptr Timeline
result
    forall (m :: * -> *) a. Monad m => a -> m a
return Timeline
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Timeline::new_from_uri
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "uri"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The URI to load from"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GES" , name = "Timeline" })
-- throws : True
-- Skip return : False

foreign import ccall "ges_timeline_new_from_uri" ges_timeline_new_from_uri :: 
    CString ->                              -- uri : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr Timeline)

-- | Creates a timeline from the given URI.
timelineNewFromUri ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    -- ^ /@uri@/: The URI to load from
    -> m (Maybe Timeline)
    -- ^ __Returns:__ A new timeline if the uri was loaded
    -- successfully, or 'P.Nothing' if the uri could not be loaded. /(Can throw 'Data.GI.Base.GError.GError')/
timelineNewFromUri :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Text -> m (Maybe Timeline)
timelineNewFromUri 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 Timeline
result <- forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError forall a b. (a -> b) -> a -> b
$ CString -> Ptr (Ptr GError) -> IO (Ptr Timeline)
ges_timeline_new_from_uri CString
uri'
        Maybe Timeline
maybeResult <- forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Timeline
result forall a b. (a -> b) -> a -> b
$ \Ptr Timeline
result' -> do
            Timeline
result'' <- (forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Timeline -> Timeline
Timeline) Ptr Timeline
result'
            forall (m :: * -> *) a. Monad m => a -> m a
return Timeline
result''
        forall a. Ptr a -> IO ()
freeMem CString
uri'
        forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Timeline
maybeResult
     ) (do
        forall a. Ptr a -> IO ()
freeMem CString
uri'
     )

#if defined(ENABLE_OVERLOADING)
#endif

-- method Timeline::add_layer
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "timeline"
--           , argType =
--               TInterface Name { namespace = "GES" , name = "Timeline" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The #GESTimeline" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "layer"
--           , argType = TInterface Name { namespace = "GES" , name = "Layer" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The layer to add" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "ges_timeline_add_layer" ges_timeline_add_layer :: 
    Ptr Timeline ->                         -- timeline : TInterface (Name {namespace = "GES", name = "Timeline"})
    Ptr GES.Layer.Layer ->                  -- layer : TInterface (Name {namespace = "GES", name = "Layer"})
    IO CInt

{-# DEPRECATED timelineAddLayer ["(Since version 1.18)","This method requires you to ensure the layer\\'s","[Layer:priority](\"GI.GES.Objects.Layer#g:attr:priority\") will be unique to the timeline. Use","'GI.GES.Objects.Timeline.timelineAppendLayer' and 'GI.GES.Objects.Timeline.timelineMoveLayer' instead."] #-}
-- | Add a layer to the timeline.
-- 
-- If the layer contains t'GI.GES.Objects.Clip.Clip'-s, then this may trigger the creation of
-- their core track element children for the timeline\'s tracks, and the
-- placement of the clip\'s children in the tracks of the timeline using
-- [Timeline::selectTracksForObject]("GI.GES.Objects.Timeline#g:signal:selectTracksForObject"). Some errors may occur if this
-- would break one of the configuration rules of the timeline in one of
-- its tracks. In such cases, some track elements would fail to be added
-- to their tracks, but this method would still return 'P.True'. As such, it
-- is advised that you only add clips to layers that already part of a
-- timeline. In such situations, 'GI.GES.Objects.Layer.layerAddClip' is able to fail if
-- adding the clip would cause such an error.
timelineAddLayer ::
    (B.CallStack.HasCallStack, MonadIO m, IsTimeline a, GES.Layer.IsLayer b) =>
    a
    -- ^ /@timeline@/: The t'GI.GES.Objects.Timeline.Timeline'
    -> b
    -- ^ /@layer@/: The layer to add
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@layer@/ was properly added.
timelineAddLayer :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsTimeline a, IsLayer b) =>
a -> b -> m Bool
timelineAddLayer a
timeline b
layer = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
    Ptr Timeline
timeline' <- forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
timeline
    Ptr Layer
layer' <- forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
layer
    CInt
result <- Ptr Timeline -> Ptr Layer -> IO CInt
ges_timeline_add_layer Ptr Timeline
timeline' Ptr Layer
layer'
    let result' :: Bool
result' = (forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
timeline
    forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
layer
    forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TimelineAddLayerMethodInfo
instance (signature ~ (b -> m Bool), MonadIO m, IsTimeline a, GES.Layer.IsLayer b) => O.OverloadedMethod TimelineAddLayerMethodInfo a signature where
    overloadedMethod = timelineAddLayer

instance O.OverloadedMethodInfo TimelineAddLayerMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GES.Objects.Timeline.timelineAddLayer",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.1/docs/GI-GES-Objects-Timeline.html#v:timelineAddLayer"
        })


#endif

-- method Timeline::add_track
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "timeline"
--           , argType =
--               TInterface Name { namespace = "GES" , name = "Timeline" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The #GESTimeline" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "track"
--           , argType = TInterface Name { namespace = "GES" , name = "Track" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The track to add" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "ges_timeline_add_track" ges_timeline_add_track :: 
    Ptr Timeline ->                         -- timeline : TInterface (Name {namespace = "GES", name = "Timeline"})
    Ptr GES.Track.Track ->                  -- track : TInterface (Name {namespace = "GES", name = "Track"})
    IO CInt

-- | Add a track to the timeline.
-- 
-- If the timeline already contains clips, then this may trigger the
-- creation of their core track element children for the track, and the
-- placement of the clip\'s children in the track of the timeline using
-- [Timeline::selectTracksForObject]("GI.GES.Objects.Timeline#g:signal:selectTracksForObject"). Some errors may occur if this
-- would break one of the configuration rules for the timeline in the
-- track. In such cases, some track elements would fail to be added to the
-- track, but this method would still return 'P.True'. As such, it is advised
-- that you avoid adding tracks to timelines that already contain clips.
timelineAddTrack ::
    (B.CallStack.HasCallStack, MonadIO m, IsTimeline a, GES.Track.IsTrack b) =>
    a
    -- ^ /@timeline@/: The t'GI.GES.Objects.Timeline.Timeline'
    -> b
    -- ^ /@track@/: The track to add
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@track@/ was properly added.
timelineAddTrack :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsTimeline a, IsTrack b) =>
a -> b -> m Bool
timelineAddTrack a
timeline b
track = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
    Ptr Timeline
timeline' <- forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
timeline
    Ptr Track
track' <- forall a b. (HasCallStack, GObject a) => a -> IO (Ptr b)
B.ManagedPtr.disownObject b
track
    CInt
result <- Ptr Timeline -> Ptr Track -> IO CInt
ges_timeline_add_track Ptr Timeline
timeline' Ptr Track
track'
    let result' :: Bool
result' = (forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
timeline
    forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
track
    forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TimelineAddTrackMethodInfo
instance (signature ~ (b -> m Bool), MonadIO m, IsTimeline a, GES.Track.IsTrack b) => O.OverloadedMethod TimelineAddTrackMethodInfo a signature where
    overloadedMethod = timelineAddTrack

instance O.OverloadedMethodInfo TimelineAddTrackMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GES.Objects.Timeline.timelineAddTrack",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.1/docs/GI-GES-Objects-Timeline.html#v:timelineAddTrack"
        })


#endif

-- method Timeline::append_layer
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "timeline"
--           , argType =
--               TInterface Name { namespace = "GES" , name = "Timeline" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The #GESTimeline" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GES" , name = "Layer" })
-- throws : False
-- Skip return : False

foreign import ccall "ges_timeline_append_layer" ges_timeline_append_layer :: 
    Ptr Timeline ->                         -- timeline : TInterface (Name {namespace = "GES", name = "Timeline"})
    IO (Ptr GES.Layer.Layer)

-- | Append a newly created layer to the timeline. The layer will
-- be added at the lowest [Layer:priority]("GI.GES.Objects.Layer#g:attr:priority") (numerically, the highest).
timelineAppendLayer ::
    (B.CallStack.HasCallStack, MonadIO m, IsTimeline a) =>
    a
    -- ^ /@timeline@/: The t'GI.GES.Objects.Timeline.Timeline'
    -> m GES.Layer.Layer
    -- ^ __Returns:__ The newly created layer.
timelineAppendLayer :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTimeline a) =>
a -> m Layer
timelineAppendLayer a
timeline = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
    Ptr Timeline
timeline' <- forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
timeline
    Ptr Layer
result <- Ptr Timeline -> IO (Ptr Layer)
ges_timeline_append_layer Ptr Timeline
timeline'
    forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"timelineAppendLayer" Ptr Layer
result
    Layer
result' <- (forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Layer -> Layer
GES.Layer.Layer) Ptr Layer
result
    forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
timeline
    forall (m :: * -> *) a. Monad m => a -> m a
return Layer
result'

#if defined(ENABLE_OVERLOADING)
data TimelineAppendLayerMethodInfo
instance (signature ~ (m GES.Layer.Layer), MonadIO m, IsTimeline a) => O.OverloadedMethod TimelineAppendLayerMethodInfo a signature where
    overloadedMethod = timelineAppendLayer

instance O.OverloadedMethodInfo TimelineAppendLayerMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GES.Objects.Timeline.timelineAppendLayer",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.1/docs/GI-GES-Objects-Timeline.html#v:timelineAppendLayer"
        })


#endif

-- method Timeline::commit
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "timeline"
--           , argType =
--               TInterface Name { namespace = "GES" , name = "Timeline" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GESTimeline" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "ges_timeline_commit" ges_timeline_commit :: 
    Ptr Timeline ->                         -- timeline : TInterface (Name {namespace = "GES", name = "Timeline"})
    IO CInt

-- | Commit all the pending changes of the clips contained in the
-- timeline.
-- 
-- When changes happen in a timeline, they are not immediately executed
-- internally, in a way that effects the output data of the timeline. You
-- should call this method when you are done with a set of changes and you
-- want them to be executed.
-- 
-- Any pending changes will be executed in the backend. The
-- [Timeline::commited]("GI.GES.Objects.Timeline#g:signal:commited") signal will be emitted once this has completed.
-- You should not try to change the state of the timeline, seek it or add
-- tracks to it before receiving this signal. You can use
-- 'GI.GES.Objects.Timeline.timelineCommitSync' if you do not want to perform other tasks in
-- the mean time.
-- 
-- Note that all the pending changes will automatically be executed when
-- the timeline goes from @/GST_STATE_READY/@ to @/GST_STATE_PAUSED/@, which is
-- usually triggered by a corresponding state changes in a containing
-- t'GI.GES.Objects.Pipeline.Pipeline'.
timelineCommit ::
    (B.CallStack.HasCallStack, MonadIO m, IsTimeline a) =>
    a
    -- ^ /@timeline@/: A t'GI.GES.Objects.Timeline.Timeline'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if pending changes were committed, or 'P.False' if nothing
    -- needed to be committed.
timelineCommit :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTimeline a) =>
a -> m Bool
timelineCommit a
timeline = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
    Ptr Timeline
timeline' <- forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
timeline
    CInt
result <- Ptr Timeline -> IO CInt
ges_timeline_commit Ptr Timeline
timeline'
    let result' :: Bool
result' = (forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
timeline
    forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TimelineCommitMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsTimeline a) => O.OverloadedMethod TimelineCommitMethodInfo a signature where
    overloadedMethod = timelineCommit

instance O.OverloadedMethodInfo TimelineCommitMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GES.Objects.Timeline.timelineCommit",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.1/docs/GI-GES-Objects-Timeline.html#v:timelineCommit"
        })


#endif

-- method Timeline::commit_sync
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "timeline"
--           , argType =
--               TInterface Name { namespace = "GES" , name = "Timeline" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GESTimeline" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "ges_timeline_commit_sync" ges_timeline_commit_sync :: 
    Ptr Timeline ->                         -- timeline : TInterface (Name {namespace = "GES", name = "Timeline"})
    IO CInt

-- | Commit all the pending changes of the clips contained in the
-- timeline and wait for the changes to complete.
-- 
-- See 'GI.GES.Objects.Timeline.timelineCommit'.
timelineCommitSync ::
    (B.CallStack.HasCallStack, MonadIO m, IsTimeline a) =>
    a
    -- ^ /@timeline@/: A t'GI.GES.Objects.Timeline.Timeline'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if pending changes were committed, or 'P.False' if nothing
    -- needed to be committed.
timelineCommitSync :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTimeline a) =>
a -> m Bool
timelineCommitSync a
timeline = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
    Ptr Timeline
timeline' <- forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
timeline
    CInt
result <- Ptr Timeline -> IO CInt
ges_timeline_commit_sync Ptr Timeline
timeline'
    let result' :: Bool
result' = (forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
timeline
    forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TimelineCommitSyncMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsTimeline a) => O.OverloadedMethod TimelineCommitSyncMethodInfo a signature where
    overloadedMethod = timelineCommitSync

instance O.OverloadedMethodInfo TimelineCommitSyncMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GES.Objects.Timeline.timelineCommitSync",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.1/docs/GI-GES-Objects-Timeline.html#v:timelineCommitSync"
        })


#endif

-- method Timeline::freeze_commit
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "timeline"
--           , argType =
--               TInterface Name { namespace = "GES" , name = "Timeline" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The #GESTimeline" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "ges_timeline_freeze_commit" ges_timeline_freeze_commit :: 
    Ptr Timeline ->                         -- timeline : TInterface (Name {namespace = "GES", name = "Timeline"})
    IO ()

-- | Freezes the timeline from being committed. This is usually needed while the
-- timeline is being rendered to ensure that not change to the timeline are
-- taken into account during that moment. Once the rendering is done, you
-- should call @/ges_timeline_thaw_commit/@ so that comiting becomes possible
-- again and any call to @commit()@ that happened during the rendering is
-- actually taken into account.
-- 
-- /Since: 1.20/
timelineFreezeCommit ::
    (B.CallStack.HasCallStack, MonadIO m, IsTimeline a) =>
    a
    -- ^ /@timeline@/: The t'GI.GES.Objects.Timeline.Timeline'
    -> m ()
timelineFreezeCommit :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTimeline a) =>
a -> m ()
timelineFreezeCommit a
timeline = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
    Ptr Timeline
timeline' <- forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
timeline
    Ptr Timeline -> IO ()
ges_timeline_freeze_commit Ptr Timeline
timeline'
    forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
timeline
    forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data TimelineFreezeCommitMethodInfo
instance (signature ~ (m ()), MonadIO m, IsTimeline a) => O.OverloadedMethod TimelineFreezeCommitMethodInfo a signature where
    overloadedMethod = timelineFreezeCommit

instance O.OverloadedMethodInfo TimelineFreezeCommitMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GES.Objects.Timeline.timelineFreezeCommit",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.1/docs/GI-GES-Objects-Timeline.html#v:timelineFreezeCommit"
        })


#endif

-- method Timeline::get_auto_transition
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "timeline"
--           , argType =
--               TInterface Name { namespace = "GES" , name = "Timeline" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The #GESTimeline" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "ges_timeline_get_auto_transition" ges_timeline_get_auto_transition :: 
    Ptr Timeline ->                         -- timeline : TInterface (Name {namespace = "GES", name = "Timeline"})
    IO CInt

-- | Gets [Timeline:autoTransition]("GI.GES.Objects.Timeline#g:attr:autoTransition") for the timeline.
timelineGetAutoTransition ::
    (B.CallStack.HasCallStack, MonadIO m, IsTimeline a) =>
    a
    -- ^ /@timeline@/: The t'GI.GES.Objects.Timeline.Timeline'
    -> m Bool
    -- ^ __Returns:__ The auto-transition of /@self@/.
timelineGetAutoTransition :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTimeline a) =>
a -> m Bool
timelineGetAutoTransition a
timeline = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
    Ptr Timeline
timeline' <- forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
timeline
    CInt
result <- Ptr Timeline -> IO CInt
ges_timeline_get_auto_transition Ptr Timeline
timeline'
    let result' :: Bool
result' = (forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
timeline
    forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TimelineGetAutoTransitionMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsTimeline a) => O.OverloadedMethod TimelineGetAutoTransitionMethodInfo a signature where
    overloadedMethod = timelineGetAutoTransition

instance O.OverloadedMethodInfo TimelineGetAutoTransitionMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GES.Objects.Timeline.timelineGetAutoTransition",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.1/docs/GI-GES-Objects-Timeline.html#v:timelineGetAutoTransition"
        })


#endif

-- method Timeline::get_duration
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "timeline"
--           , argType =
--               TInterface Name { namespace = "GES" , name = "Timeline" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The #GESTimeline" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt64)
-- throws : False
-- Skip return : False

foreign import ccall "ges_timeline_get_duration" ges_timeline_get_duration :: 
    Ptr Timeline ->                         -- timeline : TInterface (Name {namespace = "GES", name = "Timeline"})
    IO Word64

-- | Get the current [Timeline:duration]("GI.GES.Objects.Timeline#g:attr:duration") of the timeline
timelineGetDuration ::
    (B.CallStack.HasCallStack, MonadIO m, IsTimeline a) =>
    a
    -- ^ /@timeline@/: The t'GI.GES.Objects.Timeline.Timeline'
    -> m Word64
    -- ^ __Returns:__ The current duration of /@timeline@/.
timelineGetDuration :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTimeline a) =>
a -> m Word64
timelineGetDuration a
timeline = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
    Ptr Timeline
timeline' <- forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
timeline
    Word64
result <- Ptr Timeline -> IO Word64
ges_timeline_get_duration Ptr Timeline
timeline'
    forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
timeline
    forall (m :: * -> *) a. Monad m => a -> m a
return Word64
result

#if defined(ENABLE_OVERLOADING)
data TimelineGetDurationMethodInfo
instance (signature ~ (m Word64), MonadIO m, IsTimeline a) => O.OverloadedMethod TimelineGetDurationMethodInfo a signature where
    overloadedMethod = timelineGetDuration

instance O.OverloadedMethodInfo TimelineGetDurationMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GES.Objects.Timeline.timelineGetDuration",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.1/docs/GI-GES-Objects-Timeline.html#v:timelineGetDuration"
        })


#endif

-- method Timeline::get_element
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "timeline"
--           , argType =
--               TInterface Name { namespace = "GES" , name = "Timeline" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The #GESTimeline" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The name of the element to find"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "GES" , name = "TimelineElement" })
-- throws : False
-- Skip return : False

foreign import ccall "ges_timeline_get_element" ges_timeline_get_element :: 
    Ptr Timeline ->                         -- timeline : TInterface (Name {namespace = "GES", name = "Timeline"})
    CString ->                              -- name : TBasicType TUTF8
    IO (Ptr GES.TimelineElement.TimelineElement)

-- | Gets the element contained in the timeline with the given name.
timelineGetElement ::
    (B.CallStack.HasCallStack, MonadIO m, IsTimeline a) =>
    a
    -- ^ /@timeline@/: The t'GI.GES.Objects.Timeline.Timeline'
    -> T.Text
    -- ^ /@name@/: The name of the element to find
    -> m (Maybe GES.TimelineElement.TimelineElement)
    -- ^ __Returns:__ The timeline element in /@timeline@/
    -- with the given /@name@/, or 'P.Nothing' if it was not found.
timelineGetElement :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTimeline a) =>
a -> Text -> m (Maybe TimelineElement)
timelineGetElement a
timeline Text
name = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
    Ptr Timeline
timeline' <- forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
timeline
    CString
name' <- Text -> IO CString
textToCString Text
name
    Ptr TimelineElement
result <- Ptr Timeline -> CString -> IO (Ptr TimelineElement)
ges_timeline_get_element Ptr Timeline
timeline' CString
name'
    Maybe TimelineElement
maybeResult <- forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr TimelineElement
result forall a b. (a -> b) -> a -> b
$ \Ptr TimelineElement
result' -> do
        TimelineElement
result'' <- (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'
        forall (m :: * -> *) a. Monad m => a -> m a
return TimelineElement
result''
    forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
timeline
    forall a. Ptr a -> IO ()
freeMem CString
name'
    forall (m :: * -> *) a. Monad m => a -> m a
return Maybe TimelineElement
maybeResult

#if defined(ENABLE_OVERLOADING)
data TimelineGetElementMethodInfo
instance (signature ~ (T.Text -> m (Maybe GES.TimelineElement.TimelineElement)), MonadIO m, IsTimeline a) => O.OverloadedMethod TimelineGetElementMethodInfo a signature where
    overloadedMethod = timelineGetElement

instance O.OverloadedMethodInfo TimelineGetElementMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GES.Objects.Timeline.timelineGetElement",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.1/docs/GI-GES-Objects-Timeline.html#v:timelineGetElement"
        })


#endif

-- method Timeline::get_frame_at
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "GES" , name = "Timeline" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GESTimeline" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "timestamp"
--           , argType = TBasicType TUInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "The timestamp to get the corresponding frame number of"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt64)
-- throws : False
-- Skip return : False

foreign import ccall "ges_timeline_get_frame_at" ges_timeline_get_frame_at :: 
    Ptr Timeline ->                         -- self : TInterface (Name {namespace = "GES", name = "Timeline"})
    Word64 ->                               -- timestamp : TBasicType TUInt64
    IO Int64

-- | This method allows you to convert a timeline @/GstClockTime/@ into its
-- corresponding @/GESFrameNumber/@ in the timeline\'s output.
-- 
-- /Since: 1.18/
timelineGetFrameAt ::
    (B.CallStack.HasCallStack, MonadIO m, IsTimeline a) =>
    a
    -- ^ /@self@/: A t'GI.GES.Objects.Timeline.Timeline'
    -> Word64
    -- ^ /@timestamp@/: The timestamp to get the corresponding frame number of
    -> m Int64
    -- ^ __Returns:__ The frame number /@timestamp@/ corresponds to.
timelineGetFrameAt :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTimeline a) =>
a -> Word64 -> m Int64
timelineGetFrameAt a
self Word64
timestamp = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
    Ptr Timeline
self' <- forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Int64
result <- Ptr Timeline -> Word64 -> IO Int64
ges_timeline_get_frame_at Ptr Timeline
self' Word64
timestamp
    forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    forall (m :: * -> *) a. Monad m => a -> m a
return Int64
result

#if defined(ENABLE_OVERLOADING)
data TimelineGetFrameAtMethodInfo
instance (signature ~ (Word64 -> m Int64), MonadIO m, IsTimeline a) => O.OverloadedMethod TimelineGetFrameAtMethodInfo a signature where
    overloadedMethod = timelineGetFrameAt

instance O.OverloadedMethodInfo TimelineGetFrameAtMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GES.Objects.Timeline.timelineGetFrameAt",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.1/docs/GI-GES-Objects-Timeline.html#v:timelineGetFrameAt"
        })


#endif

-- method Timeline::get_frame_time
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "GES" , name = "Timeline" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "The self on which to retrieve the timestamp for @frame_number"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "frame_number"
--           , argType = TBasicType TInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "The frame number to get the corresponding timestamp of in the\n               timeline coordinates"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt64)
-- throws : False
-- Skip return : False

foreign import ccall "ges_timeline_get_frame_time" ges_timeline_get_frame_time :: 
    Ptr Timeline ->                         -- self : TInterface (Name {namespace = "GES", name = "Timeline"})
    Int64 ->                                -- frame_number : TBasicType TInt64
    IO Word64

-- | This method allows you to convert a timeline output frame number into a
-- timeline @/GstClockTime/@. For example, this time could be used to seek to a
-- particular frame in the timeline\'s output, or as the edit position for
-- an element within the timeline.
-- 
-- /Since: 1.18/
timelineGetFrameTime ::
    (B.CallStack.HasCallStack, MonadIO m, IsTimeline a) =>
    a
    -- ^ /@self@/: The self on which to retrieve the timestamp for /@frameNumber@/
    -> Int64
    -- ^ /@frameNumber@/: The frame number to get the corresponding timestamp of in the
    --                timeline coordinates
    -> m Word64
    -- ^ __Returns:__ The timestamp corresponding to /@frameNumber@/ in the output of /@self@/.
timelineGetFrameTime :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTimeline a) =>
a -> Int64 -> m Word64
timelineGetFrameTime a
self Int64
frameNumber = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
    Ptr Timeline
self' <- forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Word64
result <- Ptr Timeline -> Int64 -> IO Word64
ges_timeline_get_frame_time Ptr Timeline
self' Int64
frameNumber
    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 TimelineGetFrameTimeMethodInfo
instance (signature ~ (Int64 -> m Word64), MonadIO m, IsTimeline a) => O.OverloadedMethod TimelineGetFrameTimeMethodInfo a signature where
    overloadedMethod = timelineGetFrameTime

instance O.OverloadedMethodInfo TimelineGetFrameTimeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GES.Objects.Timeline.timelineGetFrameTime",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.1/docs/GI-GES-Objects-Timeline.html#v:timelineGetFrameTime"
        })


#endif

-- method Timeline::get_groups
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "timeline"
--           , argType =
--               TInterface Name { namespace = "GES" , name = "Timeline" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The #GESTimeline" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TGList (TInterface Name { namespace = "GES" , name = "Group" }))
-- throws : False
-- Skip return : False

foreign import ccall "ges_timeline_get_groups" ges_timeline_get_groups :: 
    Ptr Timeline ->                         -- timeline : TInterface (Name {namespace = "GES", name = "Timeline"})
    IO (Ptr (GList (Ptr GES.Group.Group)))

-- | Get the list of t'GI.GES.Objects.Group.Group'-s present in the timeline.
timelineGetGroups ::
    (B.CallStack.HasCallStack, MonadIO m, IsTimeline a) =>
    a
    -- ^ /@timeline@/: The t'GI.GES.Objects.Timeline.Timeline'
    -> m [GES.Group.Group]
    -- ^ __Returns:__ The list of
    -- groups that contain clips present in /@timeline@/\'s layers.
    -- Must not be changed.
timelineGetGroups :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTimeline a) =>
a -> m [Group]
timelineGetGroups a
timeline = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
    Ptr Timeline
timeline' <- forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
timeline
    Ptr (GList (Ptr Group))
result <- Ptr Timeline -> IO (Ptr (GList (Ptr Group)))
ges_timeline_get_groups Ptr Timeline
timeline'
    [Ptr Group]
result' <- forall a. Ptr (GList (Ptr a)) -> IO [Ptr a]
unpackGList Ptr (GList (Ptr Group))
result
    [Group]
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 Group -> Group
GES.Group.Group) [Ptr Group]
result'
    forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
timeline
    forall (m :: * -> *) a. Monad m => a -> m a
return [Group]
result''

#if defined(ENABLE_OVERLOADING)
data TimelineGetGroupsMethodInfo
instance (signature ~ (m [GES.Group.Group]), MonadIO m, IsTimeline a) => O.OverloadedMethod TimelineGetGroupsMethodInfo a signature where
    overloadedMethod = timelineGetGroups

instance O.OverloadedMethodInfo TimelineGetGroupsMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GES.Objects.Timeline.timelineGetGroups",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.1/docs/GI-GES-Objects-Timeline.html#v:timelineGetGroups"
        })


#endif

-- method Timeline::get_layer
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "timeline"
--           , argType =
--               TInterface Name { namespace = "GES" , name = "Timeline" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The #GESTimeline to retrieve a layer from"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "priority"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The priority/index of the layer to find"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GES" , name = "Layer" })
-- throws : False
-- Skip return : False

foreign import ccall "ges_timeline_get_layer" ges_timeline_get_layer :: 
    Ptr Timeline ->                         -- timeline : TInterface (Name {namespace = "GES", name = "Timeline"})
    Word32 ->                               -- priority : TBasicType TUInt
    IO (Ptr GES.Layer.Layer)

-- | Retrieve the layer whose index in the timeline matches the given
-- priority.
timelineGetLayer ::
    (B.CallStack.HasCallStack, MonadIO m, IsTimeline a) =>
    a
    -- ^ /@timeline@/: The t'GI.GES.Objects.Timeline.Timeline' to retrieve a layer from
    -> Word32
    -- ^ /@priority@/: The priority\/index of the layer to find
    -> m (Maybe GES.Layer.Layer)
    -- ^ __Returns:__ The layer with the given
    -- /@priority@/, or 'P.Nothing' if none was found.
    -- 
    -- Since 1.6
timelineGetLayer :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTimeline a) =>
a -> Word32 -> m (Maybe Layer)
timelineGetLayer a
timeline Word32
priority = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
    Ptr Timeline
timeline' <- forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
timeline
    Ptr Layer
result <- Ptr Timeline -> Word32 -> IO (Ptr Layer)
ges_timeline_get_layer Ptr Timeline
timeline' Word32
priority
    Maybe Layer
maybeResult <- forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Layer
result forall a b. (a -> b) -> a -> b
$ \Ptr Layer
result' -> do
        Layer
result'' <- (forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Layer -> Layer
GES.Layer.Layer) Ptr Layer
result'
        forall (m :: * -> *) a. Monad m => a -> m a
return Layer
result''
    forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
timeline
    forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Layer
maybeResult

#if defined(ENABLE_OVERLOADING)
data TimelineGetLayerMethodInfo
instance (signature ~ (Word32 -> m (Maybe GES.Layer.Layer)), MonadIO m, IsTimeline a) => O.OverloadedMethod TimelineGetLayerMethodInfo a signature where
    overloadedMethod = timelineGetLayer

instance O.OverloadedMethodInfo TimelineGetLayerMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GES.Objects.Timeline.timelineGetLayer",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.1/docs/GI-GES-Objects-Timeline.html#v:timelineGetLayer"
        })


#endif

-- method Timeline::get_layers
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "timeline"
--           , argType =
--               TInterface Name { namespace = "GES" , name = "Timeline" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The #GESTimeline" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TGList (TInterface Name { namespace = "GES" , name = "Layer" }))
-- throws : False
-- Skip return : False

foreign import ccall "ges_timeline_get_layers" ges_timeline_get_layers :: 
    Ptr Timeline ->                         -- timeline : TInterface (Name {namespace = "GES", name = "Timeline"})
    IO (Ptr (GList (Ptr GES.Layer.Layer)))

-- | Get the list of t'GI.GES.Objects.Layer.Layer'-s present in the timeline.
timelineGetLayers ::
    (B.CallStack.HasCallStack, MonadIO m, IsTimeline a) =>
    a
    -- ^ /@timeline@/: The t'GI.GES.Objects.Timeline.Timeline'
    -> m [GES.Layer.Layer]
    -- ^ __Returns:__ The list of
    -- layers present in /@timeline@/ sorted by priority.
timelineGetLayers :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTimeline a) =>
a -> m [Layer]
timelineGetLayers a
timeline = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
    Ptr Timeline
timeline' <- forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
timeline
    Ptr (GList (Ptr Layer))
result <- Ptr Timeline -> IO (Ptr (GList (Ptr Layer)))
ges_timeline_get_layers Ptr Timeline
timeline'
    [Ptr Layer]
result' <- forall a. Ptr (GList (Ptr a)) -> IO [Ptr a]
unpackGList Ptr (GList (Ptr Layer))
result
    [Layer]
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
wrapObject ManagedPtr Layer -> Layer
GES.Layer.Layer) [Ptr Layer]
result'
    forall a. Ptr (GList a) -> IO ()
g_list_free Ptr (GList (Ptr Layer))
result
    forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
timeline
    forall (m :: * -> *) a. Monad m => a -> m a
return [Layer]
result''

#if defined(ENABLE_OVERLOADING)
data TimelineGetLayersMethodInfo
instance (signature ~ (m [GES.Layer.Layer]), MonadIO m, IsTimeline a) => O.OverloadedMethod TimelineGetLayersMethodInfo a signature where
    overloadedMethod = timelineGetLayers

instance O.OverloadedMethodInfo TimelineGetLayersMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GES.Objects.Timeline.timelineGetLayers",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.1/docs/GI-GES-Objects-Timeline.html#v:timelineGetLayers"
        })


#endif

-- method Timeline::get_pad_for_track
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "timeline"
--           , argType =
--               TInterface Name { namespace = "GES" , name = "Timeline" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The #GESTimeline" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "track"
--           , argType = TInterface Name { namespace = "GES" , name = "Track" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A track" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gst" , name = "Pad" })
-- throws : False
-- Skip return : False

foreign import ccall "ges_timeline_get_pad_for_track" ges_timeline_get_pad_for_track :: 
    Ptr Timeline ->                         -- timeline : TInterface (Name {namespace = "GES", name = "Timeline"})
    Ptr GES.Track.Track ->                  -- track : TInterface (Name {namespace = "GES", name = "Track"})
    IO (Ptr Gst.Pad.Pad)

-- | Search for the t'GI.Gst.Objects.Pad.Pad' corresponding to the given timeline\'s track.
-- You can link to this pad to receive the output data of the given track.
timelineGetPadForTrack ::
    (B.CallStack.HasCallStack, MonadIO m, IsTimeline a, GES.Track.IsTrack b) =>
    a
    -- ^ /@timeline@/: The t'GI.GES.Objects.Timeline.Timeline'
    -> b
    -- ^ /@track@/: A track
    -> m (Maybe Gst.Pad.Pad)
    -- ^ __Returns:__ The pad corresponding to /@track@/,
    -- or 'P.Nothing' if there is an error.
timelineGetPadForTrack :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsTimeline a, IsTrack b) =>
a -> b -> m (Maybe Pad)
timelineGetPadForTrack a
timeline b
track = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
    Ptr Timeline
timeline' <- forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
timeline
    Ptr Track
track' <- forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
track
    Ptr Pad
result <- Ptr Timeline -> Ptr Track -> IO (Ptr Pad)
ges_timeline_get_pad_for_track Ptr Timeline
timeline' Ptr Track
track'
    Maybe Pad
maybeResult <- forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Pad
result forall a b. (a -> b) -> a -> b
$ \Ptr Pad
result' -> do
        Pad
result'' <- (forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Pad -> Pad
Gst.Pad.Pad) Ptr Pad
result'
        forall (m :: * -> *) a. Monad m => a -> m a
return Pad
result''
    forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
timeline
    forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
track
    forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Pad
maybeResult

#if defined(ENABLE_OVERLOADING)
data TimelineGetPadForTrackMethodInfo
instance (signature ~ (b -> m (Maybe Gst.Pad.Pad)), MonadIO m, IsTimeline a, GES.Track.IsTrack b) => O.OverloadedMethod TimelineGetPadForTrackMethodInfo a signature where
    overloadedMethod = timelineGetPadForTrack

instance O.OverloadedMethodInfo TimelineGetPadForTrackMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GES.Objects.Timeline.timelineGetPadForTrack",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.1/docs/GI-GES-Objects-Timeline.html#v:timelineGetPadForTrack"
        })


#endif

-- method Timeline::get_snapping_distance
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "timeline"
--           , argType =
--               TInterface Name { namespace = "GES" , name = "Timeline" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The #GESTimeline" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt64)
-- throws : False
-- Skip return : False

foreign import ccall "ges_timeline_get_snapping_distance" ges_timeline_get_snapping_distance :: 
    Ptr Timeline ->                         -- timeline : TInterface (Name {namespace = "GES", name = "Timeline"})
    IO Word64

-- | Gets the [Timeline:snappingDistance]("GI.GES.Objects.Timeline#g:attr:snappingDistance") for the timeline.
timelineGetSnappingDistance ::
    (B.CallStack.HasCallStack, MonadIO m, IsTimeline a) =>
    a
    -- ^ /@timeline@/: The t'GI.GES.Objects.Timeline.Timeline'
    -> m Word64
    -- ^ __Returns:__ The snapping distance (in nanoseconds) of /@timeline@/.
timelineGetSnappingDistance :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTimeline a) =>
a -> m Word64
timelineGetSnappingDistance a
timeline = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
    Ptr Timeline
timeline' <- forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
timeline
    Word64
result <- Ptr Timeline -> IO Word64
ges_timeline_get_snapping_distance Ptr Timeline
timeline'
    forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
timeline
    forall (m :: * -> *) a. Monad m => a -> m a
return Word64
result

#if defined(ENABLE_OVERLOADING)
data TimelineGetSnappingDistanceMethodInfo
instance (signature ~ (m Word64), MonadIO m, IsTimeline a) => O.OverloadedMethod TimelineGetSnappingDistanceMethodInfo a signature where
    overloadedMethod = timelineGetSnappingDistance

instance O.OverloadedMethodInfo TimelineGetSnappingDistanceMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GES.Objects.Timeline.timelineGetSnappingDistance",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.1/docs/GI-GES-Objects-Timeline.html#v:timelineGetSnappingDistance"
        })


#endif

-- method Timeline::get_track_for_pad
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "timeline"
--           , argType =
--               TInterface Name { namespace = "GES" , name = "Timeline" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The #GESTimeline" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "pad"
--           , argType = TInterface Name { namespace = "Gst" , name = "Pad" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A pad" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GES" , name = "Track" })
-- throws : False
-- Skip return : False

foreign import ccall "ges_timeline_get_track_for_pad" ges_timeline_get_track_for_pad :: 
    Ptr Timeline ->                         -- timeline : TInterface (Name {namespace = "GES", name = "Timeline"})
    Ptr Gst.Pad.Pad ->                      -- pad : TInterface (Name {namespace = "Gst", name = "Pad"})
    IO (Ptr GES.Track.Track)

-- | Search for the t'GI.GES.Objects.Track.Track' corresponding to the given timeline\'s pad.
timelineGetTrackForPad ::
    (B.CallStack.HasCallStack, MonadIO m, IsTimeline a, Gst.Pad.IsPad b) =>
    a
    -- ^ /@timeline@/: The t'GI.GES.Objects.Timeline.Timeline'
    -> b
    -- ^ /@pad@/: A pad
    -> m (Maybe GES.Track.Track)
    -- ^ __Returns:__ The track corresponding to /@pad@/,
    -- or 'P.Nothing' if there is an error.
timelineGetTrackForPad :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsTimeline a, IsPad b) =>
a -> b -> m (Maybe Track)
timelineGetTrackForPad a
timeline b
pad = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
    Ptr Timeline
timeline' <- forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
timeline
    Ptr Pad
pad' <- forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
pad
    Ptr Track
result <- Ptr Timeline -> Ptr Pad -> IO (Ptr Track)
ges_timeline_get_track_for_pad Ptr Timeline
timeline' Ptr Pad
pad'
    Maybe Track
maybeResult <- forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Track
result forall a b. (a -> b) -> a -> b
$ \Ptr Track
result' -> do
        Track
result'' <- (forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Track -> Track
GES.Track.Track) Ptr Track
result'
        forall (m :: * -> *) a. Monad m => a -> m a
return Track
result''
    forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
timeline
    forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
pad
    forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Track
maybeResult

#if defined(ENABLE_OVERLOADING)
data TimelineGetTrackForPadMethodInfo
instance (signature ~ (b -> m (Maybe GES.Track.Track)), MonadIO m, IsTimeline a, Gst.Pad.IsPad b) => O.OverloadedMethod TimelineGetTrackForPadMethodInfo a signature where
    overloadedMethod = timelineGetTrackForPad

instance O.OverloadedMethodInfo TimelineGetTrackForPadMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GES.Objects.Timeline.timelineGetTrackForPad",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.1/docs/GI-GES-Objects-Timeline.html#v:timelineGetTrackForPad"
        })


#endif

-- method Timeline::get_tracks
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "timeline"
--           , argType =
--               TInterface Name { namespace = "GES" , name = "Timeline" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The #GESTimeline" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TGList (TInterface Name { namespace = "GES" , name = "Track" }))
-- throws : False
-- Skip return : False

foreign import ccall "ges_timeline_get_tracks" ges_timeline_get_tracks :: 
    Ptr Timeline ->                         -- timeline : TInterface (Name {namespace = "GES", name = "Timeline"})
    IO (Ptr (GList (Ptr GES.Track.Track)))

-- | Get the list of t'GI.GES.Objects.Track.Track'-s used by the timeline.
timelineGetTracks ::
    (B.CallStack.HasCallStack, MonadIO m, IsTimeline a) =>
    a
    -- ^ /@timeline@/: The t'GI.GES.Objects.Timeline.Timeline'
    -> m [GES.Track.Track]
    -- ^ __Returns:__ The list of tracks
    -- used by /@timeline@/.
timelineGetTracks :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTimeline a) =>
a -> m [Track]
timelineGetTracks a
timeline = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
    Ptr Timeline
timeline' <- forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
timeline
    Ptr (GList (Ptr Track))
result <- Ptr Timeline -> IO (Ptr (GList (Ptr Track)))
ges_timeline_get_tracks Ptr Timeline
timeline'
    [Ptr Track]
result' <- forall a. Ptr (GList (Ptr a)) -> IO [Ptr a]
unpackGList Ptr (GList (Ptr Track))
result
    [Track]
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
wrapObject ManagedPtr Track -> Track
GES.Track.Track) [Ptr Track]
result'
    forall a. Ptr (GList a) -> IO ()
g_list_free Ptr (GList (Ptr Track))
result
    forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
timeline
    forall (m :: * -> *) a. Monad m => a -> m a
return [Track]
result''

#if defined(ENABLE_OVERLOADING)
data TimelineGetTracksMethodInfo
instance (signature ~ (m [GES.Track.Track]), MonadIO m, IsTimeline a) => O.OverloadedMethod TimelineGetTracksMethodInfo a signature where
    overloadedMethod = timelineGetTracks

instance O.OverloadedMethodInfo TimelineGetTracksMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GES.Objects.Timeline.timelineGetTracks",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.1/docs/GI-GES-Objects-Timeline.html#v:timelineGetTracks"
        })


#endif

-- method Timeline::is_empty
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "timeline"
--           , argType =
--               TInterface Name { namespace = "GES" , name = "Timeline" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The #GESTimeline" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "ges_timeline_is_empty" ges_timeline_is_empty :: 
    Ptr Timeline ->                         -- timeline : TInterface (Name {namespace = "GES", name = "Timeline"})
    IO CInt

-- | Check whether the timeline is empty or not.
timelineIsEmpty ::
    (B.CallStack.HasCallStack, MonadIO m, IsTimeline a) =>
    a
    -- ^ /@timeline@/: The t'GI.GES.Objects.Timeline.Timeline'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@timeline@/ is empty.
timelineIsEmpty :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTimeline a) =>
a -> m Bool
timelineIsEmpty a
timeline = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
    Ptr Timeline
timeline' <- forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
timeline
    CInt
result <- Ptr Timeline -> IO CInt
ges_timeline_is_empty Ptr Timeline
timeline'
    let result' :: Bool
result' = (forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
timeline
    forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TimelineIsEmptyMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsTimeline a) => O.OverloadedMethod TimelineIsEmptyMethodInfo a signature where
    overloadedMethod = timelineIsEmpty

instance O.OverloadedMethodInfo TimelineIsEmptyMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GES.Objects.Timeline.timelineIsEmpty",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.1/docs/GI-GES-Objects-Timeline.html#v:timelineIsEmpty"
        })


#endif

-- method Timeline::load_from_uri
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "timeline"
--           , argType =
--               TInterface Name { namespace = "GES" , name = "Timeline" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "An empty #GESTimeline into which to load the formatter"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "uri"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The URI to load from"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "ges_timeline_load_from_uri" ges_timeline_load_from_uri :: 
    Ptr Timeline ->                         -- timeline : TInterface (Name {namespace = "GES", name = "Timeline"})
    CString ->                              -- uri : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Loads the contents of URI into the timeline.
timelineLoadFromUri ::
    (B.CallStack.HasCallStack, MonadIO m, IsTimeline a) =>
    a
    -- ^ /@timeline@/: An empty t'GI.GES.Objects.Timeline.Timeline' into which to load the formatter
    -> T.Text
    -- ^ /@uri@/: The URI to load from
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
timelineLoadFromUri :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTimeline a) =>
a -> Text -> m ()
timelineLoadFromUri a
timeline Text
uri = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
    Ptr Timeline
timeline' <- forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
timeline
    CString
uri' <- Text -> IO CString
textToCString Text
uri
    forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError forall a b. (a -> b) -> a -> b
$ Ptr Timeline -> CString -> Ptr (Ptr GError) -> IO CInt
ges_timeline_load_from_uri Ptr Timeline
timeline' CString
uri'
        forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
timeline
        forall a. Ptr a -> IO ()
freeMem CString
uri'
        forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        forall a. Ptr a -> IO ()
freeMem CString
uri'
     )

#if defined(ENABLE_OVERLOADING)
data TimelineLoadFromUriMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsTimeline a) => O.OverloadedMethod TimelineLoadFromUriMethodInfo a signature where
    overloadedMethod = timelineLoadFromUri

instance O.OverloadedMethodInfo TimelineLoadFromUriMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GES.Objects.Timeline.timelineLoadFromUri",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.1/docs/GI-GES-Objects-Timeline.html#v:timelineLoadFromUri"
        })


#endif

-- method Timeline::move_layer
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "timeline"
--           , argType =
--               TInterface Name { namespace = "GES" , name = "Timeline" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GESTimeline" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "layer"
--           , argType = TInterface Name { namespace = "GES" , name = "Layer" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "A layer within @timeline, whose priority should be changed"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "new_layer_priority"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The new index for @layer"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "ges_timeline_move_layer" ges_timeline_move_layer :: 
    Ptr Timeline ->                         -- timeline : TInterface (Name {namespace = "GES", name = "Timeline"})
    Ptr GES.Layer.Layer ->                  -- layer : TInterface (Name {namespace = "GES", name = "Layer"})
    Word32 ->                               -- new_layer_priority : TBasicType TUInt
    IO CInt

-- | Moves a layer within the timeline to the index given by
-- /@newLayerPriority@/.
-- An index of 0 corresponds to the layer with the highest priority in a
-- timeline. If /@newLayerPriority@/ is greater than the number of layers
-- present in the timeline, it will become the lowest priority layer.
-- 
-- /Since: 1.16/
timelineMoveLayer ::
    (B.CallStack.HasCallStack, MonadIO m, IsTimeline a, GES.Layer.IsLayer b) =>
    a
    -- ^ /@timeline@/: A t'GI.GES.Objects.Timeline.Timeline'
    -> b
    -- ^ /@layer@/: A layer within /@timeline@/, whose priority should be changed
    -> Word32
    -- ^ /@newLayerPriority@/: The new index for /@layer@/
    -> m Bool
timelineMoveLayer :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsTimeline a, IsLayer b) =>
a -> b -> Word32 -> m Bool
timelineMoveLayer a
timeline b
layer Word32
newLayerPriority = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
    Ptr Timeline
timeline' <- forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
timeline
    Ptr Layer
layer' <- forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
layer
    CInt
result <- Ptr Timeline -> Ptr Layer -> Word32 -> IO CInt
ges_timeline_move_layer Ptr Timeline
timeline' Ptr Layer
layer' Word32
newLayerPriority
    let result' :: Bool
result' = (forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
timeline
    forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
layer
    forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TimelineMoveLayerMethodInfo
instance (signature ~ (b -> Word32 -> m Bool), MonadIO m, IsTimeline a, GES.Layer.IsLayer b) => O.OverloadedMethod TimelineMoveLayerMethodInfo a signature where
    overloadedMethod = timelineMoveLayer

instance O.OverloadedMethodInfo TimelineMoveLayerMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GES.Objects.Timeline.timelineMoveLayer",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.1/docs/GI-GES-Objects-Timeline.html#v:timelineMoveLayer"
        })


#endif

-- method Timeline::paste_element
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "timeline"
--           , argType =
--               TInterface Name { namespace = "GES" , name = "Timeline" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "The #GESTimeline onto which @element should be pasted"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "element"
--           , argType =
--               TInterface Name { namespace = "GES" , name = "TimelineElement" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The element to paste"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "position"
--           , argType = TBasicType TUInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "The position in the timeline @element should be pasted to,\ni.e. the #GESTimelineElement:start value for the pasted element."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "layer_priority"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "The layer into which the element should be pasted.\n-1 means paste to the same layer from which @element has been copied from"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "GES" , name = "TimelineElement" })
-- throws : False
-- Skip return : False

foreign import ccall "ges_timeline_paste_element" ges_timeline_paste_element :: 
    Ptr Timeline ->                         -- timeline : TInterface (Name {namespace = "GES", name = "Timeline"})
    Ptr GES.TimelineElement.TimelineElement -> -- element : TInterface (Name {namespace = "GES", name = "TimelineElement"})
    Word64 ->                               -- position : TBasicType TUInt64
    Int32 ->                                -- layer_priority : TBasicType TInt
    IO (Ptr GES.TimelineElement.TimelineElement)

-- | Paste an element inside the timeline. /@element@/ **must** be the return of
-- 'GI.GES.Objects.TimelineElement.timelineElementCopy' with @deep=TRUE@,
-- and it should not be changed before pasting. /@element@/ itself is not
-- placed in the timeline, instead a new element is created, alike to the
-- originally copied element. Note that the originally copied element must
-- also lie within /@timeline@/, at both the point of copying and pasting.
-- 
-- Pasting may fail if it would place the timeline in an unsupported
-- configuration.
-- 
-- After calling this function /@element@/ should not be used. In particular,
-- /@element@/ can **not** be pasted again. Instead, you can copy the
-- returned element and paste that copy (although, this is only possible
-- if the paste was successful).
-- 
-- See also 'GI.GES.Objects.TimelineElement.timelineElementPaste'.
timelinePasteElement ::
    (B.CallStack.HasCallStack, MonadIO m, IsTimeline a, GES.TimelineElement.IsTimelineElement b) =>
    a
    -- ^ /@timeline@/: The t'GI.GES.Objects.Timeline.Timeline' onto which /@element@/ should be pasted
    -> b
    -- ^ /@element@/: The element to paste
    -> Word64
    -- ^ /@position@/: The position in the timeline /@element@/ should be pasted to,
    -- i.e. the [TimelineElement:start]("GI.GES.Objects.TimelineElement#g:attr:start") value for the pasted element.
    -> Int32
    -- ^ /@layerPriority@/: The layer into which the element should be pasted.
    -- -1 means paste to the same layer from which /@element@/ has been copied from
    -> m (Maybe GES.TimelineElement.TimelineElement)
    -- ^ __Returns:__ The newly created element, or
    -- 'P.Nothing' if pasting fails.
timelinePasteElement :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsTimeline a, IsTimelineElement b) =>
a -> b -> Word64 -> Int32 -> m (Maybe TimelineElement)
timelinePasteElement a
timeline b
element Word64
position Int32
layerPriority = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
    Ptr Timeline
timeline' <- forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
timeline
    Ptr TimelineElement
element' <- forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
element
    Ptr TimelineElement
result <- Ptr Timeline
-> Ptr TimelineElement
-> Word64
-> Int32
-> IO (Ptr TimelineElement)
ges_timeline_paste_element Ptr Timeline
timeline' Ptr TimelineElement
element' Word64
position Int32
layerPriority
    Maybe TimelineElement
maybeResult <- forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr TimelineElement
result forall a b. (a -> b) -> a -> b
$ \Ptr TimelineElement
result' -> do
        TimelineElement
result'' <- (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'
        forall (m :: * -> *) a. Monad m => a -> m a
return TimelineElement
result''
    forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
timeline
    forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
element
    forall (m :: * -> *) a. Monad m => a -> m a
return Maybe TimelineElement
maybeResult

#if defined(ENABLE_OVERLOADING)
data TimelinePasteElementMethodInfo
instance (signature ~ (b -> Word64 -> Int32 -> m (Maybe GES.TimelineElement.TimelineElement)), MonadIO m, IsTimeline a, GES.TimelineElement.IsTimelineElement b) => O.OverloadedMethod TimelinePasteElementMethodInfo a signature where
    overloadedMethod = timelinePasteElement

instance O.OverloadedMethodInfo TimelinePasteElementMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GES.Objects.Timeline.timelinePasteElement",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.1/docs/GI-GES-Objects-Timeline.html#v:timelinePasteElement"
        })


#endif

-- method Timeline::remove_layer
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "timeline"
--           , argType =
--               TInterface Name { namespace = "GES" , name = "Timeline" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The #GESTimeline" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "layer"
--           , argType = TInterface Name { namespace = "GES" , name = "Layer" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The layer to remove"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "ges_timeline_remove_layer" ges_timeline_remove_layer :: 
    Ptr Timeline ->                         -- timeline : TInterface (Name {namespace = "GES", name = "Timeline"})
    Ptr GES.Layer.Layer ->                  -- layer : TInterface (Name {namespace = "GES", name = "Layer"})
    IO CInt

-- | Removes a layer from the timeline.
timelineRemoveLayer ::
    (B.CallStack.HasCallStack, MonadIO m, IsTimeline a, GES.Layer.IsLayer b) =>
    a
    -- ^ /@timeline@/: The t'GI.GES.Objects.Timeline.Timeline'
    -> b
    -- ^ /@layer@/: The layer to remove
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@layer@/ was properly removed.
timelineRemoveLayer :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsTimeline a, IsLayer b) =>
a -> b -> m Bool
timelineRemoveLayer a
timeline b
layer = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
    Ptr Timeline
timeline' <- forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
timeline
    Ptr Layer
layer' <- forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
layer
    CInt
result <- Ptr Timeline -> Ptr Layer -> IO CInt
ges_timeline_remove_layer Ptr Timeline
timeline' Ptr Layer
layer'
    let result' :: Bool
result' = (forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
timeline
    forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
layer
    forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TimelineRemoveLayerMethodInfo
instance (signature ~ (b -> m Bool), MonadIO m, IsTimeline a, GES.Layer.IsLayer b) => O.OverloadedMethod TimelineRemoveLayerMethodInfo a signature where
    overloadedMethod = timelineRemoveLayer

instance O.OverloadedMethodInfo TimelineRemoveLayerMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GES.Objects.Timeline.timelineRemoveLayer",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.1/docs/GI-GES-Objects-Timeline.html#v:timelineRemoveLayer"
        })


#endif

-- method Timeline::remove_track
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "timeline"
--           , argType =
--               TInterface Name { namespace = "GES" , name = "Timeline" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The #GESTimeline" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "track"
--           , argType = TInterface Name { namespace = "GES" , name = "Track" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The track to remove"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "ges_timeline_remove_track" ges_timeline_remove_track :: 
    Ptr Timeline ->                         -- timeline : TInterface (Name {namespace = "GES", name = "Timeline"})
    Ptr GES.Track.Track ->                  -- track : TInterface (Name {namespace = "GES", name = "Track"})
    IO CInt

-- | Remove a track from the timeline.
timelineRemoveTrack ::
    (B.CallStack.HasCallStack, MonadIO m, IsTimeline a, GES.Track.IsTrack b) =>
    a
    -- ^ /@timeline@/: The t'GI.GES.Objects.Timeline.Timeline'
    -> b
    -- ^ /@track@/: The track to remove
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@track@/ was properly removed.
timelineRemoveTrack :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsTimeline a, IsTrack b) =>
a -> b -> m Bool
timelineRemoveTrack a
timeline b
track = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
    Ptr Timeline
timeline' <- forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
timeline
    Ptr Track
track' <- forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
track
    CInt
result <- Ptr Timeline -> Ptr Track -> IO CInt
ges_timeline_remove_track Ptr Timeline
timeline' Ptr Track
track'
    let result' :: Bool
result' = (forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
timeline
    forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
track
    forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TimelineRemoveTrackMethodInfo
instance (signature ~ (b -> m Bool), MonadIO m, IsTimeline a, GES.Track.IsTrack b) => O.OverloadedMethod TimelineRemoveTrackMethodInfo a signature where
    overloadedMethod = timelineRemoveTrack

instance O.OverloadedMethodInfo TimelineRemoveTrackMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GES.Objects.Timeline.timelineRemoveTrack",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.1/docs/GI-GES-Objects-Timeline.html#v:timelineRemoveTrack"
        })


#endif

-- method Timeline::save_to_uri
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "timeline"
--           , argType =
--               TInterface Name { namespace = "GES" , name = "Timeline" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The #GESTimeline" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "uri"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The location to save to"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "formatter_asset"
--           , argType = TInterface Name { namespace = "GES" , name = "Asset" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The formatter asset to use, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "overwrite"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "%TRUE to overwrite file if it exists"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "ges_timeline_save_to_uri" ges_timeline_save_to_uri :: 
    Ptr Timeline ->                         -- timeline : TInterface (Name {namespace = "GES", name = "Timeline"})
    CString ->                              -- uri : TBasicType TUTF8
    Ptr GES.Asset.Asset ->                  -- formatter_asset : TInterface (Name {namespace = "GES", name = "Asset"})
    CInt ->                                 -- overwrite : TBasicType TBoolean
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Saves the timeline to the given location. If /@formatterAsset@/ is 'P.Nothing',
-- the method will attempt to save in the same format the timeline was
-- loaded from, before defaulting to the formatter with highest rank.
timelineSaveToUri ::
    (B.CallStack.HasCallStack, MonadIO m, IsTimeline a, GES.Asset.IsAsset b) =>
    a
    -- ^ /@timeline@/: The t'GI.GES.Objects.Timeline.Timeline'
    -> T.Text
    -- ^ /@uri@/: The location to save to
    -> Maybe (b)
    -- ^ /@formatterAsset@/: The formatter asset to use, or 'P.Nothing'
    -> Bool
    -- ^ /@overwrite@/: 'P.True' to overwrite file if it exists
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
timelineSaveToUri :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsTimeline a, IsAsset b) =>
a -> Text -> Maybe b -> Bool -> m ()
timelineSaveToUri a
timeline Text
uri Maybe b
formatterAsset Bool
overwrite = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
    Ptr Timeline
timeline' <- forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
timeline
    CString
uri' <- Text -> IO CString
textToCString Text
uri
    Ptr Asset
maybeFormatterAsset <- case Maybe b
formatterAsset of
        Maybe b
Nothing -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Ptr a
nullPtr
        Just b
jFormatterAsset -> do
            Ptr Asset
jFormatterAsset' <- forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jFormatterAsset
            forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Asset
jFormatterAsset'
    let overwrite' :: CInt
overwrite' = (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Enum a => a -> Int
fromEnum) Bool
overwrite
    forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError forall a b. (a -> b) -> a -> b
$ Ptr Timeline
-> CString -> Ptr Asset -> CInt -> Ptr (Ptr GError) -> IO CInt
ges_timeline_save_to_uri Ptr Timeline
timeline' CString
uri' Ptr Asset
maybeFormatterAsset CInt
overwrite'
        forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
timeline
        forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
formatterAsset forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
        forall a. Ptr a -> IO ()
freeMem CString
uri'
        forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        forall a. Ptr a -> IO ()
freeMem CString
uri'
     )

#if defined(ENABLE_OVERLOADING)
data TimelineSaveToUriMethodInfo
instance (signature ~ (T.Text -> Maybe (b) -> Bool -> m ()), MonadIO m, IsTimeline a, GES.Asset.IsAsset b) => O.OverloadedMethod TimelineSaveToUriMethodInfo a signature where
    overloadedMethod = timelineSaveToUri

instance O.OverloadedMethodInfo TimelineSaveToUriMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GES.Objects.Timeline.timelineSaveToUri",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.1/docs/GI-GES-Objects-Timeline.html#v:timelineSaveToUri"
        })


#endif

-- method Timeline::set_auto_transition
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "timeline"
--           , argType =
--               TInterface Name { namespace = "GES" , name = "Timeline" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The #GESTimeline" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "auto_transition"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "Whether transitions should be automatically added\nto @timeline's layers"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "ges_timeline_set_auto_transition" ges_timeline_set_auto_transition :: 
    Ptr Timeline ->                         -- timeline : TInterface (Name {namespace = "GES", name = "Timeline"})
    CInt ->                                 -- auto_transition : TBasicType TBoolean
    IO ()

-- | Sets [Timeline:autoTransition]("GI.GES.Objects.Timeline#g:attr:autoTransition") for the timeline. This will also set
-- the corresponding [Layer:autoTransition]("GI.GES.Objects.Layer#g:attr:autoTransition") for all of the timeline\'s
-- layers to the same value. See 'GI.GES.Objects.Layer.layerSetAutoTransition' if you
-- wish to set the layer\'s [Layer:autoTransition]("GI.GES.Objects.Layer#g:attr:autoTransition") individually.
timelineSetAutoTransition ::
    (B.CallStack.HasCallStack, MonadIO m, IsTimeline a) =>
    a
    -- ^ /@timeline@/: The t'GI.GES.Objects.Timeline.Timeline'
    -> Bool
    -- ^ /@autoTransition@/: Whether transitions should be automatically added
    -- to /@timeline@/\'s layers
    -> m ()
timelineSetAutoTransition :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTimeline a) =>
a -> Bool -> m ()
timelineSetAutoTransition a
timeline Bool
autoTransition = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
    Ptr Timeline
timeline' <- forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
timeline
    let autoTransition' :: CInt
autoTransition' = (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Enum a => a -> Int
fromEnum) Bool
autoTransition
    Ptr Timeline -> CInt -> IO ()
ges_timeline_set_auto_transition Ptr Timeline
timeline' CInt
autoTransition'
    forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
timeline
    forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data TimelineSetAutoTransitionMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsTimeline a) => O.OverloadedMethod TimelineSetAutoTransitionMethodInfo a signature where
    overloadedMethod = timelineSetAutoTransition

instance O.OverloadedMethodInfo TimelineSetAutoTransitionMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GES.Objects.Timeline.timelineSetAutoTransition",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.1/docs/GI-GES-Objects-Timeline.html#v:timelineSetAutoTransition"
        })


#endif

-- method Timeline::set_snapping_distance
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "timeline"
--           , argType =
--               TInterface Name { namespace = "GES" , name = "Timeline" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The #GESTimeline" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "snapping_distance"
--           , argType = TBasicType TUInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The snapping distance to use (in nanoseconds)"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "ges_timeline_set_snapping_distance" ges_timeline_set_snapping_distance :: 
    Ptr Timeline ->                         -- timeline : TInterface (Name {namespace = "GES", name = "Timeline"})
    Word64 ->                               -- snapping_distance : TBasicType TUInt64
    IO ()

-- | Sets [Timeline:snappingDistance]("GI.GES.Objects.Timeline#g:attr:snappingDistance") for the timeline. This new value
-- will only effect future snappings and will not be used to snap the
-- current element positions within the timeline.
timelineSetSnappingDistance ::
    (B.CallStack.HasCallStack, MonadIO m, IsTimeline a) =>
    a
    -- ^ /@timeline@/: The t'GI.GES.Objects.Timeline.Timeline'
    -> Word64
    -- ^ /@snappingDistance@/: The snapping distance to use (in nanoseconds)
    -> m ()
timelineSetSnappingDistance :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTimeline a) =>
a -> Word64 -> m ()
timelineSetSnappingDistance a
timeline Word64
snappingDistance = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
    Ptr Timeline
timeline' <- forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
timeline
    Ptr Timeline -> Word64 -> IO ()
ges_timeline_set_snapping_distance Ptr Timeline
timeline' Word64
snappingDistance
    forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
timeline
    forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data TimelineSetSnappingDistanceMethodInfo
instance (signature ~ (Word64 -> m ()), MonadIO m, IsTimeline a) => O.OverloadedMethod TimelineSetSnappingDistanceMethodInfo a signature where
    overloadedMethod = timelineSetSnappingDistance

instance O.OverloadedMethodInfo TimelineSetSnappingDistanceMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GES.Objects.Timeline.timelineSetSnappingDistance",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.1/docs/GI-GES-Objects-Timeline.html#v:timelineSetSnappingDistance"
        })


#endif

-- method Timeline::thaw_commit
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "timeline"
--           , argType =
--               TInterface Name { namespace = "GES" , name = "Timeline" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The #GESTimeline" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "ges_timeline_thaw_commit" ges_timeline_thaw_commit :: 
    Ptr Timeline ->                         -- timeline : TInterface (Name {namespace = "GES", name = "Timeline"})
    IO ()

-- | Thaw the timeline so that comiting becomes possible
-- again and any call to @commit()@ that happened during the rendering is
-- actually taken into account.
-- 
-- /Since: 1.20/
timelineThawCommit ::
    (B.CallStack.HasCallStack, MonadIO m, IsTimeline a) =>
    a
    -- ^ /@timeline@/: The t'GI.GES.Objects.Timeline.Timeline'
    -> m ()
timelineThawCommit :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTimeline a) =>
a -> m ()
timelineThawCommit a
timeline = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
    Ptr Timeline
timeline' <- forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
timeline
    Ptr Timeline -> IO ()
ges_timeline_thaw_commit Ptr Timeline
timeline'
    forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
timeline
    forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data TimelineThawCommitMethodInfo
instance (signature ~ (m ()), MonadIO m, IsTimeline a) => O.OverloadedMethod TimelineThawCommitMethodInfo a signature where
    overloadedMethod = timelineThawCommit

instance O.OverloadedMethodInfo TimelineThawCommitMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GES.Objects.Timeline.timelineThawCommit",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.1/docs/GI-GES-Objects-Timeline.html#v:timelineThawCommit"
        })


#endif