{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- This interface abstracts handling of property sets for elements with
-- children. Imagine elements such as mixers or polyphonic generators. They all
-- have multiple t'GI.Gst.Objects.Pad.Pad' or some kind of voice objects. Another use case are
-- container elements like t'GI.Gst.Objects.Bin.Bin'.
-- The element implementing the interface acts as a parent for those child
-- objects.
-- 
-- By implementing this interface the child properties can be accessed from the
-- parent element by using @/gst_child_proxy_get()/@ and @/gst_child_proxy_set()/@.
-- 
-- Property names are written as \"child-name[propertyName](#g:signal:propertyName)\". The whole naming
-- scheme is recursive. Thus \"child1[child2](#g:signal:child2)[property](#g:signal:property)\" is valid too, if
-- \"child1\" and \"child2\" implement the t'GI.Gst.Interfaces.ChildProxy.ChildProxy' interface.

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

module GI.Gst.Interfaces.ChildProxy
    ( 

-- * Exported types
    ChildProxy(..)                          ,
    IsChildProxy                            ,
    toChildProxy                            ,


 -- * 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"), [childAdded]("GI.Gst.Interfaces.ChildProxy#g:method:childAdded"), [childRemoved]("GI.Gst.Interfaces.ChildProxy#g:method:childRemoved"), [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"), [lookup]("GI.Gst.Interfaces.ChildProxy#g:method:lookup"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [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"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getChildByIndex]("GI.Gst.Interfaces.ChildProxy#g:method:getChildByIndex"), [getChildByName]("GI.Gst.Interfaces.ChildProxy#g:method:getChildByName"), [getChildrenCount]("GI.Gst.Interfaces.ChildProxy#g:method:getChildrenCount"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getProperty]("GI.Gst.Interfaces.ChildProxy#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setProperty]("GI.Gst.Interfaces.ChildProxy#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolveChildProxyMethod                 ,
#endif

-- ** childAdded #method:childAdded#

#if defined(ENABLE_OVERLOADING)
    ChildProxyChildAddedMethodInfo          ,
#endif
    childProxyChildAdded                    ,


-- ** childRemoved #method:childRemoved#

#if defined(ENABLE_OVERLOADING)
    ChildProxyChildRemovedMethodInfo        ,
#endif
    childProxyChildRemoved                  ,


-- ** getChildByIndex #method:getChildByIndex#

#if defined(ENABLE_OVERLOADING)
    ChildProxyGetChildByIndexMethodInfo     ,
#endif
    childProxyGetChildByIndex               ,


-- ** getChildByName #method:getChildByName#

#if defined(ENABLE_OVERLOADING)
    ChildProxyGetChildByNameMethodInfo      ,
#endif
    childProxyGetChildByName                ,


-- ** getChildrenCount #method:getChildrenCount#

#if defined(ENABLE_OVERLOADING)
    ChildProxyGetChildrenCountMethodInfo    ,
#endif
    childProxyGetChildrenCount              ,


-- ** getProperty #method:getProperty#

#if defined(ENABLE_OVERLOADING)
    ChildProxyGetPropertyMethodInfo         ,
#endif
    childProxyGetProperty                   ,


-- ** lookup #method:lookup#

#if defined(ENABLE_OVERLOADING)
    ChildProxyLookupMethodInfo              ,
#endif
    childProxyLookup                        ,


-- ** setProperty #method:setProperty#

#if defined(ENABLE_OVERLOADING)
    ChildProxySetPropertyMethodInfo         ,
#endif
    childProxySetProperty                   ,




 -- * Signals


-- ** childAdded #signal:childAdded#

    C_ChildProxyChildAddedCallback          ,
    ChildProxyChildAddedCallback            ,
#if defined(ENABLE_OVERLOADING)
    ChildProxyChildAddedSignalInfo          ,
#endif
    afterChildProxyChildAdded               ,
    genClosure_ChildProxyChildAdded         ,
    mk_ChildProxyChildAddedCallback         ,
    noChildProxyChildAddedCallback          ,
    onChildProxyChildAdded                  ,
    wrap_ChildProxyChildAddedCallback       ,


-- ** childRemoved #signal:childRemoved#

    C_ChildProxyChildRemovedCallback        ,
    ChildProxyChildRemovedCallback          ,
#if defined(ENABLE_OVERLOADING)
    ChildProxyChildRemovedSignalInfo        ,
#endif
    afterChildProxyChildRemoved             ,
    genClosure_ChildProxyChildRemoved       ,
    mk_ChildProxyChildRemovedCallback       ,
    noChildProxyChildRemovedCallback        ,
    onChildProxyChildRemoved                ,
    wrap_ChildProxyChildRemovedCallback     ,




    ) 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

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

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

foreign import ccall "gst_child_proxy_get_type"
    c_gst_child_proxy_get_type :: IO B.Types.GType

instance B.Types.TypedObject ChildProxy where
    glibType :: IO GType
glibType = IO GType
c_gst_child_proxy_get_type

instance B.Types.GObject ChildProxy

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

instance O.HasParentTypes ChildProxy
type instance O.ParentTypes ChildProxy = '[GObject.Object.Object]

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

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

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList ChildProxy
type instance O.AttributeList ChildProxy = ChildProxyAttributeList
type ChildProxyAttributeList = ('[ ] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveChildProxyMethod (t :: Symbol) (o :: *) :: * where
    ResolveChildProxyMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveChildProxyMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveChildProxyMethod "childAdded" o = ChildProxyChildAddedMethodInfo
    ResolveChildProxyMethod "childRemoved" o = ChildProxyChildRemovedMethodInfo
    ResolveChildProxyMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveChildProxyMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveChildProxyMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveChildProxyMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveChildProxyMethod "lookup" o = ChildProxyLookupMethodInfo
    ResolveChildProxyMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveChildProxyMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveChildProxyMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveChildProxyMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveChildProxyMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveChildProxyMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveChildProxyMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveChildProxyMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveChildProxyMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveChildProxyMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveChildProxyMethod "getChildByIndex" o = ChildProxyGetChildByIndexMethodInfo
    ResolveChildProxyMethod "getChildByName" o = ChildProxyGetChildByNameMethodInfo
    ResolveChildProxyMethod "getChildrenCount" o = ChildProxyGetChildrenCountMethodInfo
    ResolveChildProxyMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveChildProxyMethod "getProperty" o = ChildProxyGetPropertyMethodInfo
    ResolveChildProxyMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveChildProxyMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveChildProxyMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveChildProxyMethod "setProperty" o = ChildProxySetPropertyMethodInfo
    ResolveChildProxyMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

-- method ChildProxy::child_added
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "parent"
--           , argType =
--               TInterface Name { namespace = "Gst" , name = "ChildProxy" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the parent object" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "child"
--           , argType =
--               TInterface Name { namespace = "GObject" , name = "Object" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the newly added child"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the name of the new child"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gst_child_proxy_child_added" gst_child_proxy_child_added :: 
    Ptr ChildProxy ->                       -- parent : TInterface (Name {namespace = "Gst", name = "ChildProxy"})
    Ptr GObject.Object.Object ->            -- child : TInterface (Name {namespace = "GObject", name = "Object"})
    CString ->                              -- name : TBasicType TUTF8
    IO ()

-- | Emits the \"child-added\" signal.
childProxyChildAdded ::
    (B.CallStack.HasCallStack, MonadIO m, IsChildProxy a, GObject.Object.IsObject b) =>
    a
    -- ^ /@parent@/: the parent object
    -> b
    -- ^ /@child@/: the newly added child
    -> T.Text
    -- ^ /@name@/: the name of the new child
    -> m ()
childProxyChildAdded :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsChildProxy a, IsObject b) =>
a -> b -> Text -> m ()
childProxyChildAdded a
parent b
child Text
name = 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 ChildProxy
parent' <- a -> IO (Ptr ChildProxy)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
parent
    Ptr Object
child' <- b -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
child
    CString
name' <- Text -> IO CString
textToCString Text
name
    Ptr ChildProxy -> Ptr Object -> CString -> IO ()
gst_child_proxy_child_added Ptr ChildProxy
parent' Ptr Object
child' CString
name'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
parent
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
child
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

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

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


#endif

-- method ChildProxy::child_removed
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "parent"
--           , argType =
--               TInterface Name { namespace = "Gst" , name = "ChildProxy" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the parent object" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "child"
--           , argType =
--               TInterface Name { namespace = "GObject" , name = "Object" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the removed child" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the name of the old child"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gst_child_proxy_child_removed" gst_child_proxy_child_removed :: 
    Ptr ChildProxy ->                       -- parent : TInterface (Name {namespace = "Gst", name = "ChildProxy"})
    Ptr GObject.Object.Object ->            -- child : TInterface (Name {namespace = "GObject", name = "Object"})
    CString ->                              -- name : TBasicType TUTF8
    IO ()

-- | Emits the \"child-removed\" signal.
childProxyChildRemoved ::
    (B.CallStack.HasCallStack, MonadIO m, IsChildProxy a, GObject.Object.IsObject b) =>
    a
    -- ^ /@parent@/: the parent object
    -> b
    -- ^ /@child@/: the removed child
    -> T.Text
    -- ^ /@name@/: the name of the old child
    -> m ()
childProxyChildRemoved :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsChildProxy a, IsObject b) =>
a -> b -> Text -> m ()
childProxyChildRemoved a
parent b
child Text
name = 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 ChildProxy
parent' <- a -> IO (Ptr ChildProxy)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
parent
    Ptr Object
child' <- b -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
child
    CString
name' <- Text -> IO CString
textToCString Text
name
    Ptr ChildProxy -> Ptr Object -> CString -> IO ()
gst_child_proxy_child_removed Ptr ChildProxy
parent' Ptr Object
child' CString
name'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
parent
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
child
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

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

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


#endif

-- method ChildProxy::get_child_by_index
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "parent"
--           , argType =
--               TInterface Name { namespace = "Gst" , name = "ChildProxy" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the parent object to get the child from"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "index"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the child's position in the child list"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GObject" , name = "Object" })
-- throws : False
-- Skip return : False

foreign import ccall "gst_child_proxy_get_child_by_index" gst_child_proxy_get_child_by_index :: 
    Ptr ChildProxy ->                       -- parent : TInterface (Name {namespace = "Gst", name = "ChildProxy"})
    Word32 ->                               -- index : TBasicType TUInt
    IO (Ptr GObject.Object.Object)

-- | Fetches a child by its number.
childProxyGetChildByIndex ::
    (B.CallStack.HasCallStack, MonadIO m, IsChildProxy a) =>
    a
    -- ^ /@parent@/: the parent object to get the child from
    -> Word32
    -- ^ /@index@/: the child\'s position in the child list
    -> m (Maybe GObject.Object.Object)
    -- ^ __Returns:__ the child object or 'P.Nothing' if
    --     not found (index too high). Unref after usage.
    -- 
    -- MT safe.
childProxyGetChildByIndex :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsChildProxy a) =>
a -> Word32 -> m (Maybe Object)
childProxyGetChildByIndex a
parent Word32
index = IO (Maybe Object) -> m (Maybe Object)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Object) -> m (Maybe Object))
-> IO (Maybe Object) -> m (Maybe Object)
forall a b. (a -> b) -> a -> b
$ do
    Ptr ChildProxy
parent' <- a -> IO (Ptr ChildProxy)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
parent
    Ptr Object
result <- Ptr ChildProxy -> Word32 -> IO (Ptr Object)
gst_child_proxy_get_child_by_index Ptr ChildProxy
parent' Word32
index
    Maybe Object
maybeResult <- Ptr Object -> (Ptr Object -> IO Object) -> IO (Maybe Object)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Object
result ((Ptr Object -> IO Object) -> IO (Maybe Object))
-> (Ptr Object -> IO Object) -> IO (Maybe Object)
forall a b. (a -> b) -> a -> b
$ \Ptr Object
result' -> do
        Object
result'' <- ((ManagedPtr Object -> Object) -> Ptr Object -> IO Object
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Object -> Object
GObject.Object.Object) Ptr Object
result'
        Object -> IO Object
forall (m :: * -> *) a. Monad m => a -> m a
return Object
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
parent
    Maybe Object -> IO (Maybe Object)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Object
maybeResult

#if defined(ENABLE_OVERLOADING)
data ChildProxyGetChildByIndexMethodInfo
instance (signature ~ (Word32 -> m (Maybe GObject.Object.Object)), MonadIO m, IsChildProxy a) => O.OverloadedMethod ChildProxyGetChildByIndexMethodInfo a signature where
    overloadedMethod = childProxyGetChildByIndex

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


#endif

-- method ChildProxy::get_child_by_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "parent"
--           , argType =
--               TInterface Name { namespace = "Gst" , name = "ChildProxy" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the parent object to get the child from"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the child's name" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GObject" , name = "Object" })
-- throws : False
-- Skip return : False

foreign import ccall "gst_child_proxy_get_child_by_name" gst_child_proxy_get_child_by_name :: 
    Ptr ChildProxy ->                       -- parent : TInterface (Name {namespace = "Gst", name = "ChildProxy"})
    CString ->                              -- name : TBasicType TUTF8
    IO (Ptr GObject.Object.Object)

-- | Looks up a child element by the given name.
-- 
-- This virtual method has a default implementation that uses t'GI.Gst.Objects.Object.Object'
-- together with 'GI.Gst.Objects.Object.objectGetName'. If the interface is to be used with
-- @/GObjects/@, this methods needs to be overridden.
childProxyGetChildByName ::
    (B.CallStack.HasCallStack, MonadIO m, IsChildProxy a) =>
    a
    -- ^ /@parent@/: the parent object to get the child from
    -> T.Text
    -- ^ /@name@/: the child\'s name
    -> m (Maybe GObject.Object.Object)
    -- ^ __Returns:__ the child object or 'P.Nothing' if
    --     not found. Unref after usage.
    -- 
    -- MT safe.
childProxyGetChildByName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsChildProxy a) =>
a -> Text -> m (Maybe Object)
childProxyGetChildByName a
parent Text
name = IO (Maybe Object) -> m (Maybe Object)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Object) -> m (Maybe Object))
-> IO (Maybe Object) -> m (Maybe Object)
forall a b. (a -> b) -> a -> b
$ do
    Ptr ChildProxy
