{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- The t'GI.Clutter.Objects.Transition.Transition' structure contains private
-- data and should only be accessed using the provided API.
-- 
-- /Since: 1.10/

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

module GI.Clutter.Objects.Transition
    ( 

-- * Exported types
    Transition(..)                          ,
    IsTransition                            ,
    toTransition                            ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [addMarker]("GI.Clutter.Objects.Timeline#g:method:addMarker"), [addMarkerAtTime]("GI.Clutter.Objects.Timeline#g:method:addMarkerAtTime"), [advance]("GI.Clutter.Objects.Timeline#g:method:advance"), [advanceToMarker]("GI.Clutter.Objects.Timeline#g:method:advanceToMarker"), [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [clone]("GI.Clutter.Objects.Timeline#g:method:clone"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [hasMarker]("GI.Clutter.Objects.Timeline#g:method:hasMarker"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [isPlaying]("GI.Clutter.Objects.Timeline#g:method:isPlaying"), [listMarkers]("GI.Clutter.Objects.Timeline#g:method:listMarkers"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [parseCustomNode]("GI.Clutter.Interfaces.Scriptable#g:method:parseCustomNode"), [pause]("GI.Clutter.Objects.Timeline#g:method:pause"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [removeMarker]("GI.Clutter.Objects.Timeline#g:method:removeMarker"), [rewind]("GI.Clutter.Objects.Timeline#g:method:rewind"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [skip]("GI.Clutter.Objects.Timeline#g:method:skip"), [start]("GI.Clutter.Objects.Timeline#g:method:start"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [stop]("GI.Clutter.Objects.Timeline#g:method:stop"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getAnimatable]("GI.Clutter.Objects.Transition#g:method:getAnimatable"), [getAutoReverse]("GI.Clutter.Objects.Timeline#g:method:getAutoReverse"), [getCubicBezierProgress]("GI.Clutter.Objects.Timeline#g:method:getCubicBezierProgress"), [getCurrentRepeat]("GI.Clutter.Objects.Timeline#g:method:getCurrentRepeat"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getDelay]("GI.Clutter.Objects.Timeline#g:method:getDelay"), [getDelta]("GI.Clutter.Objects.Timeline#g:method:getDelta"), [getDirection]("GI.Clutter.Objects.Timeline#g:method:getDirection"), [getDuration]("GI.Clutter.Objects.Timeline#g:method:getDuration"), [getDurationHint]("GI.Clutter.Objects.Timeline#g:method:getDurationHint"), [getElapsedTime]("GI.Clutter.Objects.Timeline#g:method:getElapsedTime"), [getId]("GI.Clutter.Interfaces.Scriptable#g:method:getId"), [getInterval]("GI.Clutter.Objects.Transition#g:method:getInterval"), [getLoop]("GI.Clutter.Objects.Timeline#g:method:getLoop"), [getProgress]("GI.Clutter.Objects.Timeline#g:method:getProgress"), [getProgressMode]("GI.Clutter.Objects.Timeline#g:method:getProgressMode"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getRemoveOnComplete]("GI.Clutter.Objects.Transition#g:method:getRemoveOnComplete"), [getRepeatCount]("GI.Clutter.Objects.Timeline#g:method:getRepeatCount"), [getStepProgress]("GI.Clutter.Objects.Timeline#g:method:getStepProgress").
-- 
-- ==== Setters
-- [setAnimatable]("GI.Clutter.Objects.Transition#g:method:setAnimatable"), [setAutoReverse]("GI.Clutter.Objects.Timeline#g:method:setAutoReverse"), [setCubicBezierProgress]("GI.Clutter.Objects.Timeline#g:method:setCubicBezierProgress"), [setCustomProperty]("GI.Clutter.Interfaces.Scriptable#g:method:setCustomProperty"), [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setDelay]("GI.Clutter.Objects.Timeline#g:method:setDelay"), [setDirection]("GI.Clutter.Objects.Timeline#g:method:setDirection"), [setDuration]("GI.Clutter.Objects.Timeline#g:method:setDuration"), [setFrom]("GI.Clutter.Objects.Transition#g:method:setFrom"), [setId]("GI.Clutter.Interfaces.Scriptable#g:method:setId"), [setInterval]("GI.Clutter.Objects.Transition#g:method:setInterval"), [setLoop]("GI.Clutter.Objects.Timeline#g:method:setLoop"), [setProgressFunc]("GI.Clutter.Objects.Timeline#g:method:setProgressFunc"), [setProgressMode]("GI.Clutter.Objects.Timeline#g:method:setProgressMode"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setRemoveOnComplete]("GI.Clutter.Objects.Transition#g:method:setRemoveOnComplete"), [setRepeatCount]("GI.Clutter.Objects.Timeline#g:method:setRepeatCount"), [setStepProgress]("GI.Clutter.Objects.Timeline#g:method:setStepProgress"), [setTo]("GI.Clutter.Objects.Transition#g:method:setTo").

#if defined(ENABLE_OVERLOADING)
    ResolveTransitionMethod                 ,
#endif

-- ** getAnimatable #method:getAnimatable#

#if defined(ENABLE_OVERLOADING)
    TransitionGetAnimatableMethodInfo       ,
#endif
    transitionGetAnimatable                 ,


-- ** getInterval #method:getInterval#

#if defined(ENABLE_OVERLOADING)
    TransitionGetIntervalMethodInfo         ,
#endif
    transitionGetInterval                   ,


-- ** getRemoveOnComplete #method:getRemoveOnComplete#

#if defined(ENABLE_OVERLOADING)
    TransitionGetRemoveOnCompleteMethodInfo ,
#endif
    transitionGetRemoveOnComplete           ,


-- ** setAnimatable #method:setAnimatable#

#if defined(ENABLE_OVERLOADING)
    TransitionSetAnimatableMethodInfo       ,
#endif
    transitionSetAnimatable                 ,


-- ** setFrom #method:setFrom#

#if defined(ENABLE_OVERLOADING)
    TransitionSetFromMethodInfo             ,
#endif
    transitionSetFrom                       ,


-- ** setInterval #method:setInterval#

#if defined(ENABLE_OVERLOADING)
    TransitionSetIntervalMethodInfo         ,
#endif
    transitionSetInterval                   ,


-- ** setRemoveOnComplete #method:setRemoveOnComplete#

#if defined(ENABLE_OVERLOADING)
    TransitionSetRemoveOnCompleteMethodInfo ,
#endif
    transitionSetRemoveOnComplete           ,


-- ** setTo #method:setTo#

#if defined(ENABLE_OVERLOADING)
    TransitionSetToMethodInfo               ,
#endif
    transitionSetTo                         ,




 -- * Properties


-- ** animatable #attr:animatable#
-- | The t'GI.Clutter.Interfaces.Animatable.Animatable' instance currently being animated.
-- 
-- /Since: 1.10/

#if defined(ENABLE_OVERLOADING)
    TransitionAnimatablePropertyInfo        ,
#endif
    clearTransitionAnimatable               ,
    constructTransitionAnimatable           ,
    getTransitionAnimatable                 ,
    setTransitionAnimatable                 ,
#if defined(ENABLE_OVERLOADING)
    transitionAnimatable                    ,
#endif


-- ** interval #attr:interval#
-- | The t'GI.Clutter.Objects.Interval.Interval' used to describe the initial and final states
-- of the transition.
-- 
-- /Since: 1.10/

#if defined(ENABLE_OVERLOADING)
    TransitionIntervalPropertyInfo          ,
#endif
    clearTransitionInterval                 ,
    constructTransitionInterval             ,
    getTransitionInterval                   ,
    setTransitionInterval                   ,
#if defined(ENABLE_OVERLOADING)
    transitionInterval                      ,
#endif


-- ** removeOnComplete #attr:removeOnComplete#
-- | Whether the t'GI.Clutter.Objects.Transition.Transition' should be automatically detached
-- from the [Transition:animatable]("GI.Clutter.Objects.Transition#g:attr:animatable") instance whenever the
-- [Timeline::stopped]("GI.Clutter.Objects.Timeline#g:signal:stopped") signal is emitted.
-- 
-- The [Transition:removeOnComplete]("GI.Clutter.Objects.Transition#g:attr:removeOnComplete") property takes into
-- account the value of the [Timeline:repeatCount]("GI.Clutter.Objects.Timeline#g:attr:repeatCount") property,
-- and it only detaches the transition if the transition is not
-- repeating.
-- 
-- /Since: 1.10/

#if defined(ENABLE_OVERLOADING)
    TransitionRemoveOnCompletePropertyInfo  ,
#endif
    constructTransitionRemoveOnComplete     ,
    getTransitionRemoveOnComplete           ,
    setTransitionRemoveOnComplete           ,
#if defined(ENABLE_OVERLOADING)
    transitionRemoveOnComplete              ,
#endif




    ) where

import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R

import {-# SOURCE #-} qualified GI.Clutter.Interfaces.Animatable as Clutter.Animatable
import {-# SOURCE #-} qualified GI.Clutter.Interfaces.Scriptable as Clutter.Scriptable
import {-# SOURCE #-} qualified GI.Clutter.Objects.Interval as Clutter.Interval
import {-# SOURCE #-} qualified GI.Clutter.Objects.Timeline as Clutter.Timeline
import qualified GI.GObject.Objects.Object as GObject.Object

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

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

foreign import ccall "clutter_transition_get_type"
    c_clutter_transition_get_type :: IO B.Types.GType

instance B.Types.TypedObject Transition where
    glibType :: IO GType
glibType = IO GType
c_clutter_transition_get_type

instance B.Types.GObject Transition

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

instance O.HasParentTypes Transition
type instance O.ParentTypes Transition = '[Clutter.Timeline.Timeline, GObject.Object.Object, Clutter.Scriptable.Scriptable]

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveTransitionMethod (t :: Symbol) (o :: *) :: * where
    ResolveTransitionMethod "addMarker" o = Clutter.Timeline.TimelineAddMarkerMethodInfo
    ResolveTransitionMethod "addMarkerAtTime" o = Clutter.Timeline.TimelineAddMarkerAtTimeMethodInfo
    ResolveTransitionMethod "advance" o = Clutter.Timeline.TimelineAdvanceMethodInfo
    ResolveTransitionMethod "advanceToMarker" o = Clutter.Timeline.TimelineAdvanceToMarkerMethodInfo
    ResolveTransitionMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveTransitionMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveTransitionMethod "clone" o = Clutter.Timeline.TimelineCloneMethodInfo
    ResolveTransitionMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveTransitionMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveTransitionMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveTransitionMethod "hasMarker" o = Clutter.Timeline.TimelineHasMarkerMethodInfo
    ResolveTransitionMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveTransitionMethod "isPlaying" o = Clutter.Timeline.TimelineIsPlayingMethodInfo
    ResolveTransitionMethod "listMarkers" o = Clutter.Timeline.TimelineListMarkersMethodInfo
    ResolveTransitionMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveTransitionMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveTransitionMethod "parseCustomNode" o = Clutter.Scriptable.ScriptableParseCustomNodeMethodInfo
    ResolveTransitionMethod "pause" o = Clutter.Timeline.TimelinePauseMethodInfo
    ResolveTransitionMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveTransitionMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveTransitionMethod "removeMarker" o = Clutter.Timeline.TimelineRemoveMarkerMethodInfo
    ResolveTransitionMethod "rewind" o = Clutter.Timeline.TimelineRewindMethodInfo
    ResolveTransitionMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveTransitionMethod "skip" o = Clutter.Timeline.TimelineSkipMethodInfo
    ResolveTransitionMethod "start" o = Clutter.Timeline.TimelineStartMethodInfo
    ResolveTransitionMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveTransitionMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveTransitionMethod "stop" o = Clutter.Timeline.TimelineStopMethodInfo
    ResolveTransitionMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveTransitionMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveTransitionMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveTransitionMethod "getAnimatable" o = TransitionGetAnimatableMethodInfo
    ResolveTransitionMethod "getAutoReverse" o = Clutter.Timeline.TimelineGetAutoReverseMethodInfo
    ResolveTransitionMethod "getCubicBezierProgress" o = Clutter.Timeline.TimelineGetCubicBezierProgressMethodInfo
    ResolveTransitionMethod "getCurrentRepeat" o = Clutter.Timeline.TimelineGetCurrentRepeatMethodInfo
    ResolveTransitionMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveTransitionMethod "getDelay" o = Clutter.Timeline.TimelineGetDelayMethodInfo
    ResolveTransitionMethod "getDelta" o = Clutter.Timeline.TimelineGetDeltaMethodInfo
    ResolveTransitionMethod "getDirection" o = Clutter.Timeline.TimelineGetDirectionMethodInfo
    ResolveTransitionMethod "getDuration" o = Clutter.Timeline.TimelineGetDurationMethodInfo
    ResolveTransitionMethod "getDurationHint" o = Clutter.Timeline.TimelineGetDurationHintMethodInfo
    ResolveTransitionMethod "getElapsedTime" o = Clutter.Timeline.TimelineGetElapsedTimeMethodInfo
    ResolveTransitionMethod "getId" o = Clutter.Scriptable.ScriptableGetIdMethodInfo
    ResolveTransitionMethod "getInterval" o = TransitionGetIntervalMethodInfo
    ResolveTransitionMethod "getLoop" o = Clutter.Timeline.TimelineGetLoopMethodInfo
    ResolveTransitionMethod "getProgress" o = Clutter.Timeline.TimelineGetProgressMethodInfo
    ResolveTransitionMethod "getProgressMode" o = Clutter.Timeline.TimelineGetProgressModeMethodInfo
    ResolveTransitionMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveTransitionMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveTransitionMethod "getRemoveOnComplete" o = TransitionGetRemoveOnCompleteMethodInfo
    ResolveTransitionMethod "getRepeatCount" o = Clutter.Timeline.TimelineGetRepeatCountMethodInfo
    ResolveTransitionMethod "getStepProgress" o = Clutter.Timeline.TimelineGetStepProgressMethodInfo
    ResolveTransitionMethod "setAnimatable" o = TransitionSetAnimatableMethodInfo
    ResolveTransitionMethod "setAutoReverse" o = Clutter.Timeline.TimelineSetAutoReverseMethodInfo
    ResolveTransitionMethod "setCubicBezierProgress" o = Clutter.Timeline.TimelineSetCubicBezierProgressMethodInfo
    ResolveTransitionMethod "setCustomProperty" o = Clutter.Scriptable.ScriptableSetCustomPropertyMethodInfo
    ResolveTransitionMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveTransitionMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveTransitionMethod "setDelay" o = Clutter.Timeline.TimelineSetDelayMethodInfo
    ResolveTransitionMethod "setDirection" o = Clutter.Timeline.TimelineSetDirectionMethodInfo
    ResolveTransitionMethod "setDuration" o = Clutter.Timeline.TimelineSetDurationMethodInfo
    ResolveTransitionMethod "setFrom" o = TransitionSetFromMethodInfo
    ResolveTransitionMethod "setId" o = Clutter.Scriptable.ScriptableSetIdMethodInfo
    ResolveTransitionMethod "setInterval" o = TransitionSetIntervalMethodInfo
    ResolveTransitionMethod "setLoop" o = Clutter.Timeline.TimelineSetLoopMethodInfo
    ResolveTransitionMethod "setProgressFunc" o = Clutter.Timeline.TimelineSetProgressFuncMethodInfo
    ResolveTransitionMethod "setProgressMode" o = Clutter.Timeline.TimelineSetProgressModeMethodInfo
    ResolveTransitionMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveTransitionMethod "setRemoveOnComplete" o = TransitionSetRemoveOnCompleteMethodInfo
    ResolveTransitionMethod "setRepeatCount" o = Clutter.Timeline.TimelineSetRepeatCountMethodInfo
    ResolveTransitionMethod "setStepProgress" o = Clutter.Timeline.TimelineSetStepProgressMethodInfo
    ResolveTransitionMethod "setTo" o = TransitionSetToMethodInfo
    ResolveTransitionMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

-- VVV Prop "animatable"
   -- Type: TInterface (Name {namespace = "Clutter", name = "Animatable"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just True)

-- | Get the value of the “@animatable@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' transition #animatable
-- @
getTransitionAnimatable :: (MonadIO m, IsTransition o) => o -> m Clutter.Animatable.Animatable
getTransitionAnimatable :: forall (m :: * -> *) o.
(MonadIO m, IsTransition o) =>
o -> m Animatable
getTransitionAnimatable o
obj = IO Animatable -> m Animatable
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Animatable -> m Animatable) -> IO Animatable -> m Animatable
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Animatable) -> IO Animatable
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getTransitionAnimatable" (IO (Maybe Animatable) -> IO Animatable)
-> IO (Maybe Animatable) -> IO Animatable
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr Animatable -> Animatable)
-> IO (Maybe Animatable)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"animatable" ManagedPtr Animatable -> Animatable
Clutter.Animatable.Animatable

-- | Set the value of the “@animatable@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' transition [ #animatable 'Data.GI.Base.Attributes.:=' value ]
-- @
setTransitionAnimatable :: (MonadIO m, IsTransition o, Clutter.Animatable.IsAnimatable a) => o -> a -> m ()
setTransitionAnimatable :: forall (m :: * -> *) o a.
(MonadIO m, IsTransition o, IsAnimatable a) =>
o -> a -> m ()
setTransitionAnimatable o
obj a
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Maybe a -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"animatable" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)

-- | Construct a `GValueConstruct` with valid value for the “@animatable@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructTransitionAnimatable :: (IsTransition o, MIO.MonadIO m, Clutter.Animatable.IsAnimatable a) => a -> m (GValueConstruct o)
constructTransitionAnimatable :: forall o (m :: * -> *) a.
(IsTransition o, MonadIO m, IsAnimatable a) =>
a -> m (GValueConstruct o)
constructTransitionAnimatable a
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 a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"animatable" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)

-- | Set the value of the “@animatable@” property to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #animatable
-- @
clearTransitionAnimatable :: (MonadIO m, IsTransition o) => o -> m ()
clearTransitionAnimatable :: forall (m :: * -> *) o. (MonadIO m, IsTransition o) => o -> m ()
clearTransitionAnimatable o
obj = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Animatable -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"animatable" (Maybe Animatable
forall a. Maybe a
Nothing :: Maybe Clutter.Animatable.Animatable)

#if defined(ENABLE_OVERLOADING)
data TransitionAnimatablePropertyInfo
instance AttrInfo TransitionAnimatablePropertyInfo where
    type AttrAllowedOps TransitionAnimatablePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint TransitionAnimatablePropertyInfo = IsTransition
    type AttrSetTypeConstraint TransitionAnimatablePropertyInfo = Clutter.Animatable.IsAnimatable
    type AttrTransferTypeConstraint TransitionAnimatablePropertyInfo = Clutter.Animatable.IsAnimatable
    type AttrTransferType TransitionAnimatablePropertyInfo = Clutter.Animatable.Animatable
    type AttrGetType TransitionAnimatablePropertyInfo = Clutter.Animatable.Animatable
    type AttrLabel TransitionAnimatablePropertyInfo = "animatable"
    type AttrOrigin TransitionAnimatablePropertyInfo = Transition
    attrGet = getTransitionAnimatable
    attrSet = setTransitionAnimatable
    attrTransfer _ v = do
        unsafeCastTo Clutter.Animatable.Animatable v
    attrConstruct = constructTransitionAnimatable
    attrClear = clearTransitionAnimatable
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.Transition.animatable"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.3/docs/GI-Clutter-Objects-Transition.html#g:attr:animatable"
        })
#endif

-- VVV Prop "interval"
   -- Type: TInterface (Name {namespace = "Clutter", name = "Interval"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just True)

-- | Get the value of the “@interval@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' transition #interval
-- @
getTransitionInterval :: (MonadIO m, IsTransition o) => o -> m Clutter.Interval.Interval
getTransitionInterval :: forall (m :: * -> *) o.
(MonadIO m, IsTransition o) =>
o -> m Interval
getTransitionInterval o
obj = IO Interval -> m Interval
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Interval -> m Interval) -> IO Interval -> m Interval
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Interval) -> IO Interval
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getTransitionInterval" (IO (Maybe Interval) -> IO Interval)
-> IO (Maybe Interval) -> IO Interval
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr Interval -> Interval)
-> IO (Maybe Interval)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"interval" ManagedPtr Interval -> Interval
Clutter.Interval.Interval

-- | Set the value of the “@interval@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' transition [ #interval 'Data.GI.Base.Attributes.:=' value ]
-- @
setTransitionInterval :: (MonadIO m, IsTransition o, Clutter.Interval.IsInterval a) => o -> a -> m ()
setTransitionInterval :: forall (m :: * -> *) o a.
(MonadIO m, IsTransition o, IsInterval a) =>
o -> a -> m ()
setTransitionInterval o
obj a
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Maybe a -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"interval" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)

-- | Construct a `GValueConstruct` with valid value for the “@interval@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructTransitionInterval :: (IsTransition o, MIO.MonadIO m, Clutter.Interval.IsInterval a) => a -> m (GValueConstruct o)
constructTransitionInterval :: forall o (m :: * -> *) a.
(IsTransition o, MonadIO m, IsInterval a) =>
a -> m (GValueConstruct o)
constructTransitionInterval a
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 a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"interval" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)

-- | Set the value of the “@interval@” property to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #interval
-- @
clearTransitionInterval :: (MonadIO m, IsTransition o) => o -> m ()
clearTransitionInterval :: forall (m :: * -> *) o. (MonadIO m, IsTransition o) => o -> m ()
clearTransitionInterval o
obj = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Interval -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"interval" (Maybe Interval
forall a. Maybe a
Nothing :: Maybe Clutter.Interval.Interval)

#if defined(ENABLE_OVERLOADING)
data TransitionIntervalPropertyInfo
instance AttrInfo TransitionIntervalPropertyInfo where
    type AttrAllowedOps TransitionIntervalPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint TransitionIntervalPropertyInfo = IsTransition
    type AttrSetTypeConstraint TransitionIntervalPropertyInfo = Clutter.Interval.IsInterval
    type AttrTransferTypeConstraint TransitionIntervalPropertyInfo = Clutter.Interval.IsInterval
    type AttrTransferType TransitionIntervalPropertyInfo = Clutter.Interval.Interval
    type AttrGetType TransitionIntervalPropertyInfo = Clutter.Interval.Interval
    type AttrLabel TransitionIntervalPropertyInfo = "interval"
    type AttrOrigin TransitionIntervalPropertyInfo = Transition
    attrGet = getTransitionInterval
    attrSet = setTransitionInterval
    attrTransfer _ v = do
        unsafeCastTo Clutter.Interval.Interval v
    attrConstruct = constructTransitionInterval
    attrClear = clearTransitionInterval
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.Transition.interval"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.3/docs/GI-Clutter-Objects-Transition.html#g:attr:interval"
        })
