{-# LANGUAGE ImplicitParams, RankNTypes, 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.State.State' structure contains only
-- private data and should be accessed using the provided API
-- 
-- /Since: 1.4/

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

module GI.Clutter.Objects.State
    ( 

-- * Exported types
    State(..)                               ,
    IsState                                 ,
    toState                                 ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [parseCustomNode]("GI.Clutter.Interfaces.Scriptable#g:method:parseCustomNode"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [removeKey]("GI.Clutter.Objects.State#g:method:removeKey"), [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"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [warpToState]("GI.Clutter.Objects.State#g:method:warpToState"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getAnimator]("GI.Clutter.Objects.State#g:method:getAnimator"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getDuration]("GI.Clutter.Objects.State#g:method:getDuration"), [getId]("GI.Clutter.Interfaces.Scriptable#g:method:getId"), [getKeys]("GI.Clutter.Objects.State#g:method:getKeys"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getState]("GI.Clutter.Objects.State#g:method:getState"), [getStates]("GI.Clutter.Objects.State#g:method:getStates"), [getTimeline]("GI.Clutter.Objects.State#g:method:getTimeline").
-- 
-- ==== Setters
-- [setAnimator]("GI.Clutter.Objects.State#g:method:setAnimator"), [setCustomProperty]("GI.Clutter.Interfaces.Scriptable#g:method:setCustomProperty"), [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setDuration]("GI.Clutter.Objects.State#g:method:setDuration"), [setId]("GI.Clutter.Interfaces.Scriptable#g:method:setId"), [setKey]("GI.Clutter.Objects.State#g:method:setKey"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setState]("GI.Clutter.Objects.State#g:method:setState").

#if defined(ENABLE_OVERLOADING)
    ResolveStateMethod                      ,
#endif

-- ** getAnimator #method:getAnimator#

#if defined(ENABLE_OVERLOADING)
    StateGetAnimatorMethodInfo              ,
#endif
    stateGetAnimator                        ,


-- ** getDuration #method:getDuration#

#if defined(ENABLE_OVERLOADING)
    StateGetDurationMethodInfo              ,
#endif
    stateGetDuration                        ,


-- ** getKeys #method:getKeys#

#if defined(ENABLE_OVERLOADING)
    StateGetKeysMethodInfo                  ,
#endif
    stateGetKeys                            ,


-- ** getState #method:getState#

#if defined(ENABLE_OVERLOADING)
    StateGetStateMethodInfo                 ,
#endif
    stateGetState                           ,


-- ** getStates #method:getStates#

#if defined(ENABLE_OVERLOADING)
    StateGetStatesMethodInfo                ,
#endif
    stateGetStates                          ,


-- ** getTimeline #method:getTimeline#

#if defined(ENABLE_OVERLOADING)
    StateGetTimelineMethodInfo              ,
#endif
    stateGetTimeline                        ,


-- ** new #method:new#

    stateNew                                ,


-- ** removeKey #method:removeKey#

#if defined(ENABLE_OVERLOADING)
    StateRemoveKeyMethodInfo                ,
#endif
    stateRemoveKey                          ,


-- ** setAnimator #method:setAnimator#

#if defined(ENABLE_OVERLOADING)
    StateSetAnimatorMethodInfo              ,
#endif
    stateSetAnimator                        ,


-- ** setDuration #method:setDuration#

#if defined(ENABLE_OVERLOADING)
    StateSetDurationMethodInfo              ,
#endif
    stateSetDuration                        ,


-- ** setKey #method:setKey#

#if defined(ENABLE_OVERLOADING)
    StateSetKeyMethodInfo                   ,
#endif
    stateSetKey                             ,


-- ** setState #method:setState#

#if defined(ENABLE_OVERLOADING)
    StateSetStateMethodInfo                 ,
#endif
    stateSetState                           ,


-- ** warpToState #method:warpToState#

#if defined(ENABLE_OVERLOADING)
    StateWarpToStateMethodInfo              ,
#endif
    stateWarpToState                        ,




 -- * Properties


-- ** duration #attr:duration#
-- | Default duration used if an duration has not been specified for a specific
-- source\/target state pair. The values is in milliseconds.
-- 
-- /Since: 1.4/

#if defined(ENABLE_OVERLOADING)
    StateDurationPropertyInfo               ,
#endif
    constructStateDuration                  ,
    getStateDuration                        ,
    setStateDuration                        ,
#if defined(ENABLE_OVERLOADING)
    stateDuration                           ,
#endif


-- ** state #attr:state#
-- | The currently set target state, setting it causes the
-- state machine to transition to the new state, use
-- 'GI.Clutter.Objects.State.stateWarpToState' to change state without
-- a transition.
-- 
-- /Since: 1.4/

#if defined(ENABLE_OVERLOADING)
    StateStatePropertyInfo                  ,
#endif
    clearStateState                         ,
    constructStateState                     ,
    getStateState                           ,
    setStateState                           ,
#if defined(ENABLE_OVERLOADING)
    stateState                              ,
#endif




 -- * Signals


-- ** completed #signal:completed#

    StateCompletedCallback                  ,
#if defined(ENABLE_OVERLOADING)
    StateCompletedSignalInfo                ,
#endif
    afterStateCompleted                     ,
    onStateCompleted                        ,




    ) 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.Scriptable as Clutter.Scriptable
import {-# SOURCE #-} qualified GI.Clutter.Objects.Animator as Clutter.Animator
import {-# SOURCE #-} qualified GI.Clutter.Objects.Timeline as Clutter.Timeline
import {-# SOURCE #-} qualified GI.Clutter.Structs.StateKey as Clutter.StateKey
import qualified GI.GObject.Objects.Object as GObject.Object

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

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

foreign import ccall "clutter_state_get_type"
    c_clutter_state_get_type :: IO B.Types.GType

instance B.Types.TypedObject State where
    glibType :: IO GType
glibType = IO GType
c_clutter_state_get_type

instance B.Types.GObject State

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

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

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveStateMethod (t :: Symbol) (o :: *) :: * where
    ResolveStateMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveStateMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveStateMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveStateMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveStateMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveStateMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveStateMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveStateMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveStateMethod "parseCustomNode" o = Clutter.Scriptable.ScriptableParseCustomNodeMethodInfo
    ResolveStateMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveStateMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveStateMethod "removeKey" o = StateRemoveKeyMethodInfo
    ResolveStateMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveStateMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveStateMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveStateMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveStateMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveStateMethod "warpToState" o = StateWarpToStateMethodInfo
    ResolveStateMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveStateMethod "getAnimator" o = StateGetAnimatorMethodInfo
    ResolveStateMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveStateMethod "getDuration" o = StateGetDurationMethodInfo
    ResolveStateMethod "getId" o = Clutter.Scriptable.ScriptableGetIdMethodInfo
    ResolveStateMethod "getKeys" o = StateGetKeysMethodInfo
    ResolveStateMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveStateMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveStateMethod "getState" o = StateGetStateMethodInfo
    ResolveStateMethod "getStates" o = StateGetStatesMethodInfo
    ResolveStateMethod "getTimeline" o = StateGetTimelineMethodInfo
    ResolveStateMethod "setAnimator" o = StateSetAnimatorMethodInfo
    ResolveStateMethod "setCustomProperty" o = Clutter.Scriptable.ScriptableSetCustomPropertyMethodInfo
    ResolveStateMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveStateMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveStateMethod "setDuration" o = StateSetDurationMethodInfo
    ResolveStateMethod "setId" o = Clutter.Scriptable.ScriptableSetIdMethodInfo
    ResolveStateMethod "setKey" o = StateSetKeyMethodInfo
    ResolveStateMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveStateMethod "setState" o = StateSetStateMethodInfo
    ResolveStateMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

-- signal State::completed
{-# DEPRECATED StateCompletedCallback ["(Since version 1.12)","Use t'GI.Clutter.Objects.KeyframeTransition.KeyframeTransition' and","  t'GI.Clutter.Objects.TransitionGroup.TransitionGroup' instead"] #-}
-- | The [completed](#g:signal:completed) signal is emitted when a t'GI.Clutter.Objects.State.State' reaches
-- the target state specified by 'GI.Clutter.Objects.State.stateSetState' or
-- 'GI.Clutter.Objects.State.stateWarpToState'.
-- 
-- /Since: 1.4/
type StateCompletedCallback =
    IO ()

type C_StateCompletedCallback =
    Ptr State ->                            -- object
    Ptr () ->                               -- user_data
    IO ()

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

wrap_StateCompletedCallback :: 
    GObject a => (a -> StateCompletedCallback) ->
    C_StateCompletedCallback
wrap_StateCompletedCallback :: forall a. GObject a => (a -> IO ()) -> C_StateCompletedCallback
wrap_StateCompletedCallback a -> IO ()
gi'cb Ptr State
gi'selfPtr Ptr ()
_ = do
    Ptr State -> (State -> IO ()) -> IO ()
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr State
gi'selfPtr ((State -> IO ()) -> IO ()) -> (State -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \State
gi'self -> a -> IO ()
gi'cb (State -> a
forall a b. Coercible a b => a -> b
Coerce.coerce State
gi'self) 


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

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


#if defined(ENABLE_OVERLOADING)
data StateCompletedSignalInfo
instance SignalInfo StateCompletedSignalInfo where
    type HaskellCallbackType StateCompletedSignalInfo = StateCompletedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_StateCompletedCallback cb
        cb'' <- mk_StateCompletedCallback cb'
        connectSignalFunPtr obj "completed" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.State::completed"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.3/docs/GI-Clutter-Objects-State.html#g:signal:completed"})

#endif

-- VVV Prop "duration"
   -- Type: TBasicType TUInt
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@duration@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' state #duration
-- @
getStateDuration :: (MonadIO m, IsState o) => o -> m Word32
getStateDuration :: forall (m :: * -> *) o. (MonadIO m, IsState o) => o -> m Word32
getStateDuration o
obj = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Word32
forall a. GObject a => a -> String -> IO Word32
B.Properties.getObjectPropertyUInt32 o
obj String
"duration"

-- | Set the value of the “@duration@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' state [ #duration 'Data.GI.Base.Attributes.:=' value ]
-- @
setStateDuration :: (MonadIO m, IsState o) => o -> Word32 -> m ()
setStateDuration :: forall (m :: * -> *) o.
(MonadIO m, IsState o) =>
o -> Word32 -> m ()
setStateDuration o
obj Word32
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 -> Word32 -> IO ()
forall a. GObject a => a -> String -> Word32 -> IO ()
B.Properties.setObjectPropertyUInt32 o
obj String
"duration" Word32
val

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

#if defined(ENABLE_OVERLOADING)
data StateDurationPropertyInfo
instance AttrInfo StateDurationPropertyInfo where
    type AttrAllowedOps StateDurationPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint StateDurationPropertyInfo = IsState
    type AttrSetTypeConstraint StateDurationPropertyInfo = (~) Word32
    type AttrTransferTypeConstraint StateDurationPropertyInfo = (~) Word32
    type AttrTransferType StateDurationPropertyInfo = Word32
    type AttrGetType StateDurationPropertyInfo = Word32
    type AttrLabel StateDurationPropertyInfo = "duration"
    type AttrOrigin StateDurationPropertyInfo = State
    attrGet = getStateDuration
    attrSet = setStateDuration
    attrTransfer _ v = do
        return v
    attrConstruct = constructStateDuration
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.State.duration"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.3/docs/GI-Clutter-Objects-State.html#g:attr:duration"
        })
#endif

-- VVV Prop "state"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@state@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' state #state
-- @
getStateState :: (MonadIO m, IsState o) => o -> m T.Text
getStateState :: forall (m :: * -> *) o. (MonadIO m, IsState o) => o -> m Text
getStateState o
obj = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Text) -> IO Text
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getStateState" (IO (Maybe Text) -> IO Text) -> IO (Maybe Text) -> IO 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
"state"

-- | Set the value of the “@state@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' state [ #state 'Data.GI.Base.Attributes.:=' value ]
-- @
setStateState :: (MonadIO m, IsState o) => o -> T.Text -> m ()
setStateState :: forall (m :: * -> *) o. (MonadIO m, IsState o) => o -> Text -> m ()
setStateState o
obj Text
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 Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"state" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Construct a `GValueConstruct` with valid value for the “@state@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructStateState :: (IsState o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructStateState :: forall o (m :: * -> *).
(IsState o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructStateState 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
"state" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

-- | Set the value of the “@state@” 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' #state
-- @
clearStateState :: (MonadIO m, IsState o) => o -> m ()
clearStateState :: forall (m :: * -> *) o. (MonadIO m, IsState o) => o -> m ()
clearStateState 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 Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"state" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

#if defined(ENABLE_OVERLOADING)
data StateStatePropertyInfo
instance AttrInfo StateStatePropertyInfo where
    type AttrAllowedOps StateStatePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint StateStatePropertyInfo = IsState
    type AttrSetTypeConstraint StateStatePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint StateStatePropertyInfo = (~) T.Text
    type AttrTransferType StateStatePropertyInfo = T.Text
    type AttrGetType StateStatePropertyInfo = T.Text
    type AttrLabel StateStatePropertyInfo = "state"
    type AttrOrigin StateStatePropertyInfo = State
    attrGet = getStateState
    attrSet = setStateState
    attrTransfer _ v = do
        return v
    attrConstruct = constructStateState
    attrClear = clearStateState
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.State.state"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.3/docs/GI-Clutter-Objects-State.html#g:attr:state"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList State
type instance O.AttributeList State = StateAttributeList
type StateAttributeList = ('[ '("duration", StateDurationPropertyInfo), '("state", StateStatePropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
stateDuration :: AttrLabelProxy "duration"
stateDuration = AttrLabelProxy

stateState :: AttrLabelProxy "state"
stateState = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList State = StateSignalList
type StateSignalList = ('[ '("completed", StateCompletedSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif

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

foreign import ccall "clutter_state_new" clutter_state_new :: 
    IO (Ptr State)

{-# DEPRECATED stateNew ["(Since version 1.12)","Use t'GI.Clutter.Objects.KeyframeTransition.KeyframeTransition' and","  t'GI.Clutter.Objects.TransitionGroup.TransitionGroup' instead"] #-}
-- | Creates a new t'GI.Clutter.Objects.State.State'
-- 
-- /Since: 1.4/
stateNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m State
    -- ^ __Returns:__ the newly create t'GI.Clutter.Objects.State.State' instance
stateNew :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m State
stateNew  = IO State -> m State
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO State -> m State) -> IO State -> m State
forall a b. (a -> b) -> a -> b
$ do
    Ptr State
result <- IO (Ptr State)
clutter_state_new
    Text -> Ptr State -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"stateNew" Ptr State
result
    State
result' <- ((ManagedPtr State -> State) -> Ptr State -> IO State
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr State -> State
State) Ptr State
result
    State -> IO State
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return State
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method State::get_animator
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "state"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "State" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterState instance."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "source_state_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the name of a source state"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "target_state_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the name of a target state"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Clutter" , name = "Animator" })
-- throws : False
-- Skip return : False

foreign import ccall "clutter_state_get_animator" clutter_state_get_animator :: 
    Ptr State ->                            -- state : TInterface (Name {namespace = "Clutter", name = "State"})
    CString ->                              -- source_state_name : TBasicType TUTF8
    CString ->                              -- target_state_name : TBasicType TUTF8
    IO (Ptr Clutter.Animator.Animator)

{-# DEPRECATED stateGetAnimator ["(Since version 1.12)","Use t'GI.Clutter.Objects.KeyframeTransition.KeyframeTransition' and","  t'GI.Clutter.Objects.TransitionGroup.TransitionGroup' instead"] #-}
-- | Retrieves the t'GI.Clutter.Objects.Animator.Animator' that is being used for transitioning
-- between the two states, if any has been set
-- 
-- /Since: 1.4/
stateGetAnimator ::
    (B.CallStack.HasCallStack, MonadIO m, IsState a) =>
    a
    -- ^ /@state@/: a t'GI.Clutter.Objects.State.State' instance.
    -> T.Text
    -- ^ /@sourceStateName@/: the name of a source state
    -> T.Text
    -- ^ /@targetStateName@/: the name of a target state
    -> m Clutter.Animator.Animator
    -- ^ __Returns:__ a t'GI.Clutter.Objects.Animator.Animator' instance, or 'P.Nothing'
stateGetAnimator :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsState a) =>
a -> Text -> Text -> m Animator
stateGetAnimator a
state Text
sourceStateName Text
targetStateName = IO Animator -> m Animator
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Animator -> m Animator) -> IO Animator -> m Animator
forall a b. (a -> b) -> a -> b
$ do
    Ptr State
state' <- a -> IO (Ptr State)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
state
    CString
sourceStateName' <- Text -> IO CString
textToCString Text
sourceStateName
    CString
targetStateName' <- Text -> IO CString
textToCString Text
targetStateName
    Ptr Animator
result <- Ptr State -> CString -> CString -> IO (Ptr Animator)
clutter_state_get_animator Ptr State
state' CString
sourceStateName' CString
targetStateName'
    Text -> Ptr Animator -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"stateGetAnimator" Ptr Animator
result
    Animator
result' <- ((ManagedPtr Animator -> Animator) -> Ptr Animator -> IO Animator
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Animator -> Animator
Clutter.Animator.Animator) Ptr Animator
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
state
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
sourceStateName'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
targetStateName'
    Animator -> IO Animator
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Animator
result'

#if defined(ENABLE_OVERLOADING)
data StateGetAnimatorMethodInfo
instance (signature ~ (T.Text -> T.Text -> m Clutter.Animator.Animator), MonadIO m, IsState a) => O.OverloadedMethod StateGetAnimatorMethodInfo a signature where
    overloadedMethod = stateGetAnimator

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


#endif

-- method State::get_duration
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "state"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "State" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterState" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "source_state_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the name of the source state to\n  get the duration of, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "target_state_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the name of the source state to\n  get the duration of, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt)
-- throws : False
-- Skip return : False

foreign import ccall "clutter_state_get_duration" clutter_state_get_duration :: 
    Ptr State ->                            -- state : TInterface (Name {namespace = "Clutter", name = "State"})
    CString ->                              -- source_state_name : TBasicType TUTF8
    CString ->                              -- target_state_name : TBasicType TUTF8
    IO Word32

{-# DEPRECATED stateGetDuration ["(Since version 1.12)","Use t'GI.Clutter.Objects.KeyframeTransition.KeyframeTransition' and","  t'GI.Clutter.Objects.TransitionGroup.TransitionGroup' instead"] #-}
-- | Queries the duration used for transitions between a source and
-- target state pair
-- 
-- The semantics for the query are the same as the semantics used for
-- setting the duration with 'GI.Clutter.Objects.State.stateSetDuration'
-- 
-- /Since: 1.4/
stateGetDuration ::
    (B.CallStack.HasCallStack, MonadIO m, IsState a) =>
    a
    -- ^ /@state@/: a t'GI.Clutter.Objects.State.State'
    -> Maybe (T.Text)
    -- ^ /@sourceStateName@/: the name of the source state to
    --   get the duration of, or 'P.Nothing'
    -> Maybe (T.Text)
    -- ^ /@targetStateName@/: the name of the source state to
    --   get the duration of, or 'P.Nothing'
    -> m Word32
    -- ^ __Returns:__ the duration, in milliseconds
stateGetDuration :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsState a) =>
a -> Maybe Text -> Maybe Text -> m Word32
stateGetDuration a
state Maybe Text
sourceStateName Maybe Text
targetStateName = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    Ptr State
state' <- a -> IO (Ptr State)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
state
    CString
maybeSourceStateName <- case Maybe Text
sourceStateName of
        Maybe Text
Nothing -> CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just Text
jSourceStateName -> do
            CString
jSourceStateName' <- Text -> IO CString
textToCString Text
jSourceStateName
            CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jSourceStateName'
    CString
maybeTargetStateName <- case Maybe Text
targetStateName of
        Maybe Text
Nothing -> CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just Text
jTargetStateName -> do
            CString
jTargetStateName' <- Text -> IO CString
textToCString Text
jTargetStateName
            CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jTargetStateName'
    Word32
result <- Ptr State -> CString -> CString -> IO Word32
clutter_state_get_duration Ptr State
state' CString
maybeSourceStateName CString
maybeTargetStateName
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
state
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeSourceStateName
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeTargetStateName
    Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data StateGetDurationMethodInfo
instance (signature ~ (Maybe (T.Text) -> Maybe (T.Text) -> m Word32), MonadIO m, IsState a) => O.OverloadedMethod StateGetDurationMethodInfo a signature where
    overloadedMethod = stateGetDuration

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


#endif

-- method State::get_keys
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "state"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "State" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterState instance."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "source_state_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the source transition name to query,\n  or %NULL for all source states"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "target_state_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the target transition name to query,\n  or %NULL for all target states"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "object"
--           , argType =
--               TInterface Name { namespace = "GObject" , name = "Object" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the specific object instance to list keys for,\n  or %NULL for all managed objects"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "property_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the property name to search for, or %NULL\n  for all properties."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TGList
--                  (TInterface Name { namespace = "Clutter" , name = "StateKey" }))
-- throws : False
-- Skip return : False

foreign import ccall "clutter_state_get_keys" clutter_state_get_keys :: 
    Ptr State ->                            -- state : TInterface (Name {namespace = "Clutter", name = "State"})
    CString ->                              -- source_state_name : TBasicType TUTF8
    CString ->                              -- target_state_name : TBasicType TUTF8
    Ptr GObject.Object.Object ->            -- object : TInterface (Name {namespace = "GObject", name = "Object"})
    CString ->                              -- property_name : TBasicType TUTF8
    IO (Ptr (GList (Ptr Clutter.StateKey.StateKey)))

{-# DEPRECATED stateGetKeys ["(Since version 1.12)","Use t'GI.Clutter.Objects.KeyframeTransition.KeyframeTransition' and","  t'GI.Clutter.Objects.TransitionGroup.TransitionGroup' instead"] #-}
-- | Returns a list of pointers to opaque structures with accessor functions
-- that describe the keys added to an animator.
-- 
-- /Since: 1.4/
stateGetKeys ::
    (B.CallStack.HasCallStack, MonadIO m, IsState a, GObject.Object.IsObject b) =>
    a
    -- ^ /@state@/: a t'GI.Clutter.Objects.State.State' instance.
    -> Maybe (T.Text)
    -- ^ /@sourceStateName@/: the source transition name to query,
    --   or 'P.Nothing' for all source states
    -> Maybe (T.Text)
    -- ^ /@targetStateName@/: the target transition name to query,
    --   or 'P.Nothing' for all target states
    -> Maybe (b)
    -- ^ /@object@/: the specific object instance to list keys for,
    --   or 'P.Nothing' for all managed objects
    -> Maybe (T.Text)
    -- ^ /@propertyName@/: the property name to search for, or 'P.Nothing'
    --   for all properties.
    -> m [Clutter.StateKey.StateKey]
    -- ^ __Returns:__ a
    --   newly allocated t'GI.GLib.Structs.List.List' of t'GI.Clutter.Structs.StateKey.StateKey's. The contents of
    --   the returned list are owned by the t'GI.Clutter.Objects.State.State' and should not be
    --   modified or freed. Use @/g_list_free()/@ to free the resources allocated
    --   by the returned list when done using it
stateGetKeys :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsState a, IsObject b) =>
a
-> Maybe Text
-> Maybe Text
-> Maybe b
-> Maybe Text
-> m [StateKey]
stateGetKeys a
state Maybe Text
sourceStateName Maybe Text
targetStateName Maybe b
object Maybe Text
propertyName = IO [StateKey] -> m [StateKey]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [StateKey] -> m [StateKey]) -> IO [StateKey] -> m [StateKey]
forall a b. (a -> b) -> a -> b
$ do
    Ptr State
state' <- a -> IO (Ptr State)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
state
    CString
maybeSourceStateName <- case Maybe Text
sourceStateName of
        Maybe Text
Nothing -> CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just Text
jSourceStateName -> do
            CString
jSourceStateName' <- Text -> IO CString
textToCString Text
jSourceStateName
            CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jSourceStateName'
    CString
maybeTargetStateName <- case Maybe Text
targetStateName of
        Maybe Text
Nothing -> CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just Text
jTargetStateName -> do
            CString
jTargetStateName' <- Text -> IO CString
textToCString Text
jTargetStateName
            CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jTargetStateName'
    Ptr Object
maybeObject <- case Maybe b
object of
        Maybe b
Nothing -> Ptr Object -> IO (Ptr Object)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Object
forall a. Ptr a
nullPtr
        Just b
jObject -> do
            Ptr Object
jObject' <- b -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jObject
            Ptr Object -> IO (Ptr Object)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Object
jObject'
    CString
maybePropertyName <- case Maybe Text
propertyName of
        Maybe Text
Nothing -> CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just Text
jPropertyName -> do
            CString
jPropertyName' <- Text -> IO CString
textToCString Text
jPropertyName
            CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jPropertyName'
    Ptr (GList (Ptr StateKey))
result <- Ptr State
-> CString
-> CString
-> Ptr Object
-> CString
-> IO (Ptr (GList (Ptr StateKey)))
clutter_state_get_keys Ptr State
state' CString
maybeSourceStateName CString
maybeTargetStateName Ptr Object
maybeObject CString
maybePropertyName
    [Ptr StateKey]
result' <- Ptr (GList (Ptr StateKey)) -> IO [Ptr StateKey]
forall a. Ptr (GList (Ptr a)) -> IO [Ptr a]
unpackGList Ptr (GList (Ptr StateKey))
result
    [StateKey]
result'' <- (Ptr StateKey -> IO StateKey) -> [Ptr StateKey] -> IO [StateKey]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM ((ManagedPtr StateKey -> StateKey) -> Ptr StateKey -> IO StateKey
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr StateKey -> StateKey
Clutter.StateKey.StateKey) [Ptr StateKey]
result'
    Ptr (GList (Ptr StateKey)) -> IO ()
forall a. Ptr (GList a) -> IO ()
g_list_free Ptr (GList (Ptr StateKey))
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
state
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
object b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeSourceStateName
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeTargetStateName
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybePropertyName
    [StateKey] -> IO [StateKey]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [StateKey]
result''

#if defined(ENABLE_OVERLOADING)
data StateGetKeysMethodInfo
instance (signature ~ (Maybe (T.Text) -> Maybe (T.Text) -> Maybe (b) -> Maybe (T.Text) -> m [Clutter.StateKey.StateKey]), MonadIO m, IsState a, GObject.Object.IsObject b) => O.OverloadedMethod StateGetKeysMethodInfo a signature where
    overloadedMethod = stateGetKeys

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


#endif

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

foreign import ccall "clutter_state_get_state" clutter_state_get_state :: 
    Ptr State ->                            -- state : TInterface (Name {namespace = "Clutter", name = "State"})
    IO CString

{-# DEPRECATED stateGetState ["(Since version 1.12)","Use t'GI.Clutter.Objects.KeyframeTransition.KeyframeTransition' and","  t'GI.Clutter.Objects.TransitionGroup.TransitionGroup' instead"] #-}
-- | Queries the currently set target state.
-- 
-- During a transition this function will return the target of the transition.
-- 
-- This function is useful when called from handlers of the
-- [State::completed]("GI.Clutter.Objects.State#g:signal:completed") signal.
-- 
-- /Since: 1.4/
stateGetState ::
    (B.CallStack.HasCallStack, MonadIO m, IsState a) =>
    a
    -- ^ /@state@/: a t'GI.Clutter.Objects.State.State'
    -> m T.Text
    -- ^ __Returns:__ a string containing the target state. The returned string
    --   is owned by the t'GI.Clutter.Objects.State.State' and should not be modified or freed
stateGetState :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsState a) =>
a -> m Text
stateGetState a
state = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr State
state' <- a -> IO (Ptr State)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
state
    CString
result <- Ptr State -> IO CString
clutter_state_get_state Ptr State
state'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"stateGetState" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
state
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data StateGetStateMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsState a) => O.OverloadedMethod StateGetStateMethodInfo a signature where
    overloadedMethod = stateGetState

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


#endif

-- method State::get_states
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "state"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "State" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterState instance."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TGList (TBasicType TUTF8))
-- throws : False
-- Skip return : False

foreign import ccall "clutter_state_get_states" clutter_state_get_states :: 
    Ptr State ->                            -- state : TInterface (Name {namespace = "Clutter", name = "State"})
    IO (Ptr (GList CString))

{-# DEPRECATED stateGetStates ["(Since version 1.12)","Use t'GI.Clutter.Objects.KeyframeTransition.KeyframeTransition' and","  t'GI.Clutter.Objects.TransitionGroup.TransitionGroup' instead"] #-}
-- | Gets a list of all the state names managed by this t'GI.Clutter.Objects.State.State'.
-- 
-- /Since: 1.4/
stateGetStates ::
    (B.CallStack.HasCallStack, MonadIO m, IsState a) =>
    a
    -- ^ /@state@/: a t'GI.Clutter.Objects.State.State' instance.
    -> m [T.Text]
    -- ^ __Returns:__ a newly allocated
    --   t'GI.GLib.Structs.List.List' of state names. The contents of the returned t'GI.GLib.Structs.List.List' are owned
    --   by the t'GI.Clutter.Objects.State.State' and should not be modified or freed. Use
    --   @/g_list_free()/@ to free the resources allocated by the returned list when
    --   done using it
stateGetStates :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsState a) =>
a -> m [Text]
stateGetStates a
state = IO [Text] -> m [Text]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Text] -> m [Text]) -> IO [Text] -> m [Text]
forall a b. (a -> b) -> a -> b
$ do
    Ptr State
