{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A base class for value mapping objects that attaches control sources to gobject
-- properties. Such an object is taking one or more t'GI.Gst.Objects.ControlSource.ControlSource' instances,
-- combines them and maps the resulting value to the type and value range of the
-- bound property.

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

module GI.Gst.Objects.ControlBinding
    ( 

-- * Exported types
    ControlBinding(..)                      ,
    IsControlBinding                        ,
    toControlBinding                        ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [addControlBinding]("GI.Gst.Objects.Object#g:method:addControlBinding"), [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [defaultError]("GI.Gst.Objects.Object#g:method:defaultError"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [hasActiveControlBindings]("GI.Gst.Objects.Object#g:method:hasActiveControlBindings"), [hasAncestor]("GI.Gst.Objects.Object#g:method:hasAncestor"), [hasAsAncestor]("GI.Gst.Objects.Object#g:method:hasAsAncestor"), [hasAsParent]("GI.Gst.Objects.Object#g:method:hasAsParent"), [isDisabled]("GI.Gst.Objects.ControlBinding#g:method:isDisabled"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [ref]("GI.Gst.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [removeControlBinding]("GI.Gst.Objects.Object#g:method:removeControlBinding"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [suggestNextSync]("GI.Gst.Objects.Object#g:method:suggestNextSync"), [syncValues]("GI.Gst.Objects.ControlBinding#g:method:syncValues"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unparent]("GI.Gst.Objects.Object#g:method:unparent"), [unref]("GI.Gst.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getControlBinding]("GI.Gst.Objects.Object#g:method:getControlBinding"), [getControlRate]("GI.Gst.Objects.Object#g:method:getControlRate"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getGValueArray]("GI.Gst.Objects.ControlBinding#g:method:getGValueArray"), [getName]("GI.Gst.Objects.Object#g:method:getName"), [getParent]("GI.Gst.Objects.Object#g:method:getParent"), [getPathString]("GI.Gst.Objects.Object#g:method:getPathString"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getValue]("GI.Gst.Objects.ControlBinding#g:method:getValue").
-- 
-- ==== Setters
-- [setControlBindingDisabled]("GI.Gst.Objects.Object#g:method:setControlBindingDisabled"), [setControlBindingsDisabled]("GI.Gst.Objects.Object#g:method:setControlBindingsDisabled"), [setControlRate]("GI.Gst.Objects.Object#g:method:setControlRate"), [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setDisabled]("GI.Gst.Objects.ControlBinding#g:method:setDisabled"), [setName]("GI.Gst.Objects.Object#g:method:setName"), [setParent]("GI.Gst.Objects.Object#g:method:setParent"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolveControlBindingMethod             ,
#endif

-- ** getGValueArray #method:getGValueArray#

#if defined(ENABLE_OVERLOADING)
    ControlBindingGetGValueArrayMethodInfo  ,
#endif
    controlBindingGetGValueArray            ,


-- ** getValue #method:getValue#

#if defined(ENABLE_OVERLOADING)
    ControlBindingGetValueMethodInfo        ,
#endif
    controlBindingGetValue                  ,


-- ** isDisabled #method:isDisabled#

#if defined(ENABLE_OVERLOADING)
    ControlBindingIsDisabledMethodInfo      ,
#endif
    controlBindingIsDisabled                ,


-- ** setDisabled #method:setDisabled#

#if defined(ENABLE_OVERLOADING)
    ControlBindingSetDisabledMethodInfo     ,
#endif
    controlBindingSetDisabled               ,


-- ** syncValues #method:syncValues#

#if defined(ENABLE_OVERLOADING)
    ControlBindingSyncValuesMethodInfo      ,
#endif
    controlBindingSyncValues                ,




 -- * Properties


-- ** name #attr:name#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    ControlBindingNamePropertyInfo          ,
#endif
    constructControlBindingName             ,
#if defined(ENABLE_OVERLOADING)
    controlBindingName                      ,
#endif
    getControlBindingName                   ,


-- ** object #attr:object#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    ControlBindingObjectPropertyInfo        ,
#endif
    constructControlBindingObject           ,
#if defined(ENABLE_OVERLOADING)
    controlBindingObject                    ,
#endif
    getControlBindingObject                 ,




    ) 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.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.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 qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gst.Objects.Object as Gst.Object

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

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

foreign import ccall "gst_control_binding_get_type"
    c_gst_control_binding_get_type :: IO B.Types.GType

instance B.Types.TypedObject ControlBinding where
    glibType :: IO GType
glibType = IO GType
c_gst_control_binding_get_type

instance B.Types.GObject ControlBinding

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

instance O.HasParentTypes ControlBinding
type instance O.ParentTypes ControlBinding = '[Gst.Object.Object, GObject.Object.Object]

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveControlBindingMethod (t :: Symbol) (o :: *) :: * where
    ResolveControlBindingMethod "addControlBinding" o = Gst.Object.ObjectAddControlBindingMethodInfo
    ResolveControlBindingMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveControlBindingMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveControlBindingMethod "defaultError" o = Gst.Object.ObjectDefaultErrorMethodInfo
    ResolveControlBindingMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveControlBindingMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveControlBindingMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveControlBindingMethod "hasActiveControlBindings" o = Gst.Object.ObjectHasActiveControlBindingsMethodInfo
    ResolveControlBindingMethod "hasAncestor" o = Gst.Object.ObjectHasAncestorMethodInfo
    ResolveControlBindingMethod "hasAsAncestor" o = Gst.Object.ObjectHasAsAncestorMethodInfo
    ResolveControlBindingMethod "hasAsParent" o = Gst.Object.ObjectHasAsParentMethodInfo
    ResolveControlBindingMethod "isDisabled" o = ControlBindingIsDisabledMethodInfo
    ResolveControlBindingMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveControlBindingMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveControlBindingMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveControlBindingMethod "ref" o = Gst.Object.ObjectRefMethodInfo
    ResolveControlBindingMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveControlBindingMethod "removeControlBinding" o = Gst.Object.ObjectRemoveControlBindingMethodInfo
    ResolveControlBindingMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveControlBindingMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveControlBindingMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveControlBindingMethod "suggestNextSync" o = Gst.Object.ObjectSuggestNextSyncMethodInfo
    ResolveControlBindingMethod "syncValues" o = ControlBindingSyncValuesMethodInfo
    ResolveControlBindingMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveControlBindingMethod "unparent" o = Gst.Object.ObjectUnparentMethodInfo
    ResolveControlBindingMethod "unref" o = Gst.Object.ObjectUnrefMethodInfo
    ResolveControlBindingMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveControlBindingMethod "getControlBinding" o = Gst.Object.ObjectGetControlBindingMethodInfo
    ResolveControlBindingMethod "getControlRate" o = Gst.Object.ObjectGetControlRateMethodInfo
    ResolveControlBindingMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveControlBindingMethod "getGValueArray" o = ControlBindingGetGValueArrayMethodInfo
    ResolveControlBindingMethod "getName" o = Gst.Object.ObjectGetNameMethodInfo
    ResolveControlBindingMethod "getParent" o = Gst.Object.ObjectGetParentMethodInfo
    ResolveControlBindingMethod "getPathString" o = Gst.Object.ObjectGetPathStringMethodInfo
    ResolveControlBindingMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveControlBindingMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveControlBindingMethod "getValue" o = ControlBindingGetValueMethodInfo
    ResolveControlBindingMethod "setControlBindingDisabled" o = Gst.Object.ObjectSetControlBindingDisabledMethodInfo
    ResolveControlBindingMethod "setControlBindingsDisabled" o = Gst.Object.ObjectSetControlBindingsDisabledMethodInfo
    ResolveControlBindingMethod "setControlRate" o = Gst.Object.ObjectSetControlRateMethodInfo
    ResolveControlBindingMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveControlBindingMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveControlBindingMethod "setDisabled" o = ControlBindingSetDisabledMethodInfo
    ResolveControlBindingMethod "setName" o = Gst.Object.ObjectSetNameMethodInfo
    ResolveControlBindingMethod "setParent" o = Gst.Object.ObjectSetParentMethodInfo
    ResolveControlBindingMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveControlBindingMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

--- XXX Duplicated object with different types:
  --- Name {namespace = "Gst", name = "ControlBinding"} -> Property {propName = "name", propType = TBasicType TUTF8, propFlags = [PropertyReadable,PropertyWritable,PropertyConstructOnly], propReadNullable = Nothing, propWriteNullable = Nothing, propTransfer = TransferNothing, propDoc = Documentation {rawDocText = Nothing, sinceVersion = Nothing}, propDeprecated = Nothing}
  --- Name {namespace = "Gst", name = "Object"} -> Property {propName = "name", propType = TBasicType TUTF8, propFlags = [PropertyReadable,PropertyWritable,PropertyConstruct], propReadNullable = Nothing, propWriteNullable = Nothing, propTransfer = TransferNothing, propDoc = Documentation {rawDocText = Nothing, sinceVersion = Nothing}, propDeprecated = Nothing}
-- VVV Prop "name"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Nothing,Nothing)

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

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

#if defined(ENABLE_OVERLOADING)
data ControlBindingNamePropertyInfo
instance AttrInfo ControlBindingNamePropertyInfo where
    type AttrAllowedOps ControlBindingNamePropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint ControlBindingNamePropertyInfo = IsControlBinding
    type AttrSetTypeConstraint ControlBindingNamePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint ControlBindingNamePropertyInfo = (~) T.Text
    type AttrTransferType ControlBindingNamePropertyInfo = T.Text
    type AttrGetType ControlBindingNamePropertyInfo = (Maybe T.Text)
    type AttrLabel ControlBindingNamePropertyInfo = "name"
    type AttrOrigin ControlBindingNamePropertyInfo = ControlBinding
    attrGet = getControlBindingName
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructControlBindingName
    attrClear = undefined
#endif

-- VVV Prop "object"
   -- Type: TInterface (Name {namespace = "Gst", name = "Object"})
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Nothing,Nothing)

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

-- | Construct a `GValueConstruct` with valid value for the “@object@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructControlBindingObject :: (IsControlBinding o, MIO.MonadIO m, Gst.Object.IsObject a) => a -> m (GValueConstruct o)
constructControlBindingObject :: forall o (m :: * -> *) a.
(IsControlBinding o, MonadIO m, IsObject a) =>
a -> m (GValueConstruct o)
constructControlBindingObject a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"object" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)

#if defined(ENABLE_OVERLOADING)
data ControlBindingObjectPropertyInfo
instance AttrInfo ControlBindingObjectPropertyInfo where
    type AttrAllowedOps ControlBindingObjectPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint ControlBindingObjectPropertyInfo = IsControlBinding
    type AttrSetTypeConstraint ControlBindingObjectPropertyInfo = Gst.Object.IsObject
    type AttrTransferTypeConstraint ControlBindingObjectPropertyInfo = Gst.Object.IsObject
    type AttrTransferType ControlBindingObjectPropertyInfo = Gst.Object.Object
    type AttrGetType ControlBindingObjectPropertyInfo = (Maybe Gst.Object.Object)
    type AttrLabel ControlBindingObjectPropertyInfo = "object"
    type AttrOrigin ControlBindingObjectPropertyInfo = ControlBinding
    attrGet = getControlBindingObject
    attrSet = undefined
    attrTransfer _ v = do
        unsafeCastTo Gst.Object.Object v
    attrConstruct = constructControlBindingObject
    attrClear = undefined
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList ControlBinding
type instance O.AttributeList ControlBinding = ControlBindingAttributeList
type ControlBindingAttributeList = ('[ '("name", ControlBindingNamePropertyInfo), '("object", ControlBindingObjectPropertyInfo), '("parent", Gst.Object.ObjectParentPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
controlBindingName :: AttrLabelProxy "name"
controlBindingName = AttrLabelProxy

controlBindingObject :: AttrLabelProxy "object"
controlBindingObject = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList ControlBinding = ControlBindingSignalList
type ControlBindingSignalList = ('[ '("deepNotify", Gst.Object.ObjectDeepNotifySignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif

-- method ControlBinding::get_g_value_array
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "binding"
--           , argType =
--               TInterface Name { namespace = "Gst" , name = "ControlBinding" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the control binding"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "timestamp"
--           , argType = TBasicType TUInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the time that should be processed"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "interval"
--           , argType = TBasicType TUInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the time spacing between subsequent values"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "n_values"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the number of values"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "values"
--           , argType = TCArray False (-1) 3 TGValue
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "array to put control-values in"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "n_values"
--              , argType = TBasicType TUInt
--              , direction = DirectionIn
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText = Just "the number of values"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferNothing
--              }
--          ]
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gst_control_binding_get_g_value_array" gst_control_binding_get_g_value_array :: 
    Ptr ControlBinding ->                   -- binding : TInterface (Name {namespace = "Gst", name = "ControlBinding"})
    Word64 ->                               -- timestamp : TBasicType TUInt64
    Word64 ->                               -- interval : TBasicType TUInt64
    Word32 ->                               -- n_values : TBasicType TUInt
    Ptr B.GValue.GValue ->                  -- values : TCArray False (-1) 3 TGValue
    IO CInt

-- | Gets a number of @/GValues/@ for the given controlled property starting at the
-- requested time. The array /@values@/ need to hold enough space for /@nValues@/ of
-- t'GI.GObject.Structs.Value.Value'.
-- 
-- This function is useful if one wants to e.g. draw a graph of the control
-- curve or apply a control curve sample by sample.
controlBindingGetGValueArray ::
    (B.CallStack.HasCallStack, MonadIO m, IsControlBinding a) =>
    a
    -- ^ /@binding@/: the control binding
    -> Word64
    -- ^ /@timestamp@/: the time that should be processed
    -> Word64
    -- ^ /@interval@/: the time spacing between subsequent values
    -> [GValue]
    -- ^ /@values@/: array to put control-values in
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the given array could be filled, 'P.False' otherwise
controlBindingGetGValueArray :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsControlBinding a) =>
a -> Word64 -> Word64 -> [GValue] -> m Bool
controlBindingGetGValueArray a
binding Word64
timestamp Word64
interval [GValue]
values = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    let nValues :: Word32
nValues = Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word32) -> Int -> Word32
forall a b. (a -> b) -> a -> b
$ [GValue] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
P.length [GValue]
values
    Ptr ControlBinding
binding' <- a -> IO (Ptr ControlBinding)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
binding
    Ptr GValue
values' <- [GValue] -> IO (Ptr GValue)
B.GValue.packGValueArray [GValue]
values
    CInt
result <- Ptr ControlBinding
-> Word64 -> Word64 -> Word32 -> Ptr GValue -> IO CInt
gst_control_binding_get_g_value_array Ptr ControlBinding
binding' Word64
timestamp Word64
interval Word32
nValues Ptr GValue
values'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
binding
    (GValue -> IO ()) -> [GValue] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr [GValue]
values
    Ptr GValue -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr GValue
values'
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data ControlBindingGetGValueArrayMethodInfo
instance (signature ~ (Word64 -> Word64 -> [GValue] -> m Bool), MonadIO m, IsControlBinding a) => O.OverloadedMethod ControlBindingGetGValueArrayMethodInfo a signature where
    overloadedMethod = controlBindingGetGValueArray

instance O.OverloadedMethodInfo ControlBindingGetGValueArrayMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gst.Objects.ControlBinding.controlBindingGetGValueArray",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gst-1.0.24/docs/GI-Gst-Objects-ControlBinding.html#v:controlBindingGetGValueArray"
        }


#endif

-- method ControlBinding::get_value
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "binding"
--           , argType =
--               TInterface Name { namespace = "Gst" , name = "ControlBinding" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the control binding"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "timestamp"
--           , argType = TBasicType TUInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the time the control-change should be read from"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just TGValue
-- throws : False
-- Skip return : False

foreign import ccall "gst_control_binding_get_value" gst_control_binding_get_value :: 
    Ptr ControlBinding ->                   -- binding : TInterface (Name {namespace = "Gst", name = "ControlBinding"})
    Word64 ->                               -- timestamp : TBasicType TUInt64
    IO (Ptr GValue)

-- | Gets the value for the given controlled property at the requested time.
controlBindingGetValue ::
    (B.CallStack.HasCallStack, MonadIO m, IsControlBinding a) =>
    a
    -- ^ /@binding@/: the control binding
    -> Word64
    -- ^ /@timestamp@/: the time the control-change should be read from
    -> m (Maybe GValue)
    -- ^ __Returns:__ the GValue of the property at the given time,
    -- or 'P.Nothing' if the property isn\'t controlled.
controlBindingGetValue :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsControlBinding a) =>
a -> Word64 -> m (Maybe GValue)
controlBindingGetValue a
binding Word64
timestamp = IO (Maybe GValue) -> m (Maybe GValue)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe GValue) -> m (Maybe GValue))
-> IO (Maybe GValue) -> m (Maybe GValue)
forall a b. (a -> b) -> a -> b
$ do
    Ptr ControlBinding
binding' <- a -> IO (Ptr ControlBinding)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
binding
    Ptr GValue
result <- Ptr ControlBinding -> Word64 -> IO (Ptr GValue)
gst_control_binding_get_value Ptr ControlBinding
binding' Word64
timestamp
    Maybe GValue
maybeResult <- Ptr GValue -> (Ptr GValue -> IO GValue) -> IO (Maybe GValue)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr GValue
result ((Ptr GValue -> IO GValue) -> IO (Maybe GValue))
-> (Ptr GValue -> IO GValue) -> IO (Maybe GValue)
forall a b. (a -> b) -> a -> b
$ \Ptr GValue
result' -> do
        GValue
result'' <- Ptr GValue -> IO GValue
B.GValue.wrapGValuePtr Ptr GValue
result'
        GValue -> IO GValue
forall (m :: * -> *) a. Monad m => a -> m a
return GValue
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
binding
    Maybe GValue -> IO (Maybe GValue)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe GValue
maybeResult

#if defined(ENABLE_OVERLOADING)
data ControlBindingGetValueMethodInfo
instance (signature ~ (Word64 -> m (Maybe GValue)), MonadIO m, IsControlBinding a) => O.OverloadedMethod ControlBindingGetValueMethodInfo a signature where
    overloadedMethod = controlBindingGetValue

instance O.OverloadedMethodInfo ControlBindingGetValueMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gst.Objects.ControlBinding.controlBindingGetValue",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gst-1.0.24/docs/GI-Gst-Objects-ControlBinding.html#v:controlBindingGetValue"
        }