#endif

-- VVV Prop "remove-on-complete"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@remove-on-complete@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' transition #removeOnComplete
-- @
getTransitionRemoveOnComplete :: (MonadIO m, IsTransition o) => o -> m Bool
getTransitionRemoveOnComplete :: forall (m :: * -> *) o. (MonadIO m, IsTransition o) => o -> m Bool
getTransitionRemoveOnComplete o
obj = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"remove-on-complete"

-- | Set the value of the “@remove-on-complete@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' transition [ #removeOnComplete 'Data.GI.Base.Attributes.:=' value ]
-- @
setTransitionRemoveOnComplete :: (MonadIO m, IsTransition o) => o -> Bool -> m ()
setTransitionRemoveOnComplete :: forall (m :: * -> *) o.
(MonadIO m, IsTransition o) =>
o -> Bool -> m ()
setTransitionRemoveOnComplete o
obj Bool
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"remove-on-complete" Bool
val

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

#if defined(ENABLE_OVERLOADING)
data TransitionRemoveOnCompletePropertyInfo
instance AttrInfo TransitionRemoveOnCompletePropertyInfo where
    type AttrAllowedOps TransitionRemoveOnCompletePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint TransitionRemoveOnCompletePropertyInfo = IsTransition
    type AttrSetTypeConstraint TransitionRemoveOnCompletePropertyInfo = (~) Bool
    type AttrTransferTypeConstraint TransitionRemoveOnCompletePropertyInfo = (~) Bool
    type AttrTransferType TransitionRemoveOnCompletePropertyInfo = Bool
    type AttrGetType TransitionRemoveOnCompletePropertyInfo = Bool
    type AttrLabel TransitionRemoveOnCompletePropertyInfo = "remove-on-complete"
    type AttrOrigin TransitionRemoveOnCompletePropertyInfo = Transition
    attrGet = getTransitionRemoveOnComplete
    attrSet = setTransitionRemoveOnComplete
    attrTransfer _ v = do
        return v
    attrConstruct = constructTransitionRemoveOnComplete
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.Transition.removeOnComplete"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.3/docs/GI-Clutter-Objects-Transition.html#g:attr:removeOnComplete"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Transition
type instance O.AttributeList Transition = TransitionAttributeList
type TransitionAttributeList = ('[ '("animatable", TransitionAnimatablePropertyInfo), '("autoReverse", Clutter.Timeline.TimelineAutoReversePropertyInfo), '("delay", Clutter.Timeline.TimelineDelayPropertyInfo), '("direction", Clutter.Timeline.TimelineDirectionPropertyInfo), '("duration", Clutter.Timeline.TimelineDurationPropertyInfo), '("interval", TransitionIntervalPropertyInfo), '("loop", Clutter.Timeline.TimelineLoopPropertyInfo), '("progressMode", Clutter.Timeline.TimelineProgressModePropertyInfo), '("removeOnComplete", TransitionRemoveOnCompletePropertyInfo), '("repeatCount", Clutter.Timeline.TimelineRepeatCountPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
transitionAnimatable :: AttrLabelProxy "animatable"
transitionAnimatable = AttrLabelProxy

transitionInterval :: AttrLabelProxy "interval"
transitionInterval = AttrLabelProxy

transitionRemoveOnComplete :: AttrLabelProxy "removeOnComplete"
transitionRemoveOnComplete = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Transition = TransitionSignalList
type TransitionSignalList = ('[ '("completed", Clutter.Timeline.TimelineCompletedSignalInfo), '("markerReached", Clutter.Timeline.TimelineMarkerReachedSignalInfo), '("newFrame", Clutter.Timeline.TimelineNewFrameSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("paused", Clutter.Timeline.TimelinePausedSignalInfo), '("started", Clutter.Timeline.TimelineStartedSignalInfo), '("stopped", Clutter.Timeline.TimelineStoppedSignalInfo)] :: [(Symbol, *)])

#endif

-- method Transition::get_animatable
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "transition"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "Transition" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterTransition"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Clutter" , name = "Animatable" })
-- throws : False
-- Skip return : False

