{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Currently we only support effects with N sinkpads and one single srcpad.
-- Apart from @gesaudiomixer@ and @gescompositor@ which can be used as effects
-- and where sinkpads will be requested as needed based on the timeline topology
-- GES will always request at most one sinkpad per effect (when required).
-- 
-- > Note: GES always adds converters (@audioconvert ! audioresample !
-- > audioconvert@ for audio effects and @videoconvert@ for video effects) to
-- > make it simpler for end users.

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

module GI.GES.Objects.Effect
    ( 

-- * Exported types
    Effect(..)                              ,
    IsEffect                                ,
    toEffect                                ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [addChildProperty]("GI.GES.Objects.TimelineElement#g:method:addChildProperty"), [addChildrenProps]("GI.GES.Objects.TrackElement#g:method:addChildrenProps"), [addMetasFromString]("GI.GES.Interfaces.MetaContainer#g:method:addMetasFromString"), [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [checkMetaRegistered]("GI.GES.Interfaces.MetaContainer#g:method:checkMetaRegistered"), [clampControlSource]("GI.GES.Objects.TrackElement#g:method:clampControlSource"), [copy]("GI.GES.Objects.TimelineElement#g:method:copy"), [edit]("GI.GES.Objects.TrackElement#g:method:edit"), [editFull]("GI.GES.Objects.TimelineElement#g:method:editFull"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [foreach]("GI.GES.Interfaces.MetaContainer#g:method:foreach"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [hasInternalSource]("GI.GES.Objects.TrackElement#g:method:hasInternalSource"), [isActive]("GI.GES.Objects.TrackElement#g:method:isActive"), [isCore]("GI.GES.Objects.TrackElement#g:method:isCore"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [isTimeEffect]("GI.GES.Objects.BaseEffect#g:method:isTimeEffect"), [listChildrenProperties]("GI.GES.Objects.TrackElement#g:method:listChildrenProperties"), [lookupChild]("GI.GES.Objects.TrackElement#g:method:lookupChild"), [metasToString]("GI.GES.Interfaces.MetaContainer#g:method:metasToString"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [paste]("GI.GES.Objects.TimelineElement#g:method:paste"), [ref]("GI.GObject.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"), [registerTimeProperty]("GI.GES.Objects.BaseEffect#g:method:registerTimeProperty"), [removeChildProperty]("GI.GES.Objects.TimelineElement#g:method:removeChildProperty"), [removeControlBinding]("GI.GES.Objects.TrackElement#g:method:removeControlBinding"), [ripple]("GI.GES.Objects.TimelineElement#g:method:ripple"), [rippleEnd]("GI.GES.Objects.TimelineElement#g:method:rippleEnd"), [rollEnd]("GI.GES.Objects.TimelineElement#g:method:rollEnd"), [rollStart]("GI.GES.Objects.TimelineElement#g:method:rollStart"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [trim]("GI.GES.Objects.TimelineElement#g:method:trim"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getAllControlBindings]("GI.GES.Objects.TrackElement#g:method:getAllControlBindings"), [getAsset]("GI.GES.Interfaces.Extractable#g:method:getAsset"), [getAutoClampControlSources]("GI.GES.Objects.TrackElement#g:method:getAutoClampControlSources"), [getBoolean]("GI.GES.Interfaces.MetaContainer#g:method:getBoolean"), [getChildProperty]("GI.GES.Objects.TimelineElement#g:method:getChildProperty"), [getChildPropertyByPspec]("GI.GES.Objects.TimelineElement#g:method:getChildPropertyByPspec"), [getControlBinding]("GI.GES.Objects.TrackElement#g:method:getControlBinding"), [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.TimelineElement#g:method:getDuration"), [getElement]("GI.GES.Objects.TrackElement#g:method:getElement"), [getFloat]("GI.GES.Interfaces.MetaContainer#g:method:getFloat"), [getGnlobject]("GI.GES.Objects.TrackElement#g:method:getGnlobject"), [getId]("GI.GES.Interfaces.Extractable#g:method:getId"), [getInpoint]("GI.GES.Objects.TimelineElement#g:method:getInpoint"), [getInt]("GI.GES.Interfaces.MetaContainer#g:method:getInt"), [getInt64]("GI.GES.Interfaces.MetaContainer#g:method:getInt64"), [getLayerPriority]("GI.GES.Objects.TimelineElement#g:method:getLayerPriority"), [getMarkerList]("GI.GES.Interfaces.MetaContainer#g:method:getMarkerList"), [getMaxDuration]("GI.GES.Objects.TimelineElement#g:method:getMaxDuration"), [getMeta]("GI.GES.Interfaces.MetaContainer#g:method:getMeta"), [getName]("GI.GES.Objects.TimelineElement#g:method:getName"), [getNaturalFramerate]("GI.GES.Objects.TimelineElement#g:method:getNaturalFramerate"), [getNleobject]("GI.GES.Objects.TrackElement#g:method:getNleobject"), [getParent]("GI.GES.Objects.TimelineElement#g:method:getParent"), [getPriority]("GI.GES.Objects.TimelineElement#g:method:getPriority"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getStart]("GI.GES.Objects.TimelineElement#g:method:getStart"), [getString]("GI.GES.Interfaces.MetaContainer#g:method:getString"), [getTimeline]("GI.GES.Objects.TimelineElement#g:method:getTimeline"), [getToplevelParent]("GI.GES.Objects.TimelineElement#g:method:getToplevelParent"), [getTrack]("GI.GES.Objects.TrackElement#g:method:getTrack"), [getTrackType]("GI.GES.Objects.TrackElement#g:method:getTrackType"), [getTrackTypes]("GI.GES.Objects.TimelineElement#g:method:getTrackTypes"), [getUint]("GI.GES.Interfaces.MetaContainer#g:method:getUint"), [getUint64]("GI.GES.Interfaces.MetaContainer#g:method:getUint64").
-- 
-- ==== Setters
-- [setActive]("GI.GES.Objects.TrackElement#g:method:setActive"), [setAsset]("GI.GES.Interfaces.Extractable#g:method:setAsset"), [setAutoClampControlSources]("GI.GES.Objects.TrackElement#g:method:setAutoClampControlSources"), [setBoolean]("GI.GES.Interfaces.MetaContainer#g:method:setBoolean"), [setChildProperty]("GI.GES.Objects.TimelineElement#g:method:setChildProperty"), [setChildPropertyByPspec]("GI.GES.Objects.TimelineElement#g:method:setChildPropertyByPspec"), [setChildPropertyFull]("GI.GES.Objects.TimelineElement#g:method:setChildPropertyFull"), [setControlSource]("GI.GES.Objects.TrackElement#g:method:setControlSource"), [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"), [setDuration]("GI.GES.Objects.TimelineElement#g:method:setDuration"), [setFloat]("GI.GES.Interfaces.MetaContainer#g:method:setFloat"), [setHasInternalSource]("GI.GES.Objects.TrackElement#g:method:setHasInternalSource"), [setInpoint]("GI.GES.Objects.TimelineElement#g:method:setInpoint"), [setInt]("GI.GES.Interfaces.MetaContainer#g:method:setInt"), [setInt64]("GI.GES.Interfaces.MetaContainer#g:method:setInt64"), [setMarkerList]("GI.GES.Interfaces.MetaContainer#g:method:setMarkerList"), [setMaxDuration]("GI.GES.Objects.TimelineElement#g:method:setMaxDuration"), [setMeta]("GI.GES.Interfaces.MetaContainer#g:method:setMeta"), [setName]("GI.GES.Objects.TimelineElement#g:method:setName"), [setParent]("GI.GES.Objects.TimelineElement#g:method:setParent"), [setPriority]("GI.GES.Objects.TimelineElement#g:method:setPriority"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setStart]("GI.GES.Objects.TimelineElement#g:method:setStart"), [setString]("GI.GES.Interfaces.MetaContainer#g:method:setString"), [setTimeTranslationFuncs]("GI.GES.Objects.BaseEffect#g:method:setTimeTranslationFuncs"), [setTimeline]("GI.GES.Objects.TimelineElement#g:method:setTimeline"), [setTrackType]("GI.GES.Objects.TrackElement#g:method:setTrackType"), [setUint]("GI.GES.Interfaces.MetaContainer#g:method:setUint"), [setUint64]("GI.GES.Interfaces.MetaContainer#g:method:setUint64").

#if defined(ENABLE_OVERLOADING)
    ResolveEffectMethod                     ,
#endif

-- ** new #method:new#

    effectNew                               ,




 -- * Properties


-- ** binDescription #attr:binDescription#
-- | The description of the effect bin with a gst-launch-style
-- pipeline description.
-- 
-- Example: \"videobalance saturation=1.5 hue=+0.5\"

#if defined(ENABLE_OVERLOADING)
    EffectBinDescriptionPropertyInfo        ,
#endif
    constructEffectBinDescription           ,
#if defined(ENABLE_OVERLOADING)
    effectBinDescription                    ,
#endif
    getEffectBinDescription                 ,




    ) 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.BaseEffect as GES.BaseEffect
import {-# SOURCE #-} qualified GI.GES.Objects.Operation as GES.Operation
import {-# SOURCE #-} qualified GI.GES.Objects.TimelineElement as GES.TimelineElement
import {-# SOURCE #-} qualified GI.GES.Objects.TrackElement as GES.TrackElement
import qualified GI.GObject.Objects.Object as GObject.Object

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

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

foreign import ccall "ges_effect_get_type"
    c_ges_effect_get_type :: IO B.Types.GType

instance B.Types.TypedObject Effect where
    glibType :: IO GType
glibType = IO GType
c_ges_effect_get_type

instance B.Types.GObject Effect

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

instance O.HasParentTypes Effect
type instance O.ParentTypes Effect = '[GES.BaseEffect.BaseEffect, GES.Operation.Operation, GES.TrackElement.TrackElement, GES.TimelineElement.TimelineElement, GObject.Object.Object, GES.Extractable.Extractable, GES.MetaContainer.MetaContainer]

-- | Cast to `Effect`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toEffect :: (MIO.MonadIO m, IsEffect o) => o -> m Effect
toEffect :: forall (m :: * -> *) o. (MonadIO m, IsEffect o) => o -> m Effect
toEffect = IO Effect -> m Effect
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Effect -> m Effect) -> (o -> IO Effect) -> o -> m Effect
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr Effect -> Effect) -> o -> IO Effect
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr Effect -> Effect
Effect

-- | Convert 'Effect' 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 Effect) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_ges_effect_get_type
    gvalueSet_ :: Ptr GValue -> Maybe Effect -> IO ()
gvalueSet_ Ptr GValue
gv Maybe Effect
P.Nothing = Ptr GValue -> Ptr Effect -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr Effect
forall a. Ptr a
FP.nullPtr :: FP.Ptr Effect)
    gvalueSet_ Ptr GValue
gv (P.Just Effect
obj) = Effect -> (Ptr Effect -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Effect
obj (Ptr GValue -> Ptr Effect -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe Effect)
gvalueGet_ Ptr GValue
gv = do
        Ptr Effect
ptr <- Ptr GValue -> IO (Ptr Effect)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr Effect)
        if Ptr Effect
ptr Ptr Effect -> Ptr Effect -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr Effect
forall a. Ptr a
FP.nullPtr
        then Effect -> Maybe Effect
forall a. a -> Maybe a
P.Just (Effect -> Maybe Effect) -> IO Effect -> IO (Maybe Effect)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr Effect -> Effect) -> Ptr Effect -> IO Effect
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr Effect -> Effect
Effect Ptr Effect
ptr
        else Maybe Effect -> IO (Maybe Effect)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Effect
forall a. Maybe a
P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
type family ResolveEffectMethod (t :: Symbol) (o :: *) :: * where
    ResolveEffectMethod "addChildProperty" o = GES.TimelineElement.TimelineElementAddChildPropertyMethodInfo
    ResolveEffectMethod "addChildrenProps" o = GES.TrackElement.TrackElementAddChildrenPropsMethodInfo
    ResolveEffectMethod "addMetasFromString" o = GES.MetaContainer.MetaContainerAddMetasFromStringMethodInfo
    ResolveEffectMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveEffectMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveEffectMethod "checkMetaRegistered" o = GES.MetaContainer.MetaContainerCheckMetaRegisteredMethodInfo
    ResolveEffectMethod "clampControlSource" o = GES.TrackElement.TrackElementClampControlSourceMethodInfo
    ResolveEffectMethod "copy" o = GES.TimelineElement.TimelineElementCopyMethodInfo
    ResolveEffectMethod "edit" o = GES.TrackElement.TrackElementEditMethodInfo
    ResolveEffectMethod "editFull" o = GES.TimelineElement.TimelineElementEditFullMethodInfo
    ResolveEffectMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveEffectMethod "foreach" o = GES.MetaContainer.MetaContainerForeachMethodInfo
    ResolveEffectMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveEffectMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveEffectMethod "hasInternalSource" o = GES.TrackElement.TrackElementHasInternalSourceMethodInfo
    ResolveEffectMethod "isActive" o = GES.TrackElement.TrackElementIsActiveMethodInfo
    ResolveEffectMethod "isCore" o = GES.TrackElement.TrackElementIsCoreMethodInfo
    ResolveEffectMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveEffectMethod "isTimeEffect" o = GES.BaseEffect.BaseEffectIsTimeEffectMethodInfo
    ResolveEffectMethod "listChildrenProperties" o = GES.TrackElement.TrackElementListChildrenPropertiesMethodInfo
    ResolveEffectMethod "lookupChild" o = GES.TrackElement.TrackElementLookupChildMethodInfo
    ResolveEffectMethod "metasToString" o = GES.MetaContainer.MetaContainerMetasToStringMethodInfo
    ResolveEffectMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveEffectMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveEffectMethod "paste" o = GES.TimelineElement.TimelineElementPasteMethodInfo
    ResolveEffectMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveEffectMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveEffectMethod "registerMeta" o = GES.MetaContainer.MetaContainerRegisterMetaMethodInfo
    ResolveEffectMethod "registerMetaBoolean" o = GES.MetaContainer.MetaContainerRegisterMetaBooleanMethodInfo
    ResolveEffectMethod "registerMetaDate" o = GES.MetaContainer.MetaContainerRegisterMetaDateMethodInfo
    ResolveEffectMethod "registerMetaDateTime" o = GES.MetaContainer.MetaContainerRegisterMetaDateTimeMethodInfo
    ResolveEffectMethod "registerMetaDouble" o = GES.MetaContainer.MetaContainerRegisterMetaDoubleMethodInfo
    ResolveEffectMethod "registerMetaFloat" o = GES.MetaContainer.MetaContainerRegisterMetaFloatMethodInfo
    ResolveEffectMethod "registerMetaInt" o = GES.MetaContainer.MetaContainerRegisterMetaIntMethodInfo
    ResolveEffectMethod "registerMetaInt64" o = GES.MetaContainer.MetaContainerRegisterMetaInt64MethodInfo
    ResolveEffectMethod "registerMetaString" o = GES.MetaContainer.MetaContainerRegisterMetaStringMethodInfo
    ResolveEffectMethod "registerMetaUint" o = GES.MetaContainer.MetaContainerRegisterMetaUintMethodInfo
    ResolveEffectMethod "registerMetaUint64" o = GES.MetaContainer.MetaContainerRegisterMetaUint64MethodInfo
    ResolveEffectMethod "registerStaticMeta" o = GES.MetaContainer.MetaContainerRegisterStaticMetaMethodInfo
    ResolveEffectMethod "registerTimeProperty" o = GES.BaseEffect.BaseEffectRegisterTimePropertyMethodInfo
    ResolveEffectMethod "removeChildProperty" o = GES.TimelineElement.TimelineElementRemoveChildPropertyMethodInfo
    ResolveEffectMethod "removeControlBinding" o = GES.TrackElement.TrackElementRemoveControlBindingMethodInfo
    ResolveEffectMethod "ripple" o = GES.TimelineElement.TimelineElementRippleMethodInfo
    ResolveEffectMethod "rippleEnd" o = GES.TimelineElement.TimelineElementRippleEndMethodInfo
    ResolveEffectMethod "rollEnd" o = GES.TimelineElement.TimelineElementRollEndMethodInfo
    ResolveEffectMethod "rollStart" o = GES.TimelineElement.TimelineElementRollStartMethodInfo
    ResolveEffectMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveEffectMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveEffectMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveEffectMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveEffectMethod "trim" o = GES.TimelineElement.TimelineElementTrimMethodInfo
    ResolveEffectMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveEffectMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveEffectMethod "getAllControlBindings" o = GES.TrackElement.TrackElementGetAllControlBindingsMethodInfo
    ResolveEffectMethod "getAsset" o = GES.Extractable.ExtractableGetAssetMethodInfo
    ResolveEffectMethod "getAutoClampControlSources" o = GES.TrackElement.TrackElementGetAutoClampControlSourcesMethodInfo
    ResolveEffectMethod "getBoolean" o = GES.MetaContainer.MetaContainerGetBooleanMethodInfo
    ResolveEffectMethod "getChildProperty" o = GES.TimelineElement.TimelineElementGetChildPropertyMethodInfo
    ResolveEffectMethod "getChildPropertyByPspec" o = GES.TimelineElement.TimelineElementGetChildPropertyByPspecMethodInfo
    ResolveEffectMethod "getControlBinding" o = GES.TrackElement.TrackElementGetControlBindingMethodInfo
    ResolveEffectMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveEffectMethod "getDate" o = GES.MetaContainer.MetaContainerGetDateMethodInfo
    ResolveEffectMethod "getDateTime" o = GES.MetaContainer.MetaContainerGetDateTimeMethodInfo
    ResolveEffectMethod "getDouble" o = GES.MetaContainer.MetaContainerGetDoubleMethodInfo
    ResolveEffectMethod "getDuration" o = GES.TimelineElement.TimelineElementGetDurationMethodInfo
    ResolveEffectMethod "getElement" o = GES.TrackElement.TrackElementGetElementMethodInfo
    ResolveEffectMethod "getFloat" o = GES.MetaContainer.MetaContainerGetFloatMethodInfo
    ResolveEffectMethod "getGnlobject" o = GES.TrackElement.TrackElementGetGnlobjectMethodInfo
    ResolveEffectMethod "getId" o = GES.Extractable.ExtractableGetIdMethodInfo
    ResolveEffectMethod "getInpoint" o = GES.TimelineElement.TimelineElementGetInpointMethodInfo
    ResolveEffectMethod "getInt" o = GES.MetaContainer.MetaContainerGetIntMethodInfo
    ResolveEffectMethod "getInt64" o = GES.MetaContainer.MetaContainerGetInt64MethodInfo
    ResolveEffectMethod "getLayerPriority" o = GES.TimelineElement.TimelineElementGetLayerPriorityMethodInfo
    ResolveEffectMethod "getMarkerList" o = GES.MetaContainer.MetaContainerGetMarkerListMethodInfo
    ResolveEffectMethod "getMaxDuration" o = GES.TimelineElement.TimelineElementGetMaxDurationMethodInfo
    ResolveEffectMethod "getMeta" o = GES.MetaContainer.MetaContainerGetMetaMethodInfo
    ResolveEffectMethod "getName" o = GES.TimelineElement.TimelineElementGetNameMethodInfo
    ResolveEffectMethod "getNaturalFramerate" o = GES.TimelineElement.TimelineElementGetNaturalFramerateMethodInfo
    ResolveEffectMethod "getNleobject" o = GES.TrackElement.TrackElementGetNleobjectMethodInfo
    ResolveEffectMethod "getParent" o = GES.TimelineElement.TimelineElementGetParentMethodInfo
    ResolveEffectMethod "getPriority" o = GES.TimelineElement.TimelineElementGetPriorityMethodInfo
    ResolveEffectMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveEffectMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveEffectMethod "getStart" o = GES.TimelineElement.TimelineElementGetStartMethodInfo
    ResolveEffectMethod "getString" o = GES.MetaContainer.MetaContainerGetStringMethodInfo
    ResolveEffectMethod "getTimeline" o = GES.TimelineElement.TimelineElementGetTimelineMethodInfo
    ResolveEffectMethod "getToplevelParent" o = GES.TimelineElement.TimelineElementGetToplevelParentMethodInfo
    ResolveEffectMethod "getTrack" o = GES.TrackElement.TrackElementGetTrackMethodInfo
    ResolveEffectMethod "getTrackType" o = GES.TrackElement.TrackElementGetTrackTypeMethodInfo
    ResolveEffectMethod "getTrackTypes" o = GES.TimelineElement.TimelineElementGetTrackTypesMethodInfo
    ResolveEffectMethod "getUint" o = GES.MetaContainer.MetaContainerGetUintMethodInfo
    ResolveEffectMethod "getUint64" o = GES.MetaContainer.MetaContainerGetUint64MethodInfo
    ResolveEffectMethod "setActive" o = GES.TrackElement.TrackElementSetActiveMethodInfo
    ResolveEffectMethod "setAsset" o = GES.Extractable.ExtractableSetAssetMethodInfo
    ResolveEffectMethod "setAutoClampControlSources" o = GES.TrackElement.TrackElementSetAutoClampControlSourcesMethodInfo
    ResolveEffectMethod "setBoolean" o = GES.MetaContainer.MetaContainerSetBooleanMethodInfo
    ResolveEffectMethod "setChildProperty" o = GES.TimelineElement.TimelineElementSetChildPropertyMethodInfo
    ResolveEffectMethod "setChildPropertyByPspec" o = GES.TimelineElement.TimelineElementSetChildPropertyByPspecMethodInfo
    ResolveEffectMethod "setChildPropertyFull" o = GES.TimelineElement.TimelineElementSetChildPropertyFullMethodInfo
    ResolveEffectMethod "setControlSource" o = GES.TrackElement.TrackElementSetControlSourceMethodInfo
    ResolveEffectMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveEffectMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveEffectMethod "setDate" o = GES.MetaContainer.MetaContainerSetDateMethodInfo
    ResolveEffectMethod "setDateTime" o = GES.MetaContainer.MetaContainerSetDateTimeMethodInfo
    ResolveEffectMethod "setDouble" o = GES.MetaContainer.MetaContainerSetDoubleMethodInfo
    ResolveEffectMethod "setDuration" o = GES.TimelineElement.TimelineElementSetDurationMethodInfo
    ResolveEffectMethod "setFloat" o = GES.MetaContainer.MetaContainerSetFloatMethodInfo
    ResolveEffectMethod "setHasInternalSource" o = GES.TrackElement.TrackElementSetHasInternalSourceMethodInfo
    ResolveEffectMethod "setInpoint" o = GES.TimelineElement.TimelineElementSetInpointMethodInfo
    ResolveEffectMethod "setInt" o = GES.MetaContainer.MetaContainerSetIntMethodInfo
    ResolveEffectMethod "setInt64" o = GES.MetaContainer.MetaContainerSetInt64MethodInfo
    ResolveEffectMethod "setMarkerList" o = GES.MetaContainer.MetaContainerSetMarkerListMethodInfo
    ResolveEffectMethod "setMaxDuration" o = GES.TimelineElement.TimelineElementSetMaxDurationMethodInfo
    ResolveEffectMethod "setMeta" o = GES.MetaContainer.MetaContainerSetMetaMethodInfo
    ResolveEffectMethod "setName" o = GES.TimelineElement.TimelineElementSetNameMethodInfo
    ResolveEffectMethod "setParent" o = GES.TimelineElement.TimelineElementSetParentMethodInfo
    ResolveEffectMethod "setPriority" o = GES.TimelineElement.TimelineElementSetPriorityMethodInfo
    ResolveEffectMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveEffectMethod "setStart" o = GES.TimelineElement.TimelineElementSetStartMethodInfo
    ResolveEffectMethod "setString" o = GES.MetaContainer.MetaContainerSetStringMethodInfo
    ResolveEffectMethod "setTimeTranslationFuncs" o = GES.BaseEffect.BaseEffectSetTimeTranslationFuncsMethodInfo
    ResolveEffectMethod "setTimeline" o = GES.TimelineElement.TimelineElementSetTimelineMethodInfo
    ResolveEffectMethod "setTrackType" o = GES.TrackElement.TrackElementSetTrackTypeMethodInfo
    ResolveEffectMethod "setUint" o = GES.MetaContainer.MetaContainerSetUintMethodInfo
    ResolveEffectMethod "setUint64" o = GES.MetaContainer.MetaContainerSetUint64MethodInfo
    ResolveEffectMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

-- VVV Prop "bin-description"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@bin-description@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' effect #binDescription
-- @
getEffectBinDescription :: (MonadIO m, IsEffect o) => o -> m (Maybe T.Text)
getEffectBinDescription :: forall (m :: * -> *) o.
(MonadIO m, IsEffect o) =>
o -> m (Maybe Text)
getEffectBinDescription o
obj = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"bin-description"

-- | Construct a `GValueConstruct` with valid value for the “@bin-description@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructEffectBinDescription :: (IsEffect o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructEffectBinDescription :: forall o (m :: * -> *).
(IsEffect o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructEffectBinDescription Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"bin-description" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

#if defined(ENABLE_OVERLOADING)
data EffectBinDescriptionPropertyInfo
instance AttrInfo EffectBinDescriptionPropertyInfo where
    type AttrAllowedOps EffectBinDescriptionPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint EffectBinDescriptionPropertyInfo = IsEffect
    type AttrSetTypeConstraint EffectBinDescriptionPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint EffectBinDescriptionPropertyInfo = (~) T.Text
    type AttrTransferType EffectBinDescriptionPropertyInfo = T.Text
    type AttrGetType EffectBinDescriptionPropertyInfo = (Maybe T.Text)
    type AttrLabel EffectBinDescriptionPropertyInfo = "bin-description"
    type AttrOrigin EffectBinDescriptionPropertyInfo = Effect
    attrGet = getEffectBinDescription
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructEffectBinDescription
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GES.Objects.Effect.binDescription"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ges-1.0.2/docs/GI-GES-Objects-Effect.html#g:attr:binDescription"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Effect
type instance O.AttributeList Effect = EffectAttributeList
type EffectAttributeList = ('[ '("active", GES.TrackElement.TrackElementActivePropertyInfo), '("autoClampControlSources", GES.TrackElement.TrackElementAutoClampControlSourcesPropertyInfo), '("binDescription", EffectBinDescriptionPropertyInfo), '("duration", GES.TimelineElement.TimelineElementDurationPropertyInfo), '("hasInternalSource", GES.TrackElement.TrackElementHasInternalSourcePropertyInfo), '("inPoint", GES.TimelineElement.TimelineElementInPointPropertyInfo), '("maxDuration", GES.TimelineElement.TimelineElementMaxDurationPropertyInfo), '("name", GES.TimelineElement.TimelineElementNamePropertyInfo), '("parent", GES.TimelineElement.TimelineElementParentPropertyInfo), '("priority", GES.TimelineElement.TimelineElementPriorityPropertyInfo), '("serialize", GES.TimelineElement.TimelineElementSerializePropertyInfo), '("start", GES.TimelineElement.TimelineElementStartPropertyInfo), '("timeline", GES.TimelineElement.TimelineElementTimelinePropertyInfo), '("track", GES.TrackElement.TrackElementTrackPropertyInfo), '("trackType", GES.TrackElement.TrackElementTrackTypePropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
effectBinDescription :: AttrLabelProxy "binDescription"
effectBinDescription = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Effect = EffectSignalList
type EffectSignalList = ('[ '("childPropertyAdded", GES.TimelineElement.TimelineElementChildPropertyAddedSignalInfo), '("childPropertyRemoved", GES.TimelineElement.TimelineElementChildPropertyRemovedSignalInfo), '("controlBindingAdded", GES.TrackElement.TrackElementControlBindingAddedSignalInfo), '("controlBindingRemoved", GES.TrackElement.TrackElementControlBindingRemovedSignalInfo), '("deepNotify", GES.TimelineElement.TimelineElementDeepNotifySignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("notifyMeta", GES.MetaContainer.MetaContainerNotifyMetaSignalInfo)] :: [(Symbol, *)])

#endif

-- method Effect::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "bin_description"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "The gst-launch like bin description of the effect"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GES" , name = "Effect" })
-- throws : False
-- Skip return : False

foreign import ccall "ges_effect_new" ges_effect_new :: 
    CString ->                              -- bin_description : TBasicType TUTF8
    IO (Ptr Effect)

-- | Creates a new t'GI.GES.Objects.Effect.Effect' from the description of the bin. It should be
-- possible to determine the type of the effect through the element
-- \'klass\' metadata of the GstElements that will be created.
-- In that corner case, you should use:
-- @/ges_asset_request/@ (GES_TYPE_EFFECT, \"audio your ! bin ! description\", NULL);
-- and extract that asset to be in full control.
effectNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    -- ^ /@binDescription@/: The gst-launch like bin description of the effect
    -> m (Maybe Effect)
    -- ^ __Returns:__ a newly created t'GI.GES.Objects.Effect.Effect', or 'P.Nothing' if something went
    -- wrong.
effectNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Text -> m (Maybe Effect)
effectNew Text
binDescription = IO (Maybe Effect) -> m (Maybe Effect)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Effect) -> m (Maybe Effect))
-> IO (Maybe Effect) -> m (Maybe Effect)
forall a b. (a -> b) -> a -> b
$ do
    CString
binDescription' <- Text -> IO CString
textToCString Text
binDescription
    Ptr Effect
result <- CString -> IO (Ptr Effect)
ges_effect_new CString
binDescription'
    Maybe Effect
maybeResult <- Ptr Effect -> (Ptr Effect -> IO Effect) -> IO (Maybe Effect)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Effect
result ((Ptr Effect -> IO Effect) -> IO (Maybe Effect))
-> (Ptr Effect -> IO Effect) -> IO (Maybe Effect)
forall a b. (a -> b) -> a -> b
$ \Ptr Effect
result' -> do
        Effect
result'' <- ((ManagedPtr Effect -> Effect) -> Ptr Effect -> IO Effect
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Effect -> Effect
Effect) Ptr Effect
result'
        Effect -> IO Effect
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Effect
result''
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
binDescription'
    Maybe Effect -> IO (Maybe Effect)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Effect
maybeResult

#if defined(ENABLE_OVERLOADING)
#endif