#endif

-- method ControlBinding::is_disabled
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "binding"
--           , argType =
--               TInterface Name { namespace = "Gst" , name = "ControlBinding" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the control binding"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gst_control_binding_is_disabled" gst_control_binding_is_disabled :: 
    Ptr ControlBinding ->                   -- binding : TInterface (Name {namespace = "Gst", name = "ControlBinding"})
    IO CInt

-- | Check if the control binding is disabled.
controlBindingIsDisabled ::
    (B.CallStack.HasCallStack, MonadIO m, IsControlBinding a) =>
    a
    -- ^ /@binding@/: the control binding
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the binding is inactive
controlBindingIsDisabled :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsControlBinding a) =>
a -> m Bool
controlBindingIsDisabled a
binding = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr ControlBinding
binding' <- a -> IO (Ptr ControlBinding)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
binding
    CInt
result <- Ptr ControlBinding -> IO CInt
gst_control_binding_is_disabled Ptr ControlBinding
binding'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
binding
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data ControlBindingIsDisabledMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsControlBinding a) => O.OverloadedMethod ControlBindingIsDisabledMethodInfo a signature where
    overloadedMethod = controlBindingIsDisabled

instance O.OverloadedMethodInfo ControlBindingIsDisabledMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gst.Objects.ControlBinding.controlBindingIsDisabled",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gst-1.0.24/docs/GI-Gst-Objects-ControlBinding.html#v:controlBindingIsDisabled"
        }