foreign import ccall "clutter_transition_get_animatable" clutter_transition_get_animatable :: 
    Ptr Transition ->                       -- transition : TInterface (Name {namespace = "Clutter", name = "Transition"})
    IO (Ptr Clutter.Animatable.Animatable)

-- | Retrieves the t'GI.Clutter.Interfaces.Animatable.Animatable' set using 'GI.Clutter.Objects.Transition.transitionSetAnimatable'.
-- 
-- /Since: 1.10/
transitionGetAnimatable ::
    (B.CallStack.HasCallStack, MonadIO m, IsTransition a) =>
    a
    -- ^ /@transition@/: a t'GI.Clutter.Objects.Transition.Transition'
    -> m Clutter.Animatable.Animatable
    -- ^ __Returns:__ a t'GI.Clutter.Interfaces.Animatable.Animatable', or 'P.Nothing'; the returned
    --   animatable is owned by the t'GI.Clutter.Objects.Transition.Transition', and it should not be freed
    --   directly.
transitionGetAnimatable :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTransition a) =>
a -> m Animatable
transitionGetAnimatable a
transition = IO Animatable -> m Animatable
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Animatable -> m Animatable) -> IO Animatable -> m Animatable
forall a b. (a -> b) -> a -> b
$ do
    Ptr Transition