state' <- a -> IO (Ptr State)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
state
    Ptr (GList CString)
result <- Ptr State -> IO (Ptr (GList CString))
clutter_state_get_states Ptr State
state'
    [CString]
result' <- Ptr (GList CString) -> IO [CString]
forall a. Ptr (GList (Ptr a)) -> IO [Ptr a]
unpackGList Ptr (GList CString)
result
    [Text]
result'' <- (CString -> IO Text) -> [CString] -> IO [Text]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText [CString]
result'
    Ptr (GList CString) -> IO ()
forall a. Ptr (GList a) -> IO ()
g_list_free Ptr (GList CString)
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
state
    [Text] -> IO [Text]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [Text]
result''

#if defined(ENABLE_OVERLOADING)
data StateGetStatesMethodInfo
instance (signature ~ (m [T.Text]), MonadIO m, IsState a) => O.OverloadedMethod StateGetStatesMethodInfo a signature where
    overloadedMethod = stateGetStates

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


#endif

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

foreign import ccall "clutter_state_get_timeline" clutter_state_get_timeline :: 
    Ptr State ->                            -- state : TInterface (Name {namespace = "Clutter", name = "State"})
    IO (Ptr Clutter.Timeline.Timeline)

{-# DEPRECATED stateGetTimeline ["(Since version 1.12)","Use t'GI.Clutter.Objects.KeyframeTransition.KeyframeTransition' and","  t'GI.Clutter.Objects.TransitionGroup.TransitionGroup' instead"] #-}
-- | Gets the timeline driving the t'GI.Clutter.Objects.State.State'
-- 
-- /Since: 1.4/
stateGetTimeline ::
    (B.CallStack.HasCallStack, MonadIO m, IsState a) =>
    a
    -- ^ /@state@/: a t'GI.Clutter.Objects.State.State'
    -> m Clutter.Timeline.Timeline
    -- ^ __Returns:__ the t'GI.Clutter.Objects.Timeline.Timeline' that drives
    --   the state change animations. The returned timeline is owned
    --   by the t'GI.Clutter.Objects.State.State' and it should not be unreferenced directly
stateGetTimeline :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsState a) =>
a -> m Timeline
stateGetTimeline a
state = IO Timeline -> m Timeline
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Timeline -> m Timeline) -> IO Timeline -> m Timeline
forall a b. (a -> b) -> a -> b
$ do
    Ptr State