parent' <- a -> IO (Ptr ChildProxy)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
parent
    CString
name' <- Text -> IO CString
textToCString Text
name
    Ptr Object
result <- Ptr ChildProxy -> CString -> IO (Ptr Object)
gst_child_proxy_get_child_by_name Ptr ChildProxy
parent' CString
name'
    Maybe Object
maybeResult <- Ptr Object -> (Ptr Object -> IO Object) -> IO (Maybe Object)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Object
result ((Ptr Object -> IO Object) -> IO (Maybe Object))
-> (Ptr Object -> IO Object) -> IO (Maybe Object)
forall a b. (a -> b) -> a -> b
$ \Ptr Object
result' -> do
        Object
result'' <- ((ManagedPtr Object -> Object) -> Ptr Object -> IO Object
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Object -> Object
GObject.Object.Object) Ptr Object
result'
        Object -> IO Object
forall (m :: * -> *) a. Monad m => a -> m a
return Object
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
parent
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
    Maybe Object -> IO (Maybe Object)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Object
maybeResult

#if defined(ENABLE_OVERLOADING)
data ChildProxyGetChildByNameMethodInfo
instance (signature ~ (T.Text -> m (Maybe GObject.Object.Object)), MonadIO m, IsChildProxy a) => O.OverloadedMethod ChildProxyGetChildByNameMethodInfo a signature where
    overloadedMethod = childProxyGetChildByName

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