transition' <- a -> IO (Ptr Transition)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
transition
    Ptr Animatable
result <- Ptr Transition -> IO (Ptr Animatable)
clutter_transition_get_animatable Ptr Transition
transition'
    Text -> Ptr Animatable -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"transitionGetAnimatable" Ptr Animatable
result
    Animatable
result' <- ((ManagedPtr Animatable -> Animatable)
-> Ptr Animatable -> IO Animatable
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Animatable -> Animatable
Clutter.Animatable.Animatable) Ptr Animatable
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
transition
    Animatable -> IO Animatable
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Animatable
result'

#if defined(ENABLE_OVERLOADING)
data TransitionGetAnimatableMethodInfo
instance (signature ~ (m Clutter.Animatable.Animatable), MonadIO m, IsTransition a) => O.OverloadedMethod TransitionGetAnimatableMethodInfo a signature where
    overloadedMethod = transitionGetAnimatable

instance O.OverloadedMethodInfo TransitionGetAnimatableMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.Transition.transitionGetAnimatable",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.3/docs/GI-Clutter-Objects-Transition.html#v:transitionGetAnimatable"
        })


#endif

-- method Transition::get_interval
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "transition"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "Transition" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterTransition"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Clutter" , name = "Interval" })
-- throws : False
-- Skip return : False