state' <- a -> IO (Ptr State)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
state
    Ptr Timeline
result <- Ptr State -> IO (Ptr Timeline)
clutter_state_get_timeline Ptr State
state'
    Text -> Ptr Timeline -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"stateGetTimeline" Ptr Timeline
result
    Timeline
result' <- ((ManagedPtr Timeline -> Timeline) -> Ptr Timeline -> IO Timeline
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Timeline -> Timeline
Clutter.Timeline.Timeline) Ptr Timeline
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
state
    Timeline -> IO Timeline
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Timeline
result'

#if defined(ENABLE_OVERLOADING)
data StateGetTimelineMethodInfo
instance (signature ~ (m Clutter.Timeline.Timeline), MonadIO m, IsState a) => O.OverloadedMethod StateGetTimelineMethodInfo a signature where
    overloadedMethod = stateGetTimeline

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


#endif

-- method State::remove_key
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "state"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "State" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterState instance."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "source_state_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the source state name to query,\n  or %NULL for all source states"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "target_state_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the target state name to query,\n  or %NULL for all target states"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "object"
--           , argType =
--               TInterface Name { namespace = "GObject" , name = "Object" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the specific object instance to list keys for,\n  or %NULL for all managed objects"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "property_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the property name to search for,\n  or %NULL for all properties."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "clutter_state_remove_key" clutter_state_remove_key :: 
    Ptr State ->                            -- state : TInterface (Name {namespace = "Clutter", name = "State"})
    CString ->                              -- source_state_name : TBasicType TUTF8
    CString ->                              -- target_state_name : TBasicType TUTF8
    Ptr GObject.Object.Object ->            -- object : TInterface (Name {namespace = "GObject", name = "Object"})
    CString ->                              -- property_name : TBasicType TUTF8
    IO ()

{-# DEPRECATED stateRemoveKey ["(Since version 1.12)","Use t'GI.Clutter.Objects.KeyframeTransition.KeyframeTransition' and","  t'GI.Clutter.Objects.TransitionGroup.TransitionGroup' instead"] #-}
-- | Removes all keys matching the search criteria passed in arguments.
-- 
-- /Since: 1.4/
stateRemoveKey ::
    (B.CallStack.HasCallStack, MonadIO m, IsState a, GObject.Object.IsObject b) =>
    a
    -- ^ /@state@/: a t'GI.Clutter.Objects.State.State' instance.
    -> Maybe (T.Text)
    -- ^ /@sourceStateName@/: the source state name to query,
    --   or 'P.Nothing' for all source states
    -> Maybe (T.Text)
    -- ^ /@targetStateName@/: the target state name to query,
    --   or 'P.Nothing' for all target states
    -> Maybe (b)
    -- ^ /@object@/: the specific object instance to list keys for,
    --   or 'P.Nothing' for all managed objects
    -> Maybe (T.Text)
    -- ^ /@propertyName@/: the property name to search for,
    --   or 'P.Nothing' for all properties.
    -> m ()
stateRemoveKey :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsState a, IsObject b) =>
a -> Maybe Text -> Maybe Text -> Maybe b -> Maybe Text -> m ()
stateRemoveKey a
state Maybe Text
sourceStateName Maybe Text
targetStateName Maybe b
object Maybe Text
propertyName = 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 State
state' <- a -> IO (Ptr State)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
state
    CString
maybeSourceStateName <- case Maybe Text
sourceStateName of
        Maybe Text
Nothing -> CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just Text
jSourceStateName -> do
            CString
jSourceStateName' <- Text -> IO CString
textToCString Text
jSourceStateName
            CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jSourceStateName'
    CString
maybeTargetStateName <- case Maybe Text
targetStateName of
        Maybe Text
Nothing -> CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just Text
jTargetStateName -> do
            CString
jTargetStateName' <- Text -> IO CString
textToCString Text
jTargetStateName
            CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jTargetStateName'
    Ptr Object
maybeObject <- case Maybe b
object of
        Maybe b
Nothing -> Ptr Object -> IO (Ptr Object)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Object
forall a. Ptr a
nullPtr
        Just b
jObject -> do
            Ptr Object
jObject' <- b -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jObject
            Ptr Object -> IO (Ptr Object)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Object
jObject'
    CString
maybePropertyName <- case Maybe Text
propertyName of
        Maybe Text
Nothing -> CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just Text
jPropertyName -> do
            CString
jPropertyName' <- Text -> IO CString
textToCString Text
jPropertyName
            CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jPropertyName'
    Ptr State -> CString -> CString -> Ptr Object -> CString -> IO ()
clutter_state_remove_key Ptr State
state' CString
maybeSourceStateName CString
maybeTargetStateName Ptr Object
maybeObject CString
maybePropertyName
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
state
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
object b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeSourceStateName
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeTargetStateName
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybePropertyName
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data StateRemoveKeyMethodInfo
instance (signature ~ (Maybe (T.Text) -> Maybe (T.Text) -> Maybe (b) -> Maybe (T.Text) -> m ()), MonadIO m, IsState a, GObject.Object.IsObject b) => O.OverloadedMethod StateRemoveKeyMethodInfo a signature where
    overloadedMethod = stateRemoveKey

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


#endif

-- method State::set_animator
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "state"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "State" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterState instance."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "source_state_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the name of a source state"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "target_state_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the name of a target state"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "animator"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "Animator" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a #ClutterAnimator instance, or %NULL to\n  unset an existing #ClutterAnimator"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "clutter_state_set_animator" clutter_state_set_animator :: 
    Ptr State ->                            -- state : TInterface (Name {namespace = "Clutter", name = "State"})
    CString ->                              -- source_state_name : TBasicType TUTF8
    CString ->                              -- target_state_name : TBasicType TUTF8
    Ptr Clutter.Animator.Animator ->        -- animator : TInterface (Name {namespace = "Clutter", name = "Animator"})
    IO ()

{-# DEPRECATED stateSetAnimator ["(Since version 1.12)","Use t'GI.Clutter.Objects.KeyframeTransition.KeyframeTransition' and","  t'GI.Clutter.Objects.TransitionGroup.TransitionGroup' instead"] #-}
-- | Specifies a t'GI.Clutter.Objects.Animator.Animator' to be used when transitioning between
-- the two named states.
-- 
-- The /@animator@/ allows specifying a transition between the state that is
-- more elaborate than the basic transitions allowed by the tweening of
-- properties defined in the t'GI.Clutter.Objects.State.State' keys.
-- 
-- If /@animator@/ is 'P.Nothing' it will unset an existing animator.
-- 
-- t'GI.Clutter.Objects.State.State' will take a reference on the passed /@animator@/, if any
-- 
-- /Since: 1.4/
stateSetAnimator ::
    (B.CallStack.HasCallStack, MonadIO m, IsState a, Clutter.Animator.IsAnimator b) =>
    a
    -- ^ /@state@/: a t'GI.Clutter.Objects.State.State' instance.
    -> T.Text
    -- ^ /@sourceStateName@/: the name of a source state
    -> T.Text
    -- ^ /@targetStateName@/: the name of a target state
    -> Maybe (b)
    -- ^ /@animator@/: a t'GI.Clutter.Objects.Animator.Animator' instance, or 'P.Nothing' to
    --   unset an existing t'GI.Clutter.Objects.Animator.Animator'
    -> m ()
stateSetAnimator :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsState a, IsAnimator b) =>
a -> Text -> Text -> Maybe b -> m ()
stateSetAnimator a
state Text
sourceStateName Text
targetStateName Maybe b
animator = 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 State
state' <- a -> IO (Ptr State)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
state
    CString
sourceStateName' <- Text -> IO CString
textToCString Text
sourceStateName
    CString
targetStateName' <- Text -> IO CString
textToCString Text
targetStateName
    Ptr Animator
maybeAnimator <- case Maybe b
animator of
        Maybe b
Nothing -> Ptr Animator -> IO (Ptr Animator)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Animator
forall a. Ptr a
nullPtr
        Just b
jAnimator -> do
            Ptr Animator
jAnimator' <- b -> IO (Ptr Animator)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jAnimator
            Ptr Animator -> IO (Ptr Animator)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Animator
jAnimator'
    Ptr State -> CString -> CString -> Ptr Animator -> IO ()
clutter_state_set_animator Ptr State
state' CString
sourceStateName' CString
targetStateName' Ptr Animator
maybeAnimator
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
state
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
animator b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
sourceStateName'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
targetStateName'
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data StateSetAnimatorMethodInfo
instance (signature ~ (T.Text -> T.Text -> Maybe (b) -> m ()), MonadIO m, IsState a, Clutter.Animator.IsAnimator b) => O.OverloadedMethod StateSetAnimatorMethodInfo a signature where
    overloadedMethod = stateSetAnimator

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


#endif

-- method State::set_duration
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "state"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "State" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterState" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "source_state_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the name of the source state, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "target_state_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the name of the target state, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "duration"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the duration of the transition, in milliseconds"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "clutter_state_set_duration" clutter_state_set_duration :: 
    Ptr State ->                            -- state : TInterface (Name {namespace = "Clutter", name = "State"})
    CString ->                              -- source_state_name : TBasicType TUTF8
    CString ->                              -- target_state_name : TBasicType TUTF8
    Word32 ->                               -- duration : TBasicType TUInt
    IO ()

{-# DEPRECATED stateSetDuration ["(Since version 1.12)","Use t'GI.Clutter.Objects.KeyframeTransition.KeyframeTransition' and","  t'GI.Clutter.Objects.TransitionGroup.TransitionGroup' instead"] #-}
-- | Sets the duration of a transition.
-- 
-- If both state names are 'P.Nothing' the default duration for /@state@/ is set.
-- 
-- If only /@targetStateName@/ is specified, the passed /@duration@/ becomes
-- the default duration for transitions to the target state.
-- 
-- If both states names are specified, the passed /@duration@/ only applies
-- to the specified transition.
-- 
-- /Since: 1.4/
stateSetDuration ::
    (B.CallStack.HasCallStack, MonadIO m, IsState a) =>
    a
    -- ^ /@state@/: a t'GI.Clutter.Objects.State.State'
    -> Maybe (T.Text)
    -- ^ /@sourceStateName@/: the name of the source state, or 'P.Nothing'
    -> Maybe (T.Text)
    -- ^ /@targetStateName@/: the name of the target state, or 'P.Nothing'
    -> Word32
    -- ^ /@duration@/: the duration of the transition, in milliseconds
    -> m ()
stateSetDuration :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsState a) =>
a -> Maybe Text -> Maybe Text -> Word32 -> m ()
stateSetDuration a
state Maybe Text
sourceStateName Maybe Text
targetStateName Word32
duration = 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 State
state' <- a -> IO (Ptr State)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
state
    CString
maybeSourceStateName <- case Maybe Text
sourceStateName of
        Maybe Text
Nothing -> CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just Text
jSourceStateName -> do
            CString
jSourceStateName' <- Text -> IO CString
textToCString Text
jSourceStateName
            CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jSourceStateName'
    CString
maybeTargetStateName <- case Maybe Text
targetStateName of
        Maybe Text
Nothing -> CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just Text
jTargetStateName -> do
            CString
jTargetStateName' <- Text -> IO CString
textToCString Text
jTargetStateName
            CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jTargetStateName'
    Ptr State -> CString -> CString -> Word32 -> IO ()
clutter_state_set_duration Ptr State
state' CString
maybeSourceStateName CString
maybeTargetStateName Word32
duration
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
state
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeSourceStateName
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeTargetStateName
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data StateSetDurationMethodInfo
instance (signature ~ (Maybe (T.Text) -> Maybe (T.Text) -> Word32 -> m ()), MonadIO m, IsState a) => O.OverloadedMethod StateSetDurationMethodInfo a signature where
    overloadedMethod = stateSetDuration

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


#endif

-- method State::set_key
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "state"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "State" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterState instance."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "source_state_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the source transition to specify\n  transition for, or %NULL to specify the default fallback when a\n  more specific source state doesn't exist."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "target_state_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the name of the transition to set a key value for."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "object"
--           , argType =
--               TInterface Name { namespace = "GObject" , name = "Object" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #GObject to set a key for"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "property_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the property to set a key for"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "mode"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the id of the alpha function to use"
--                 , 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 "the value for property_name of object in state_name"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "pre_delay"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "relative time of the transition to be idle in the beginning\n  of the transition"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "post_delay"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "relative time of the transition to be idle in the end of\n  the transition"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Clutter" , name = "State" })
-- throws : False
-- Skip return : False

foreign import ccall "clutter_state_set_key" clutter_state_set_key :: 
    Ptr State ->                            -- state : TInterface (Name {namespace = "Clutter", name = "State"})
    CString ->                              -- source_state_name : TBasicType TUTF8
    CString ->                              -- target_state_name : TBasicType TUTF8
    Ptr GObject.Object.Object ->            -- object : TInterface (Name {namespace = "GObject", name = "Object"})
    CString ->                              -- property_name : TBasicType TUTF8
    Word32 ->                               -- mode : TBasicType TUInt
    Ptr GValue ->                           -- value : TGValue
    CDouble ->                              -- pre_delay : TBasicType TDouble
    CDouble ->                              -- post_delay : TBasicType TDouble
    IO (Ptr State)

{-# DEPRECATED stateSetKey ["(Since version 1.12)","Use t'GI.Clutter.Objects.KeyframeTransition.KeyframeTransition' and","  t'GI.Clutter.Objects.TransitionGroup.TransitionGroup' instead"] #-}
-- | Sets one specific end key for a state name, /@object@/, /@propertyName@/
-- combination.
-- 
-- /Since: 1.4/
stateSetKey ::
    (B.CallStack.HasCallStack, MonadIO m, IsState a, GObject.Object.IsObject b) =>
    a
    -- ^ /@state@/: a t'GI.Clutter.Objects.State.State' instance.
    -> Maybe (T.Text)
    -- ^ /@sourceStateName@/: the source transition to specify
    --   transition for, or 'P.Nothing' to specify the default fallback when a
    --   more specific source state doesn\'t exist.
    -> T.Text
    -- ^ /@targetStateName@/: the name of the transition to set a key value for.
    -> b
    -- ^ /@object@/: the t'GI.GObject.Objects.Object.Object' to set a key for
    -> T.Text
    -- ^ /@propertyName@/: the property to set a key for
    -> Word32
    -- ^ /@mode@/: the id of the alpha function to use
    -> GValue
    -- ^ /@value@/: the value for property_name of object in state_name
    -> Double
    -- ^ /@preDelay@/: relative time of the transition to be idle in the beginning
    --   of the transition
    -> Double
    -- ^ /@postDelay@/: relative time of the transition to be idle in the end of
    --   the transition
    -> m State
    -- ^ __Returns:__ the t'GI.Clutter.Objects.State.State' instance, allowing
    --   chaining of multiple calls
stateSetKey :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsState a, IsObject b) =>
a
-> Maybe Text
-> Text
-> b
-> Text
-> Word32
-> GValue
-> Double
-> Double
-> m State
stateSetKey a
state Maybe Text
sourceStateName Text
targetStateName b
object Text
propertyName Word32
mode GValue
value Double
preDelay Double
postDelay = IO State -> m State
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO State -> m State) -> IO State -> m State
forall a b. (a -> b) -> a -> b
$ do
    Ptr State
state' <- a -> IO (Ptr State)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
state
    CString
maybeSourceStateName <- case Maybe Text
sourceStateName of
        Maybe Text
Nothing -> CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just Text
jSourceStateName -> do
            CString
jSourceStateName' <- Text -> IO CString
textToCString Text
jSourceStateName
            CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jSourceStateName'
    CString
targetStateName' <- Text -> IO CString
textToCString Text
targetStateName
    Ptr Object
object' <- b -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
object
    CString
propertyName' <- Text -> IO CString
textToCString Text
propertyName
    Ptr GValue
value' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
value
    let preDelay' :: CDouble
preDelay' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
preDelay
    let postDelay' :: CDouble
postDelay' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
postDelay
    Ptr State
result <- Ptr State
-> CString
-> CString
-> Ptr Object
-> CString
-> Word32
-> Ptr GValue
-> CDouble
-> CDouble
-> IO (Ptr State)
clutter_state_set_key Ptr State
state' CString
maybeSourceStateName CString
targetStateName' Ptr Object
object' CString
propertyName' Word32
mode Ptr GValue
value' CDouble
preDelay' CDouble
postDelay'
    Text -> Ptr State -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"stateSetKey" Ptr State
result
    State
result' <- ((ManagedPtr State -> State) -> Ptr State -> IO State
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr State -> State
State) Ptr State
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
state
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
object
    GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