#endif

-- method ChildProxy::get_children_count
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "parent"
--           , argType =
--               TInterface Name { namespace = "Gst" , name = "ChildProxy" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the parent object" , 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 "gst_child_proxy_get_children_count" gst_child_proxy_get_children_count :: 
    Ptr ChildProxy ->                       -- parent : TInterface (Name {namespace = "Gst", name = "ChildProxy"})
    IO Word32

-- | Gets the number of child objects this parent contains.
childProxyGetChildrenCount ::
    (B.CallStack.HasCallStack, MonadIO m, IsChildProxy a) =>
    a
    -- ^ /@parent@/: the parent object
    -> m Word32
    -- ^ __Returns:__ the number of child objects
    -- 
    -- MT safe.
childProxyGetChildrenCount :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsChildProxy a) =>
a -> m Word32
childProxyGetChildrenCount a
parent = IO Word32 -> m Word32
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 ChildProxy
parent' <- a -> IO (Ptr ChildProxy)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
parent
    Word32
result <- Ptr ChildProxy -> IO Word32
gst_child_proxy_get_children_count Ptr ChildProxy
parent'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
parent
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data ChildProxyGetChildrenCountMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsChildProxy a) => O.OverloadedMethod ChildProxyGetChildrenCountMethodInfo a signature where
    overloadedMethod = childProxyGetChildrenCount

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