foreign import ccall "clutter_transition_get_interval" clutter_transition_get_interval :: 
    Ptr Transition ->                       -- transition : TInterface (Name {namespace = "Clutter", name = "Transition"})
    IO (Ptr Clutter.Interval.Interval)

-- | Retrieves the interval set using 'GI.Clutter.Objects.Transition.transitionSetInterval'
-- 
-- /Since: 1.10/
transitionGetInterval ::
    (B.CallStack.HasCallStack, MonadIO m, IsTransition a) =>
    a
    -- ^ /@transition@/: a t'GI.Clutter.Objects.Transition.Transition'
    -> m Clutter.Interval.Interval
    -- ^ __Returns:__ a t'GI.Clutter.Objects.Interval.Interval', or 'P.Nothing'; the returned
    --   interval is owned by the t'GI.Clutter.Objects.Transition.Transition' and it should not be freed
    --   directly
transitionGetInterval :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTransition a) =>
a -> m Interval
transitionGetInterval a
transition = IO Interval -> m Interval
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Interval -> m Interval) -> IO Interval -> m Interval
forall a b. (a -> b) -> a -> b
$ do
    Ptr Transition
transition' <- a -> IO (Ptr Transition)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
transition
    Ptr Interval
result <- Ptr Transition -> IO (Ptr Interval)
clutter_transition_get_interval Ptr Transition
transition'
    Text -> Ptr Interval -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"transitionGetInterval" Ptr Interval