value
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeSourceStateName
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
targetStateName'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
propertyName'
    State -> IO State
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return State
result'

#if defined(ENABLE_OVERLOADING)
data StateSetKeyMethodInfo
instance (signature ~ (Maybe (T.Text) -> T.Text -> b -> T.Text -> Word32 -> GValue -> Double -> Double -> m State), MonadIO m, IsState a, GObject.Object.IsObject b) => O.OverloadedMethod StateSetKeyMethodInfo a signature where
    overloadedMethod = stateSetKey

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


#endif

-- method State::set_state
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "state"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "State" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterState" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "target_state_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the state to transition to"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Clutter" , name = "Timeline" })
-- throws : False
-- Skip return : False

foreign import ccall "clutter_state_set_state" clutter_state_set_state :: 
    Ptr State ->                            -- state : TInterface (Name {namespace = "Clutter", name = "State"})
    CString ->                              -- target_state_name : TBasicType TUTF8
    IO (Ptr Clutter.Timeline.Timeline)

{-# DEPRECATED stateSetState ["(Since version 1.12)","Use t'GI.Clutter.Objects.KeyframeTransition.KeyframeTransition' and","  t'GI.Clutter.Objects.TransitionGroup.TransitionGroup' instead"] #-}
-- | Change the current state of t'GI.Clutter.Objects.State.State' to /@targetStateName@/.
-- 
-- The state will animate during its transition, see
-- @/clutter_state_warp_to_state/@ for animation-free state switching.
-- 
-- Setting a 'P.Nothing' state will stop the current animation and unset
-- the current state, but keys will be left intact.
-- 
-- /Since: 1.4/
stateSetState ::
    (B.CallStack.HasCallStack, MonadIO m, IsState a) =>
    a
    -- ^ /@state@/: a t'GI.Clutter.Objects.State.State'
    -> T.Text
    -- ^ /@targetStateName@/: the state to transition to
    -> m Clutter.Timeline.Timeline
    -- ^ __Returns:__ the t'GI.Clutter.Objects.Timeline.Timeline' that drives the
    --   state transition. The returned timeline is owned by the t'GI.Clutter.Objects.State.State'
    --   and it should not be unreferenced
stateSetState :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsState a) =>
a -> Text -> m Timeline
stateSetState a
state Text
targetStateName = IO Timeline -> m Timeline
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Timeline -> m Timeline) -> IO Timeline -> m Timeline
forall a b. (a -> b) -> a -> b
$ do
    Ptr State