#endif

-- method ChildProxy::get_property
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "object"
--           , argType =
--               TInterface Name { namespace = "Gst" , name = "ChildProxy" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "object to query" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "name of the property"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TGValue
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GValue that should take the result."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gst_child_proxy_get_property" gst_child_proxy_get_property :: 
    Ptr ChildProxy ->                       -- object : TInterface (Name {namespace = "Gst", name = "ChildProxy"})
    CString ->                              -- name : TBasicType TUTF8
    Ptr GValue ->                           -- value : TGValue
    IO ()

-- | Gets a single property using the GstChildProxy mechanism.
-- You are responsible for freeing it by calling 'GI.GObject.Structs.Value.valueUnset'
childProxyGetProperty ::
    (B.CallStack.HasCallStack, MonadIO m, IsChildProxy a) =>
    a
    -- ^ /@object@/: object to query
    -> T.Text
    -- ^ /@name@/: name of the property
    -> m (GValue)
childProxyGetProperty :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsChildProxy a) =>
a -> Text -> m GValue
childProxyGetProperty a
object Text
name = IO GValue -> m GValue
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO GValue -> m GValue) -> IO GValue -> m GValue
forall a b. (a -> b) -> a -> b
$ do
    Ptr ChildProxy
object' <- a -> IO (Ptr ChildProxy)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
object
    CString
name' <- Text -> IO CString
textToCString Text
name
    Ptr GValue
value <- Int -> IO (Ptr GValue)
forall a. Int -> IO (Ptr a)
SP.callocBytes Int
24 :: IO (Ptr GValue)
    Ptr ChildProxy -> CString -> Ptr GValue -> IO ()
gst_child_proxy_get_property Ptr ChildProxy
object' CString
name' Ptr GValue
value
    GValue