#endif

-- method ControlBinding::set_disabled
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "binding"
--           , argType =
--               TInterface Name { namespace = "Gst" , name = "ControlBinding" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the control binding"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "disabled"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "boolean that specifies whether to disable the controller\nor not."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gst_control_binding_set_disabled" gst_control_binding_set_disabled :: 
    Ptr ControlBinding ->                   -- binding : TInterface (Name {namespace = "Gst", name = "ControlBinding"})
    CInt ->                                 -- disabled : TBasicType TBoolean
    IO ()

-- | This function is used to disable a control binding for some time, i.e.
-- 'GI.Gst.Objects.Object.objectSyncValues' will do nothing.
controlBindingSetDisabled ::
    (B.CallStack.HasCallStack, MonadIO m, IsControlBinding a) =>
    a
    -- ^ /@binding@/: the control binding
    -> Bool
    -- ^ /@disabled@/: boolean that specifies whether to disable the controller
    -- or not.
    -> m ()
controlBindingSetDisabled :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsControlBinding a) =>
a -> Bool -> m ()
controlBindingSetDisabled a
binding Bool
disabled = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr ControlBinding
binding' <- a -> IO (Ptr ControlBinding)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
binding
    let disabled' :: CInt
disabled' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
disabled
    Ptr ControlBinding -> CInt -> IO ()