state' <- a -> IO (Ptr State)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
state
    CString
targetStateName' <- Text -> IO CString
textToCString Text
targetStateName
    Ptr Timeline
result <- Ptr State -> CString -> IO (Ptr Timeline)
clutter_state_set_state Ptr State
state' CString
targetStateName'
    Text -> Ptr Timeline -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"stateSetState" Ptr Timeline
result
    Timeline
result' <- ((ManagedPtr Timeline -> Timeline) -> Ptr Timeline -> IO Timeline
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Timeline -> Timeline
Clutter.Timeline.Timeline) Ptr Timeline
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
state
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
targetStateName'
    Timeline -> IO Timeline
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Timeline
result'

#if defined(ENABLE_OVERLOADING)
data StateSetStateMethodInfo
instance (signature ~ (T.Text -> m Clutter.Timeline.Timeline), MonadIO m, IsState a) => O.OverloadedMethod StateSetStateMethodInfo a signature where
    overloadedMethod = stateSetState

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


#endif

-- method State::warp_to_state
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "state"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "State" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterState" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "target_state_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the state to transition to"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Clutter" , name = "Timeline" })
-- throws : False
-- Skip return : False

foreign import ccall "clutter_state_warp_to_state" clutter_state_warp_to_state :: 
    Ptr State ->                            -- state : TInterface (Name {namespace = "Clutter", name = "State"})
    CString ->                              -- target_state_name : TBasicType TUTF8
    IO (Ptr Clutter.Timeline.Timeline)