value' <- Ptr GValue -> IO GValue
B.GValue.wrapGValuePtr Ptr GValue
value
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
object
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
    GValue -> IO GValue
forall (m :: * -> *) a. Monad m => a -> m a
return GValue
value'

#if defined(ENABLE_OVERLOADING)
data ChildProxyGetPropertyMethodInfo
instance (signature ~ (T.Text -> m (GValue)), MonadIO m, IsChildProxy a) => O.OverloadedMethod ChildProxyGetPropertyMethodInfo a signature where
    overloadedMethod = childProxyGetProperty

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


#endif

-- method ChildProxy::lookup
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "object"
--           , argType =
--               TInterface Name { namespace = "Gst" , name = "ChildProxy" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "child proxy object to lookup the property in"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "name of the property to look up"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "target"
--           , argType =
--               TInterface Name { namespace = "GObject" , name = "Object" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "pointer to a #GObject that\n    takes the real object to set property on"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "pspec"
--           , argType = TParamSpec
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "pointer to take the #GParamSpec\n    describing the property"
--                 , 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_child_proxy_lookup" gst_child_proxy_lookup :: 
    Ptr ChildProxy ->                       -- object : TInterface (Name {namespace = "Gst", name = "ChildProxy"})
    CString ->                              -- name : TBasicType TUTF8
    Ptr (Ptr GObject.Object.Object) ->      -- target : TInterface (Name {namespace = "GObject", name = "Object"})
    Ptr (Ptr GParamSpec) ->                 -- pspec : TParamSpec
    IO CInt

-- | Looks up which object and t'GI.GObject.Objects.ParamSpec.ParamSpec' would be effected by the given /@name@/.
-- 
-- MT safe.
childProxyLookup ::
    (B.CallStack.HasCallStack, MonadIO m, IsChildProxy a) =>
    a
    -- ^ /@object@/: child proxy object to lookup the property in
    -> T.Text
    -- ^ /@name@/: name of the property to look up
    -> m ((Bool, GObject.Object.Object, GParamSpec))
    -- ^ __Returns:__ 'P.True' if /@target@/ and /@pspec@/ could be found. 'P.False' otherwise. In that
    -- case the values for /@pspec@/ and /@target@/ are not modified. Unref /@target@/ after
    -- usage. For plain GObjects /@target@/ is the same as /@object@/.
childProxyLookup :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsChildProxy a) =>
a -> Text -> m (Bool, Object, GParamSpec)
childProxyLookup a
object Text
name = IO (Bool, Object, GParamSpec) -> m (Bool, Object, GParamSpec)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, Object, GParamSpec) -> m (Bool, Object, GParamSpec))
-> IO (Bool, Object, GParamSpec) -> m (Bool, Object, GParamSpec)
forall a b. (a -> b) -> a -> b
$ do
    Ptr ChildProxy
object' <- a -> IO (Ptr ChildProxy)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
object
    CString
name' <- Text -> IO CString
textToCString Text
name
    Ptr (Ptr Object)
target <- IO (Ptr (Ptr Object))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (Ptr GObject.Object.Object))
    Ptr (Ptr GParamSpec)
pspec <- IO (Ptr (Ptr GParamSpec))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (Ptr GParamSpec))
    CInt
result <- Ptr ChildProxy
-> CString -> Ptr (Ptr Object) -> Ptr (Ptr GParamSpec) -> IO CInt
gst_child_proxy_lookup Ptr ChildProxy
object' CString
name' Ptr (Ptr Object)
target Ptr (Ptr GParamSpec)
pspec
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    Ptr Object
target' <- Ptr (Ptr Object) -> IO (Ptr Object)
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr Object)
target
    Object
target'' <- ((ManagedPtr Object -> Object) -> Ptr Object -> IO Object
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Object -> Object
GObject.Object.Object) Ptr Object
target'
    Ptr GParamSpec
pspec' <- Ptr (Ptr GParamSpec) -> IO (Ptr GParamSpec)
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr GParamSpec)
pspec
    GParamSpec
pspec'' <- Ptr GParamSpec -> IO GParamSpec
B.GParamSpec.newGParamSpecFromPtr Ptr GParamSpec
pspec'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
object
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
    Ptr (Ptr Object) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr Object)
target
    Ptr (Ptr GParamSpec) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr GParamSpec)
pspec
    (Bool, Object, GParamSpec) -> IO (Bool, Object, GParamSpec)
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', Object
target'', GParamSpec
pspec'')

#if defined(ENABLE_OVERLOADING)
data ChildProxyLookupMethodInfo
instance (signature ~ (T.Text -> m ((Bool, GObject.Object.Object, GParamSpec))), MonadIO m, IsChildProxy a) => O.OverloadedMethod ChildProxyLookupMethodInfo a signature where
    overloadedMethod = childProxyLookup

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


#endif