gst_control_binding_set_disabled Ptr ControlBinding
binding' CInt
disabled'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
binding
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ControlBindingSetDisabledMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsControlBinding a) => O.OverloadedMethod ControlBindingSetDisabledMethodInfo a signature where
    overloadedMethod = controlBindingSetDisabled

instance O.OverloadedMethodInfo ControlBindingSetDisabledMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gst.Objects.ControlBinding.controlBindingSetDisabled",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gst-1.0.24/docs/GI-Gst-Objects-ControlBinding.html#v:controlBindingSetDisabled"
        }


#endif

-- method ControlBinding::sync_values
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "binding"
--           , argType =
--               TInterface Name { namespace = "Gst" , name = "ControlBinding" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the control binding"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "object"
--           , argType = TInterface Name { namespace = "Gst" , name = "Object" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the object that has controlled properties"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "timestamp"
--           , argType = TBasicType TUInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the time that should be processed"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "last_sync"
--           , argType = TBasicType TUInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the last time this was called"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gst_control_binding_sync_values" gst_control_binding_sync_values :: 
    Ptr ControlBinding ->                   -- binding : TInterface (Name {namespace = "Gst", name = "ControlBinding"})
    Ptr Gst.Object.Object ->                -- object : TInterface (Name {namespace = "Gst", name = "Object"})
    Word64 ->                               -- timestamp : TBasicType TUInt64
    Word64 ->                               -- last_sync : TBasicType TUInt64
    IO CInt

-- | Sets the property of the /@object@/, according to the @/GstControlSources/@ that
-- handle them and for the given timestamp.
-- 
-- If this function fails, it is most likely the application developers fault.
-- Most probably the control sources are not setup correctly.
controlBindingSyncValues ::
    (B.CallStack.HasCallStack, MonadIO m, IsControlBinding a, Gst.Object.IsObject b) =>
    a
    -- ^ /@binding@/: the control binding
    -> b
    -- ^ /@object@/: the object that has controlled properties
    -> Word64
    -- ^ /@timestamp@/: the time that should be processed
    -> Word64
    -- ^ /@lastSync@/: the last time this was called
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the controller value could be applied to the object
    -- property, 'P.False' otherwise
controlBindingSyncValues :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsControlBinding a, IsObject b) =>
a -> b -> Word64 -> Word64 -> m Bool
controlBindingSyncValues a
binding b
object Word64
timestamp Word64
lastSync = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr ControlBinding
binding' <- a -> IO (Ptr ControlBinding)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
binding
    Ptr Object
object' <- b -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
object
    CInt
result <- Ptr ControlBinding -> Ptr Object -> Word64 -> Word64 -> IO CInt
gst_control_binding_sync_values Ptr ControlBinding
binding' Ptr Object
object' Word64
timestamp Word64
lastSync
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
binding
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
object
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data ControlBindingSyncValuesMethodInfo
instance (signature ~ (b -> Word64 -> Word64 -> m Bool), MonadIO m, IsControlBinding a, Gst.Object.IsObject b) => O.OverloadedMethod ControlBindingSyncValuesMethodInfo a signature where
    overloadedMethod = controlBindingSyncValues

instance O.OverloadedMethodInfo ControlBindingSyncValuesMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gst.Objects.ControlBinding.controlBindingSyncValues",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gst-1.0.24/docs/GI-Gst-Objects-ControlBinding.html#v:controlBindingSyncValues"
        }


#endif