result
    Interval
result' <- ((ManagedPtr Interval -> Interval) -> Ptr Interval -> IO Interval
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Interval -> Interval
Clutter.Interval.Interval) Ptr Interval
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
transition
    Interval -> IO Interval
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Interval
result'

#if defined(ENABLE_OVERLOADING)
data TransitionGetIntervalMethodInfo
instance (signature ~ (m Clutter.Interval.Interval), MonadIO m, IsTransition a) => O.OverloadedMethod TransitionGetIntervalMethodInfo a signature where
    overloadedMethod = transitionGetInterval

instance O.OverloadedMethodInfo TransitionGetIntervalMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.Transition.transitionGetInterval",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.3/docs/GI-Clutter-Objects-Transition.html#v:transitionGetInterval"
        })


#endif

-- method Transition::get_remove_on_complete
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "transition"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "Transition" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterTransition"
--                 , 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 "clutter_transition_get_remove_on_complete" clutter_transition_get_remove_on_complete :: 
    Ptr Transition ->                       -- transition : TInterface (Name {namespace = "Clutter", name = "Transition"})
    IO CInt

-- | Retrieves the value of the [Transition:removeOnComplete]("GI.Clutter.Objects.Transition#g:attr:removeOnComplete") property.
-- 
-- /Since: 1.10/
transitionGetRemoveOnComplete ::
    (B.CallStack.HasCallStack, MonadIO m, IsTransition a) =>
    a
    -- ^ /@transition@/: a t'GI.Clutter.Objects.Transition.Transition'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the /@transition@/ should be detached when complete,
    --   and 'P.False' otherwise
transitionGetRemoveOnComplete :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTransition a) =>
a -> m Bool
transitionGetRemoveOnComplete a
transition = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Transition
transition' <- a -> IO (Ptr Transition)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
transition
    CInt
result <- Ptr Transition -> IO CInt
clutter_transition_get_remove_on_complete Ptr Transition
transition'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
transition
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TransitionGetRemoveOnCompleteMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsTransition a) => O.OverloadedMethod TransitionGetRemoveOnCompleteMethodInfo a signature where
    overloadedMethod = transitionGetRemoveOnComplete

instance O.OverloadedMethodInfo TransitionGetRemoveOnCompleteMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.Transition.transitionGetRemoveOnComplete",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.3/docs/GI-Clutter-Objects-Transition.html#v:transitionGetRemoveOnComplete"
        })


#endif

-- method Transition::set_animatable
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "transition"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "Transition" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterTransition"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "animatable"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "Animatable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterAnimatable, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "clutter_transition_set_animatable" clutter_transition_set_animatable :: 
    Ptr Transition ->                       -- transition : TInterface (Name {namespace = "Clutter", name = "Transition"})
    Ptr Clutter.Animatable.Animatable ->    -- animatable : TInterface (Name {namespace = "Clutter", name = "Animatable"})
    IO ()