-- method ChildProxy::set_property
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "object"
--           , argType =
--               TInterface Name { namespace = "Gst" , name = "ChildProxy" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the parent object" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "name of the property to set"
--                 , 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 "new #GValue for the property"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gst_child_proxy_set_property" gst_child_proxy_set_property :: 
    Ptr ChildProxy ->                       -- object : TInterface (Name {namespace = "Gst", name = "ChildProxy"})
    CString ->                              -- name : TBasicType TUTF8
    Ptr GValue ->                           -- value : TGValue
    IO ()

-- | Sets a single property using the GstChildProxy mechanism.
childProxySetProperty ::
    (B.CallStack.HasCallStack, MonadIO m, IsChildProxy a) =>
    a
    -- ^ /@object@/: the parent object
    -> T.Text
    -- ^ /@name@/: name of the property to set
    -> GValue
    -- ^ /@value@/: new t'GI.GObject.Structs.Value.Value' for the property
    -> m ()
childProxySetProperty :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsChildProxy a) =>
a -> Text -> GValue -> m ()
childProxySetProperty a
object Text
name GValue
value = 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 ChildProxy
object' <- a -> IO (Ptr ChildProxy)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
object
    CString
name' <- Text -> IO CString
textToCString Text
name
    Ptr GValue
value' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
value
    Ptr ChildProxy -> CString -> Ptr GValue -> IO ()
gst_child_proxy_set_property Ptr ChildProxy
object' CString
name' Ptr GValue
value'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
object
    GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
value
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ChildProxySetPropertyMethodInfo
instance (signature ~ (T.Text -> GValue -> m ()), MonadIO m, IsChildProxy a) => O.OverloadedMethod ChildProxySetPropertyMethodInfo a signature where
    overloadedMethod = childProxySetProperty

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


#endif

-- signal ChildProxy::child-added
-- | Will be emitted after the /@object@/ was added to the /@childProxy@/.
type ChildProxyChildAddedCallback =
    GObject.Object.Object
    -- ^ /@object@/: the t'GI.GObject.Objects.Object.Object' that was added
    -> T.Text
    -- ^ /@name@/: the name of the new child
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `ChildProxyChildAddedCallback`@.
noChildProxyChildAddedCallback :: Maybe ChildProxyChildAddedCallback
noChildProxyChildAddedCallback :: Maybe ChildProxyChildAddedCallback
noChildProxyChildAddedCallback = Maybe ChildProxyChildAddedCallback
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_ChildProxyChildAddedCallback =
    Ptr () ->                               -- object
    Ptr GObject.Object.Object ->
    CString ->
    Ptr () ->                               -- user_data
    IO ()

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

-- | Wrap the callback into a `GClosure`.
genClosure_ChildProxyChildAdded :: MonadIO m => ChildProxyChildAddedCallback -> m (GClosure C_ChildProxyChildAddedCallback)
genClosure_ChildProxyChildAdded :: forall (m :: * -> *).
MonadIO m =>
ChildProxyChildAddedCallback
-> m (GClosure C_ChildProxyChildAddedCallback)
genClosure_ChildProxyChildAdded ChildProxyChildAddedCallback
cb = IO (GClosure C_ChildProxyChildAddedCallback)
-> m (GClosure C_ChildProxyChildAddedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_ChildProxyChildAddedCallback)
 -> m (GClosure C_ChildProxyChildAddedCallback))