{-# DEPRECATED stateWarpToState ["(Since version 1.12)","Use t'GI.Clutter.Objects.KeyframeTransition.KeyframeTransition' and","  t'GI.Clutter.Objects.TransitionGroup.TransitionGroup' instead"] #-}
-- | Change to the specified target state immediately with no animation.
-- 
-- See 'GI.Clutter.Objects.State.stateSetState'.
-- 
-- /Since: 1.4/
stateWarpToState ::
    (B.CallStack.HasCallStack, MonadIO m, IsState a) =>
    a
    -- ^ /@state@/: a t'GI.Clutter.Objects.State.State'
    -> T.Text
    -- ^ /@targetStateName@/: the state to transition to
    -> m Clutter.Timeline.Timeline
    -- ^ __Returns:__ the t'GI.Clutter.Objects.Timeline.Timeline' that drives the
    --   state transition. The returned timeline is owned by the t'GI.Clutter.Objects.State.State'
    --   and it should not be unreferenced
stateWarpToState :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsState a) =>
a -> Text -> m Timeline
stateWarpToState a
state Text
targetStateName = IO Timeline -> m Timeline
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Timeline -> m Timeline) -> IO Timeline -> m Timeline
forall a b. (a -> b) -> a -> b
$ do
    Ptr State
state' <- a -> IO (Ptr State)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
state
    CString
targetStateName' <- Text -> IO CString
textToCString Text
targetStateName
    Ptr Timeline
result <- Ptr State -> CString -> IO (Ptr Timeline)
clutter_state_warp_to_state Ptr State
state' CString
targetStateName'
    Text -> Ptr Timeline -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"stateWarpToState" Ptr Timeline
result
    Timeline
result' <- ((ManagedPtr Timeline -> Timeline) -> Ptr Timeline -> IO Timeline
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Timeline -> Timeline
Clutter.Timeline.Timeline) Ptr Timeline
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
state
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
targetStateName'
    Timeline -> IO Timeline
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Timeline
result'

#if defined(ENABLE_OVERLOADING)
data StateWarpToStateMethodInfo
instance (signature ~ (T.Text -> m Clutter.Timeline.Timeline), MonadIO m, IsState a) => O.OverloadedMethod StateWarpToStateMethodInfo a signature where
    overloadedMethod = stateWarpToState

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


#endif