-- | Sets the [Transition:animatable]("GI.Clutter.Objects.Transition#g:attr:animatable") property.
-- 
-- The /@transition@/ will acquire a reference to the /@animatable@/ instance,
-- and will call the t'GI.Clutter.Structs.TransitionClass.TransitionClass'.@/attached/@() virtual function.
-- 
-- If an existing t'GI.Clutter.Interfaces.Animatable.Animatable' is attached to /@transition@/, the
-- reference will be released, and the t'GI.Clutter.Structs.TransitionClass.TransitionClass'.@/detached/@()
-- virtual function will be called.
-- 
-- /Since: 1.10/
transitionSetAnimatable ::
    (B.CallStack.HasCallStack, MonadIO m, IsTransition a, Clutter.Animatable.IsAnimatable b) =>
    a
    -- ^ /@transition@/: a t'GI.Clutter.Objects.Transition.Transition'
    -> Maybe (b)
    -- ^ /@animatable@/: a t'GI.Clutter.Interfaces.Animatable.Animatable', or 'P.Nothing'
    -> m ()
transitionSetAnimatable :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsTransition a, IsAnimatable b) =>
a -> Maybe b -> m ()
transitionSetAnimatable a
transition Maybe b
animatable = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Transition
transition' <- a -> IO (Ptr Transition)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
transition
    Ptr Animatable
maybeAnimatable <- case Maybe b
animatable of
        Maybe b
Nothing -> Ptr Animatable -> IO (Ptr Animatable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Animatable
forall a. Ptr a
nullPtr
        Just b
jAnimatable -> do
            Ptr Animatable
jAnimatable' <- b -> IO (Ptr Animatable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jAnimatable
            Ptr Animatable -> IO (Ptr Animatable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Animatable
jAnimatable'
    Ptr Transition -> Ptr Animatable -> IO ()
clutter_transition_set_animatable Ptr Transition
transition' Ptr Animatable
maybeAnimatable
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
transition
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
animatable b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data TransitionSetAnimatableMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsTransition a, Clutter.Animatable.IsAnimatable b) => O.OverloadedMethod TransitionSetAnimatableMethodInfo a signature where
    overloadedMethod = transitionSetAnimatable

instance O.OverloadedMethodInfo TransitionSetAnimatableMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.Transition.transitionSetAnimatable",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.3/docs/GI-Clutter-Objects-Transition.html#v:transitionSetAnimatable"
        })


#endif

-- method Transition::set_from
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "transition"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "Transition" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterTransition"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TGValue
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #GValue with the initial value of the transition"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "clutter_transition_set_from_value" clutter_transition_set_from_value :: 
    Ptr Transition ->                       -- transition : TInterface (Name {namespace = "Clutter", name = "Transition"})
    Ptr GValue ->                           -- value : TGValue
    IO ()

-- | Sets the initial value of the transition.
-- 
-- This is a convenience function that will either create the
-- t'GI.Clutter.Objects.Interval.Interval' used by /@transition@/, or will update it if
-- the [Transition:interval]("GI.Clutter.Objects.Transition#g:attr:interval") is already set.
-- 
-- This function will copy the contents of /@value@/, so it is
-- safe to call 'GI.GObject.Structs.Value.valueUnset' after it returns.
-- 
-- If /@transition@/ already has a [Transition:interval]("GI.Clutter.Objects.Transition#g:attr:interval") set,
-- then /@value@/ must hold the same type, or a transformable type,
-- as the interval\'s [Interval:valueType]("GI.Clutter.Objects.Interval#g:attr:valueType") property.
-- 
-- This function is meant to be used by language bindings.
-- 
-- /Since: 1.12/
transitionSetFrom ::
    (B.CallStack.HasCallStack, MonadIO m, IsTransition a) =>
    a
    -- ^ /@transition@/: a t'GI.Clutter.Objects.Transition.Transition'
    -> GValue
    -- ^ /@value@/: a t'GI.GObject.Structs.Value.Value' with the initial value of the transition
    -> m ()
transitionSetFrom :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTransition a) =>
a -> GValue -> m ()
transitionSetFrom a
transition GValue
value = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Transition
transition' <- a -> IO (Ptr Transition)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
transition
    Ptr GValue
value' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
value
    Ptr Transition -> Ptr GValue -> IO ()
clutter_transition_set_from_value Ptr Transition
transition' Ptr GValue
value'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
transition
    GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
value
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data TransitionSetFromMethodInfo
instance (signature ~ (GValue -> m ()), MonadIO m, IsTransition a) => O.OverloadedMethod TransitionSetFromMethodInfo a signature where
    overloadedMethod = transitionSetFrom

instance O.OverloadedMethodInfo TransitionSetFromMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.Transition.transitionSetFrom",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.3/docs/GI-Clutter-Objects-Transition.html#v:transitionSetFrom"
        })


#endif

-- method Transition::set_interval
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "transition"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "Transition" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterTransition"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "interval"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "Interval" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterInterval, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "clutter_transition_set_interval" clutter_transition_set_interval :: 
    Ptr Transition ->                       -- transition : TInterface (Name {namespace = "Clutter", name = "Transition"})
    Ptr Clutter.Interval.Interval ->        -- interval : TInterface (Name {namespace = "Clutter", name = "Interval"})
    IO ()

-- | Sets the [Transition:interval]("GI.Clutter.Objects.Transition#g:attr:interval") property using /@interval@/.
-- 
-- The /@transition@/ will acquire a reference on the /@interval@/, sinking
-- the floating flag on it if necessary.
-- 
-- /Since: 1.10/
transitionSetInterval ::
    (B.CallStack.HasCallStack, MonadIO m, IsTransition a, Clutter.Interval.IsInterval b) =>
    a
    -- ^ /@transition@/: a t'GI.Clutter.Objects.Transition.Transition'
    -> Maybe (b)
    -- ^ /@interval@/: a t'GI.Clutter.Objects.Interval.Interval', or 'P.Nothing'
    -> m ()
transitionSetInterval :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsTransition a, IsInterval b) =>
a -> Maybe b -> m ()
transitionSetInterval a
transition Maybe b
interval = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Transition
transition' <- a -> IO (Ptr Transition)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
transition
    Ptr Interval
maybeInterval <- case Maybe b
interval of
        Maybe b
Nothing -> Ptr Interval -> IO (Ptr Interval)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Interval
forall a. Ptr a
nullPtr
        Just b
jInterval -> do
            Ptr Interval
jInterval' <- b -> IO (Ptr Interval)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jInterval
            Ptr Interval -> IO (Ptr Interval)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Interval
jInterval'
    Ptr Transition -> Ptr Interval -> IO ()
clutter_transition_set_interval Ptr Transition
transition' Ptr Interval
maybeInterval
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
transition
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
interval b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data TransitionSetIntervalMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsTransition a, Clutter.Interval.IsInterval b) => O.OverloadedMethod TransitionSetIntervalMethodInfo a signature where
    overloadedMethod = transitionSetInterval

instance O.OverloadedMethodInfo TransitionSetIntervalMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.Transition.transitionSetInterval",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.3/docs/GI-Clutter-Objects-Transition.html#v:transitionSetInterval"
        })


#endif

-- method Transition::set_remove_on_complete
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "transition"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "Transition" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterTransition"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "remove_complete"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "whether to detach @transition when complete"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "clutter_transition_set_remove_on_complete" clutter_transition_set_remove_on_complete :: 
    Ptr Transition ->                       -- transition : TInterface (Name {namespace = "Clutter", name = "Transition"})
    CInt ->                                 -- remove_complete : TBasicType TBoolean
    IO ()

-- | Sets whether /@transition@/ should be detached from the t'GI.Clutter.Interfaces.Animatable.Animatable'
-- set using 'GI.Clutter.Objects.Transition.transitionSetAnimatable' when the
-- [Timeline::completed]("GI.Clutter.Objects.Timeline#g:signal:completed") signal is emitted.
-- 
-- /Since: 1.10/
transitionSetRemoveOnComplete ::
    (B.CallStack.HasCallStack, MonadIO m, IsTransition a) =>
    a
    -- ^ /@transition@/: a t'GI.Clutter.Objects.Transition.Transition'
    -> Bool
    -- ^ /@removeComplete@/: whether to detach /@transition@/ when complete
    -> m ()
transitionSetRemoveOnComplete :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTransition a) =>
a -> Bool -> m ()
transitionSetRemoveOnComplete a
transition Bool
removeComplete = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Transition
transition' <- a -> IO (Ptr Transition)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
transition
    let removeComplete' :: CInt
removeComplete' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
removeComplete
    Ptr Transition -> CInt -> IO ()
clutter_transition_set_remove_on_complete Ptr Transition
transition' CInt
removeComplete'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
transition
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data TransitionSetRemoveOnCompleteMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsTransition a) => O.OverloadedMethod TransitionSetRemoveOnCompleteMethodInfo a signature where
    overloadedMethod = transitionSetRemoveOnComplete

instance O.OverloadedMethodInfo TransitionSetRemoveOnCompleteMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.Transition.transitionSetRemoveOnComplete",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.3/docs/GI-Clutter-Objects-Transition.html#v:transitionSetRemoveOnComplete"
        })


#endif

-- method Transition::set_to
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "transition"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "Transition" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterTransition"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TGValue
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #GValue with the final value of the transition"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "clutter_transition_set_to_value" clutter_transition_set_to_value :: 
    Ptr Transition ->                       -- transition : TInterface (Name {namespace = "Clutter", name = "Transition"})
    Ptr GValue ->                           -- value : TGValue
    IO ()

-- | Sets the final value of the transition.
-- 
-- This is a convenience function that will either create the
-- t'GI.Clutter.Objects.Interval.Interval' used by /@transition@/, or will update it if
-- the [Transition:interval]("GI.Clutter.Objects.Transition#g:attr:interval") is already set.
-- 
-- This function will copy the contents of /@value@/, so it is
-- safe to call 'GI.GObject.Structs.Value.valueUnset' after it returns.
-- 
-- If /@transition@/ already has a [Transition:interval]("GI.Clutter.Objects.Transition#g:attr:interval") set,
-- then /@value@/ must hold the same type, or a transformable type,
-- as the interval\'s [Interval:valueType]("GI.Clutter.Objects.Interval#g:attr:valueType") property.
-- 
-- This function is meant to be used by language bindings.
-- 
-- /Since: 1.12/
transitionSetTo ::
    (B.CallStack.HasCallStack, MonadIO m, IsTransition a) =>
    a
    -- ^ /@transition@/: a t'GI.Clutter.Objects.Transition.Transition'
    -> GValue
    -- ^ /@value@/: a t'GI.GObject.Structs.Value.Value' with the final value of the transition
    -> m ()
transitionSetTo :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTransition a) =>
a -> GValue -> m ()
transitionSetTo a
transition GValue
value = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Transition
transition' <- a -> IO (Ptr Transition)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
transition
    Ptr GValue
value' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
value
    Ptr Transition -> Ptr GValue -> IO ()
clutter_transition_set_to_value Ptr Transition
transition' Ptr GValue
value'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
transition
    GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
value
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data TransitionSetToMethodInfo
instance (signature ~ (GValue -> m ()), MonadIO m, IsTransition a) => O.OverloadedMethod TransitionSetToMethodInfo a signature where
    overloadedMethod = transitionSetTo

instance O.OverloadedMethodInfo TransitionSetToMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.Transition.transitionSetTo",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.3/docs/GI-Clutter-Objects-Transition.html#v:transitionSetTo"
        })


#endif