-> IO (GClosure C_ChildProxyChildAddedCallback)
-> m (GClosure C_ChildProxyChildAddedCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_ChildProxyChildAddedCallback
cb' = ChildProxyChildAddedCallback -> C_ChildProxyChildAddedCallback
wrap_ChildProxyChildAddedCallback ChildProxyChildAddedCallback
cb
    C_ChildProxyChildAddedCallback
-> IO (FunPtr C_ChildProxyChildAddedCallback)
mk_ChildProxyChildAddedCallback C_ChildProxyChildAddedCallback
cb' IO (FunPtr C_ChildProxyChildAddedCallback)
-> (FunPtr C_ChildProxyChildAddedCallback
    -> IO (GClosure C_ChildProxyChildAddedCallback))
-> IO (GClosure C_ChildProxyChildAddedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_ChildProxyChildAddedCallback
-> IO (GClosure C_ChildProxyChildAddedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `ChildProxyChildAddedCallback` into a `C_ChildProxyChildAddedCallback`.
wrap_ChildProxyChildAddedCallback ::
    ChildProxyChildAddedCallback ->
    C_ChildProxyChildAddedCallback
wrap_ChildProxyChildAddedCallback :: ChildProxyChildAddedCallback -> C_ChildProxyChildAddedCallback
wrap_ChildProxyChildAddedCallback ChildProxyChildAddedCallback
_cb Ptr ()
_ Ptr Object
object CString
name Ptr ()
_ = do
    Object
object' <- ((ManagedPtr Object -> Object) -> Ptr Object -> IO Object
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Object -> Object
GObject.Object.Object) Ptr Object
object
    Text
name' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
name
    ChildProxyChildAddedCallback
_cb  Object
object' Text
name'


-- | Connect a signal handler for the [childAdded](#signal:childAdded) 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' childProxy #childAdded callback
-- @
-- 
-- 
onChildProxyChildAdded :: (IsChildProxy a, MonadIO m) => a -> ChildProxyChildAddedCallback -> m SignalHandlerId
onChildProxyChildAdded :: forall a (m :: * -> *).
(IsChildProxy a, MonadIO m) =>
a -> ChildProxyChildAddedCallback -> m SignalHandlerId
onChildProxyChildAdded a
obj ChildProxyChildAddedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
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 cb' :: C_ChildProxyChildAddedCallback
cb' = ChildProxyChildAddedCallback -> C_ChildProxyChildAddedCallback
wrap_ChildProxyChildAddedCallback ChildProxyChildAddedCallback
cb
    FunPtr C_ChildProxyChildAddedCallback
cb'' <- C_ChildProxyChildAddedCallback
-> IO (FunPtr C_ChildProxyChildAddedCallback)
mk_ChildProxyChildAddedCallback C_ChildProxyChildAddedCallback
cb'
    a
-> Text
-> FunPtr C_ChildProxyChildAddedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"child-added" FunPtr C_ChildProxyChildAddedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [childAdded](#signal:childAdded) 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' childProxy #childAdded callback
-- @
-- 
-- 
afterChildProxyChildAdded :: (IsChildProxy a, MonadIO m) => a -> ChildProxyChildAddedCallback -> m SignalHandlerId
afterChildProxyChildAdded :: forall a (m :: * -> *).
(IsChildProxy a, MonadIO m) =>
a -> ChildProxyChildAddedCallback -> m SignalHandlerId
afterChildProxyChildAdded a
obj ChildProxyChildAddedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
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 cb' :: C_ChildProxyChildAddedCallback
cb' = ChildProxyChildAddedCallback -> C_ChildProxyChildAddedCallback
wrap_ChildProxyChildAddedCallback ChildProxyChildAddedCallback
cb
    FunPtr C_ChildProxyChildAddedCallback
cb'' <- C_ChildProxyChildAddedCallback
-> IO (FunPtr C_ChildProxyChildAddedCallback)
mk_ChildProxyChildAddedCallback C_ChildProxyChildAddedCallback
cb'
    a
-> Text
-> FunPtr C_ChildProxyChildAddedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"child-added" FunPtr C_ChildProxyChildAddedCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data ChildProxyChildAddedSignalInfo
instance SignalInfo ChildProxyChildAddedSignalInfo where
    type HaskellCallbackType ChildProxyChildAddedSignalInfo = ChildProxyChildAddedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_ChildProxyChildAddedCallback cb
        cb'' <- mk_ChildProxyChildAddedCallback cb'
        connectSignalFunPtr obj "child-added" cb'' connectMode detail

#endif

-- signal ChildProxy::child-removed
-- | Will be emitted after the /@object@/ was removed from the /@childProxy@/.
type ChildProxyChildRemovedCallback =
    GObject.Object.Object
    -- ^ /@object@/: the t'GI.GObject.Objects.Object.Object' that was removed
    -> T.Text
    -- ^ /@name@/: the name of the old child
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `ChildProxyChildRemovedCallback`@.
noChildProxyChildRemovedCallback :: Maybe ChildProxyChildRemovedCallback
noChildProxyChildRemovedCallback :: Maybe ChildProxyChildAddedCallback
noChildProxyChildRemovedCallback = Maybe ChildProxyChildAddedCallback
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_ChildProxyChildRemovedCallback =
    Ptr () ->                               -- object
    Ptr GObject.Object.Object ->
    CString ->
    Ptr () ->                               -- user_data
    IO ()

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

-- | Wrap the callback into a `GClosure`.
genClosure_ChildProxyChildRemoved :: MonadIO m => ChildProxyChildRemovedCallback -> m (GClosure C_ChildProxyChildRemovedCallback)
genClosure_ChildProxyChildRemoved :: forall (m :: * -> *).
MonadIO m =>
ChildProxyChildAddedCallback
-> m (GClosure C_ChildProxyChildAddedCallback)
genClosure_ChildProxyChildRemoved ChildProxyChildAddedCallback
cb = IO (GClosure C_ChildProxyChildAddedCallback)
-> m (GClosure C_ChildProxyChildAddedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_ChildProxyChildAddedCallback)
 -> m (GClosure C_ChildProxyChildAddedCallback))
-> IO (GClosure C_ChildProxyChildAddedCallback)
-> m (GClosure C_ChildProxyChildAddedCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_ChildProxyChildAddedCallback
cb' = ChildProxyChildAddedCallback -> C_ChildProxyChildAddedCallback
wrap_ChildProxyChildRemovedCallback ChildProxyChildAddedCallback
cb
    C_ChildProxyChildAddedCallback
-> IO (FunPtr C_ChildProxyChildAddedCallback)
mk_ChildProxyChildRemovedCallback C_ChildProxyChildAddedCallback
cb' IO (FunPtr C_ChildProxyChildAddedCallback)
-> (FunPtr C_ChildProxyChildAddedCallback
    -> IO (GClosure C_ChildProxyChildAddedCallback))
-> IO (GClosure C_ChildProxyChildAddedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_ChildProxyChildAddedCallback
-> IO (GClosure C_ChildProxyChildAddedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `ChildProxyChildRemovedCallback` into a `C_ChildProxyChildRemovedCallback`.
wrap_ChildProxyChildRemovedCallback ::
    ChildProxyChildRemovedCallback ->
    C_ChildProxyChildRemovedCallback
wrap_ChildProxyChildRemovedCallback :: ChildProxyChildAddedCallback -> C_ChildProxyChildAddedCallback
wrap_ChildProxyChildRemovedCallback ChildProxyChildAddedCallback
_cb Ptr ()
_ Ptr Object
object CString
name Ptr ()
_ = do
    Object
object' <- ((ManagedPtr Object -> Object) -> Ptr Object -> IO Object
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Object -> Object
GObject.Object.Object) Ptr Object
object
    Text
name' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
name
    ChildProxyChildAddedCallback
_cb  Object
object' Text
name'


-- | Connect a signal handler for the [childRemoved](#signal:childRemoved) 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' childProxy #childRemoved callback
-- @
-- 
-- 
onChildProxyChildRemoved :: (IsChildProxy a, MonadIO m) => a -> ChildProxyChildRemovedCallback -> m SignalHandlerId
onChildProxyChildRemoved :: forall a (m :: * -> *).
(IsChildProxy a, MonadIO m) =>
a -> ChildProxyChildAddedCallback -> m SignalHandlerId
onChildProxyChildRemoved a
obj ChildProxyChildAddedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
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 cb' :: C_ChildProxyChildAddedCallback
cb' = ChildProxyChildAddedCallback -> C_ChildProxyChildAddedCallback
wrap_ChildProxyChildRemovedCallback ChildProxyChildAddedCallback
cb
    FunPtr C_ChildProxyChildAddedCallback
cb'' <- C_ChildProxyChildAddedCallback
-> IO (FunPtr C_ChildProxyChildAddedCallback)
mk_ChildProxyChildRemovedCallback C_ChildProxyChildAddedCallback
cb'
    a
-> Text
-> FunPtr C_ChildProxyChildAddedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"child-removed" FunPtr C_ChildProxyChildAddedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [childRemoved](#signal:childRemoved) 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' childProxy #childRemoved callback
-- @
-- 
-- 
afterChildProxyChildRemoved :: (IsChildProxy a, MonadIO m) => a -> ChildProxyChildRemovedCallback -> m SignalHandlerId
afterChildProxyChildRemoved :: forall a (m :: * -> *).
(IsChildProxy a, MonadIO m) =>
a -> ChildProxyChildAddedCallback -> m SignalHandlerId
afterChildProxyChildRemoved a
obj ChildProxyChildAddedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
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 cb' :: C_ChildProxyChildAddedCallback
cb' = ChildProxyChildAddedCallback -> C_ChildProxyChildAddedCallback
wrap_ChildProxyChildRemovedCallback ChildProxyChildAddedCallback
cb
    FunPtr C_ChildProxyChildAddedCallback
cb'' <- C_ChildProxyChildAddedCallback
-> IO (FunPtr C_ChildProxyChildAddedCallback)
mk_ChildProxyChildRemovedCallback C_ChildProxyChildAddedCallback
cb'
    a
-> Text
-> FunPtr C_ChildProxyChildAddedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"child-removed" FunPtr C_ChildProxyChildAddedCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data ChildProxyChildRemovedSignalInfo
instance SignalInfo ChildProxyChildRemovedSignalInfo where
    type HaskellCallbackType ChildProxyChildRemovedSignalInfo = ChildProxyChildRemovedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_ChildProxyChildRemovedCallback cb
        cb'' <- mk_ChildProxyChildRemovedCallback cb'
        connectSignalFunPtr obj "child-removed" cb'' connectMode detail

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList ChildProxy = ChildProxySignalList
type ChildProxySignalList = ('[ '("childAdded", ChildProxyChildAddedSignalInfo), '("childRemoved", ChildProxyChildRemovedSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif