{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A collection of t'GI.Gst.Objects.Stream.Stream' that are available.
-- 
-- A t'GI.Gst.Objects.StreamCollection.StreamCollection' will be provided by elements that can make those
-- streams available. Applications can use the collection to show the user
-- what streams are available by using @/gst_stream_collection_get_stream/@()
-- 
-- Once posted, a t'GI.Gst.Objects.StreamCollection.StreamCollection' is immutable. Updates are made by sending
-- a new t'GI.Gst.Objects.StreamCollection.StreamCollection' message, which may or may not share some of
-- the t'GI.Gst.Objects.Stream.Stream' objects from the collection it replaces. The receiver can check
-- the sender of a stream collection message to know which collection is
-- obsoleted.
-- 
-- Several elements in a pipeline can provide t'GI.Gst.Objects.StreamCollection.StreamCollection'.
-- 
-- Applications can activate streams from a collection by using the
-- @/GST_EVENT_SELECT_STREAMS/@ event on a pipeline, bin or element.
-- 
-- /Since: 1.10/

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

module GI.Gst.Objects.StreamCollection
    ( 

-- * Exported types
    StreamCollection(..)                    ,
    IsStreamCollection                      ,
    toStreamCollection                      ,


 -- * Methods
-- ** Overloaded methods #method:Overloaded methods#

#if defined(ENABLE_OVERLOADING)
    ResolveStreamCollectionMethod           ,
#endif


-- ** addStream #method:addStream#

#if defined(ENABLE_OVERLOADING)
    StreamCollectionAddStreamMethodInfo     ,
#endif
    streamCollectionAddStream               ,


-- ** getSize #method:getSize#

#if defined(ENABLE_OVERLOADING)
    StreamCollectionGetSizeMethodInfo       ,
#endif
    streamCollectionGetSize                 ,


-- ** getStream #method:getStream#

#if defined(ENABLE_OVERLOADING)
    StreamCollectionGetStreamMethodInfo     ,
#endif
    streamCollectionGetStream               ,


-- ** getUpstreamId #method:getUpstreamId#

#if defined(ENABLE_OVERLOADING)
    StreamCollectionGetUpstreamIdMethodInfo ,
#endif
    streamCollectionGetUpstreamId           ,


-- ** new #method:new#

    streamCollectionNew                     ,




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

#if defined(ENABLE_OVERLOADING)
    StreamCollectionUpstreamIdPropertyInfo  ,
#endif
    clearStreamCollectionUpstreamId         ,
    constructStreamCollectionUpstreamId     ,
    getStreamCollectionUpstreamId           ,
    setStreamCollectionUpstreamId           ,
#if defined(ENABLE_OVERLOADING)
    streamCollectionUpstreamId              ,
#endif




 -- * Signals
-- ** streamNotify #signal:streamNotify#

    C_StreamCollectionStreamNotifyCallback  ,
    StreamCollectionStreamNotifyCallback    ,
#if defined(ENABLE_OVERLOADING)
    StreamCollectionStreamNotifySignalInfo  ,
#endif
    afterStreamCollectionStreamNotify       ,
    genClosure_StreamCollectionStreamNotify ,
    mk_StreamCollectionStreamNotifyCallback ,
    noStreamCollectionStreamNotifyCallback  ,
    onStreamCollectionStreamNotify          ,
    wrap_StreamCollectionStreamNotifyCallback,




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

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

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

foreign import ccall "gst_stream_collection_get_type"
    c_gst_stream_collection_get_type :: IO B.Types.GType

instance B.Types.TypedObject StreamCollection where
    glibType :: IO GType
glibType = IO GType
c_gst_stream_collection_get_type

instance B.Types.GObject StreamCollection

-- | Convert 'StreamCollection' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue StreamCollection where
    toGValue :: StreamCollection -> IO GValue
toGValue StreamCollection
o = do
        GType
gtype <- IO GType
c_gst_stream_collection_get_type
        StreamCollection
-> (Ptr StreamCollection -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr StreamCollection
o (GType
-> (GValue -> Ptr StreamCollection -> IO ())
-> Ptr StreamCollection
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr StreamCollection -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
        
    fromGValue :: GValue -> IO StreamCollection
fromGValue GValue
gv = do
        Ptr StreamCollection
ptr <- GValue -> IO (Ptr StreamCollection)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr StreamCollection)
        (ManagedPtr StreamCollection -> StreamCollection)
-> Ptr StreamCollection -> IO StreamCollection
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr StreamCollection -> StreamCollection
StreamCollection Ptr StreamCollection
ptr
        
    

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

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

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

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

instance (info ~ ResolveStreamCollectionMethod t StreamCollection, O.MethodInfo info StreamCollection p) => OL.IsLabel t (StreamCollection -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#endif

-- signal StreamCollection::stream-notify
-- | /No description available in the introspection data./
type StreamCollectionStreamNotifyCallback =
    Gst.Stream.Stream
    -> GParamSpec
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `StreamCollectionStreamNotifyCallback`@.
noStreamCollectionStreamNotifyCallback :: Maybe StreamCollectionStreamNotifyCallback
noStreamCollectionStreamNotifyCallback :: Maybe StreamCollectionStreamNotifyCallback
noStreamCollectionStreamNotifyCallback = Maybe StreamCollectionStreamNotifyCallback
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_StreamCollectionStreamNotifyCallback =
    Ptr () ->                               -- object
    Ptr Gst.Stream.Stream ->
    Ptr GParamSpec ->
    Ptr () ->                               -- user_data
    IO ()

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

-- | Wrap the callback into a `GClosure`.
genClosure_StreamCollectionStreamNotify :: MonadIO m => StreamCollectionStreamNotifyCallback -> m (GClosure C_StreamCollectionStreamNotifyCallback)
genClosure_StreamCollectionStreamNotify :: StreamCollectionStreamNotifyCallback
-> m (GClosure C_StreamCollectionStreamNotifyCallback)
genClosure_StreamCollectionStreamNotify StreamCollectionStreamNotifyCallback
cb = IO (GClosure C_StreamCollectionStreamNotifyCallback)
-> m (GClosure C_StreamCollectionStreamNotifyCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_StreamCollectionStreamNotifyCallback)
 -> m (GClosure C_StreamCollectionStreamNotifyCallback))
-> IO (GClosure C_StreamCollectionStreamNotifyCallback)
-> m (GClosure C_StreamCollectionStreamNotifyCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_StreamCollectionStreamNotifyCallback
cb' = StreamCollectionStreamNotifyCallback
-> C_StreamCollectionStreamNotifyCallback
wrap_StreamCollectionStreamNotifyCallback StreamCollectionStreamNotifyCallback
cb
    C_StreamCollectionStreamNotifyCallback
-> IO (FunPtr C_StreamCollectionStreamNotifyCallback)
mk_StreamCollectionStreamNotifyCallback C_StreamCollectionStreamNotifyCallback
cb' IO (FunPtr C_StreamCollectionStreamNotifyCallback)
-> (FunPtr C_StreamCollectionStreamNotifyCallback
    -> IO (GClosure C_StreamCollectionStreamNotifyCallback))
-> IO (GClosure C_StreamCollectionStreamNotifyCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_StreamCollectionStreamNotifyCallback
-> IO (GClosure C_StreamCollectionStreamNotifyCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `StreamCollectionStreamNotifyCallback` into a `C_StreamCollectionStreamNotifyCallback`.
wrap_StreamCollectionStreamNotifyCallback ::
    StreamCollectionStreamNotifyCallback ->
    C_StreamCollectionStreamNotifyCallback
wrap_StreamCollectionStreamNotifyCallback :: StreamCollectionStreamNotifyCallback
-> C_StreamCollectionStreamNotifyCallback
wrap_StreamCollectionStreamNotifyCallback StreamCollectionStreamNotifyCallback
_cb Ptr ()
_ Ptr Stream
object Ptr GParamSpec
p0 Ptr ()
_ = do
    Stream
object' <- ((ManagedPtr Stream -> Stream) -> Ptr Stream -> IO Stream
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Stream -> Stream
Gst.Stream.Stream) Ptr Stream
object
    GParamSpec
p0' <- Ptr GParamSpec -> IO GParamSpec
B.GParamSpec.newGParamSpecFromPtr Ptr GParamSpec
p0
    StreamCollectionStreamNotifyCallback
_cb  Stream
object' GParamSpec
p0'


-- | Connect a signal handler for the [streamNotify](#signal:streamNotify) 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' streamCollection #streamNotify callback
-- @
-- 
-- This signal admits a optional parameter @detail@.
-- If it's not @Nothing@, we will connect to “@stream-notify::detail@” instead.
-- 
onStreamCollectionStreamNotify :: (IsStreamCollection a, MonadIO m) => a -> P.Maybe T.Text -> StreamCollectionStreamNotifyCallback -> m SignalHandlerId
onStreamCollectionStreamNotify :: a
-> Maybe Text
-> StreamCollectionStreamNotifyCallback
-> m SignalHandlerId
onStreamCollectionStreamNotify a
obj Maybe Text
detail StreamCollectionStreamNotifyCallback
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_StreamCollectionStreamNotifyCallback
cb' = StreamCollectionStreamNotifyCallback
-> C_StreamCollectionStreamNotifyCallback
wrap_StreamCollectionStreamNotifyCallback StreamCollectionStreamNotifyCallback
cb
    FunPtr C_StreamCollectionStreamNotifyCallback
cb'' <- C_StreamCollectionStreamNotifyCallback
-> IO (FunPtr C_StreamCollectionStreamNotifyCallback)
mk_StreamCollectionStreamNotifyCallback C_StreamCollectionStreamNotifyCallback
cb'
    a
-> Text
-> FunPtr C_StreamCollectionStreamNotifyCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"stream-notify" FunPtr C_StreamCollectionStreamNotifyCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
detail

-- | Connect a signal handler for the [streamNotify](#signal:streamNotify) 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' streamCollection #streamNotify callback
-- @
-- 
-- This signal admits a optional parameter @detail@.
-- If it's not @Nothing@, we will connect to “@stream-notify::detail@” instead.
-- 
afterStreamCollectionStreamNotify :: (IsStreamCollection a, MonadIO m) => a -> P.Maybe T.Text -> StreamCollectionStreamNotifyCallback -> m SignalHandlerId
afterStreamCollectionStreamNotify :: a
-> Maybe Text
-> StreamCollectionStreamNotifyCallback
-> m SignalHandlerId
afterStreamCollectionStreamNotify a
obj Maybe Text
detail StreamCollectionStreamNotifyCallback
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_StreamCollectionStreamNotifyCallback
cb' = StreamCollectionStreamNotifyCallback
-> C_StreamCollectionStreamNotifyCallback
wrap_StreamCollectionStreamNotifyCallback StreamCollectionStreamNotifyCallback
cb
    FunPtr C_StreamCollectionStreamNotifyCallback
cb'' <- C_StreamCollectionStreamNotifyCallback
-> IO (FunPtr C_StreamCollectionStreamNotifyCallback)
mk_StreamCollectionStreamNotifyCallback C_StreamCollectionStreamNotifyCallback
cb'
    a
-> Text
-> FunPtr C_StreamCollectionStreamNotifyCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"stream-notify" FunPtr C_StreamCollectionStreamNotifyCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
detail


#if defined(ENABLE_OVERLOADING)
data StreamCollectionStreamNotifySignalInfo
instance SignalInfo StreamCollectionStreamNotifySignalInfo where
    type HaskellCallbackType StreamCollectionStreamNotifySignalInfo = StreamCollectionStreamNotifyCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_StreamCollectionStreamNotifyCallback cb
        cb'' <- mk_StreamCollectionStreamNotifyCallback cb'
        connectSignalFunPtr obj "stream-notify" cb'' connectMode detail

#endif

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

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

-- | Set the value of the “@upstream-id@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' streamCollection [ #upstreamId 'Data.GI.Base.Attributes.:=' value ]
-- @
setStreamCollectionUpstreamId :: (MonadIO m, IsStreamCollection o) => o -> T.Text -> m ()
setStreamCollectionUpstreamId :: o -> Text -> m ()
setStreamCollectionUpstreamId o
obj Text
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"upstream-id" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

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

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

#if defined(ENABLE_OVERLOADING)
data StreamCollectionUpstreamIdPropertyInfo
instance AttrInfo StreamCollectionUpstreamIdPropertyInfo where
    type AttrAllowedOps StreamCollectionUpstreamIdPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint StreamCollectionUpstreamIdPropertyInfo = IsStreamCollection
    type AttrSetTypeConstraint StreamCollectionUpstreamIdPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint StreamCollectionUpstreamIdPropertyInfo = (~) T.Text
    type AttrTransferType StreamCollectionUpstreamIdPropertyInfo = T.Text
    type AttrGetType StreamCollectionUpstreamIdPropertyInfo = T.Text
    type AttrLabel StreamCollectionUpstreamIdPropertyInfo = "upstream-id"
    type AttrOrigin StreamCollectionUpstreamIdPropertyInfo = StreamCollection
    attrGet = getStreamCollectionUpstreamId
    attrSet = setStreamCollectionUpstreamId
    attrTransfer _ v = do
        return v
    attrConstruct = constructStreamCollectionUpstreamId
    attrClear = clearStreamCollectionUpstreamId
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList StreamCollection
type instance O.AttributeList StreamCollection = StreamCollectionAttributeList
type StreamCollectionAttributeList = ('[ '("name", Gst.Object.ObjectNamePropertyInfo), '("parent", Gst.Object.ObjectParentPropertyInfo), '("upstreamId", StreamCollectionUpstreamIdPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
streamCollectionUpstreamId :: AttrLabelProxy "upstreamId"
streamCollectionUpstreamId = AttrLabelProxy

#endif

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

#endif

-- method StreamCollection::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "upstream_id"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The stream id of the parent stream"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gst" , name = "StreamCollection" })
-- throws : False
-- Skip return : False

foreign import ccall "gst_stream_collection_new" gst_stream_collection_new :: 
    CString ->                              -- upstream_id : TBasicType TUTF8
    IO (Ptr StreamCollection)

-- | Create a new t'GI.Gst.Objects.StreamCollection.StreamCollection'.
-- 
-- /Since: 1.10/
streamCollectionNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Maybe (T.Text)
    -- ^ /@upstreamId@/: The stream id of the parent stream
    -> m StreamCollection
    -- ^ __Returns:__ The new t'GI.Gst.Objects.StreamCollection.StreamCollection'.
streamCollectionNew :: Maybe Text -> m StreamCollection
streamCollectionNew Maybe Text
upstreamId = IO StreamCollection -> m StreamCollection
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO StreamCollection -> m StreamCollection)
-> IO StreamCollection -> m StreamCollection
forall a b. (a -> b) -> a -> b
$ do
    Ptr CChar
maybeUpstreamId <- case Maybe Text
upstreamId of
        Maybe Text
Nothing -> Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
nullPtr
        Just Text
jUpstreamId -> do
            Ptr CChar
jUpstreamId' <- Text -> IO (Ptr CChar)
textToCString Text
jUpstreamId
            Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
jUpstreamId'
    Ptr StreamCollection
result <- Ptr CChar -> IO (Ptr StreamCollection)
gst_stream_collection_new Ptr CChar
maybeUpstreamId
    Text -> Ptr StreamCollection -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"streamCollectionNew" Ptr StreamCollection
result
    StreamCollection
result' <- ((ManagedPtr StreamCollection -> StreamCollection)
-> Ptr StreamCollection -> IO StreamCollection
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr StreamCollection -> StreamCollection
StreamCollection) Ptr StreamCollection
result
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
maybeUpstreamId
    StreamCollection -> IO StreamCollection
forall (m :: * -> *) a. Monad m => a -> m a
return StreamCollection
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method StreamCollection::add_stream
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "collection"
--           , argType =
--               TInterface Name { namespace = "Gst" , name = "StreamCollection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstStreamCollection"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "stream"
--           , argType = TInterface Name { namespace = "Gst" , name = "Stream" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #GstStream to add"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gst_stream_collection_add_stream" gst_stream_collection_add_stream :: 
    Ptr StreamCollection ->                 -- collection : TInterface (Name {namespace = "Gst", name = "StreamCollection"})
    Ptr Gst.Stream.Stream ->                -- stream : TInterface (Name {namespace = "Gst", name = "Stream"})
    IO CInt

-- | Add the given /@stream@/ to the /@collection@/.
-- 
-- /Since: 1.10/
streamCollectionAddStream ::
    (B.CallStack.HasCallStack, MonadIO m, IsStreamCollection a, Gst.Stream.IsStream b) =>
    a
    -- ^ /@collection@/: a t'GI.Gst.Objects.StreamCollection.StreamCollection'
    -> b
    -- ^ /@stream@/: the t'GI.Gst.Objects.Stream.Stream' to add
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the /@stream@/ was properly added, else 'P.False'
streamCollectionAddStream :: a -> b -> m Bool
streamCollectionAddStream a
collection b
stream = 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 StreamCollection
collection' <- a -> IO (Ptr StreamCollection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
collection
    Ptr Stream
stream' <- b -> IO (Ptr Stream)
forall a b. (HasCallStack, GObject a) => a -> IO (Ptr b)
B.ManagedPtr.disownObject b
stream
    CInt
result <- Ptr StreamCollection -> Ptr Stream -> IO CInt
gst_stream_collection_add_stream Ptr StreamCollection
collection' Ptr Stream
stream'
    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
collection
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
stream
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data StreamCollectionAddStreamMethodInfo
instance (signature ~ (b -> m Bool), MonadIO m, IsStreamCollection a, Gst.Stream.IsStream b) => O.MethodInfo StreamCollectionAddStreamMethodInfo a signature where
    overloadedMethod = streamCollectionAddStream

#endif

-- method StreamCollection::get_size
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "collection"
--           , argType =
--               TInterface Name { namespace = "Gst" , name = "StreamCollection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstStreamCollection"
--                 , 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_stream_collection_get_size" gst_stream_collection_get_size :: 
    Ptr StreamCollection ->                 -- collection : TInterface (Name {namespace = "Gst", name = "StreamCollection"})
    IO Word32

-- | Get the number of streams this collection contains
-- 
-- /Since: 1.10/
streamCollectionGetSize ::
    (B.CallStack.HasCallStack, MonadIO m, IsStreamCollection a) =>
    a
    -- ^ /@collection@/: a t'GI.Gst.Objects.StreamCollection.StreamCollection'
    -> m Word32
    -- ^ __Returns:__ The number of streams that /@collection@/ contains
streamCollectionGetSize :: a -> m Word32
streamCollectionGetSize a
collection = 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 StreamCollection
collection' <- a -> IO (Ptr StreamCollection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
collection
    Word32
result <- Ptr StreamCollection -> IO Word32
gst_stream_collection_get_size Ptr StreamCollection
collection'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
collection
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data StreamCollectionGetSizeMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsStreamCollection a) => O.MethodInfo StreamCollectionGetSizeMethodInfo a signature where
    overloadedMethod = streamCollectionGetSize

#endif

-- method StreamCollection::get_stream
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "collection"
--           , argType =
--               TInterface Name { namespace = "Gst" , name = "StreamCollection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstStreamCollection"
--                 , 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 "Index of the stream to retrieve"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gst" , name = "Stream" })
-- throws : False
-- Skip return : False

foreign import ccall "gst_stream_collection_get_stream" gst_stream_collection_get_stream :: 
    Ptr StreamCollection ->                 -- collection : TInterface (Name {namespace = "Gst", name = "StreamCollection"})
    Word32 ->                               -- index : TBasicType TUInt
    IO (Ptr Gst.Stream.Stream)

-- | Retrieve the t'GI.Gst.Objects.Stream.Stream' with index /@index@/ from the collection.
-- 
-- The caller should not modify the returned t'GI.Gst.Objects.Stream.Stream'
-- 
-- /Since: 1.10/
streamCollectionGetStream ::
    (B.CallStack.HasCallStack, MonadIO m, IsStreamCollection a) =>
    a
    -- ^ /@collection@/: a t'GI.Gst.Objects.StreamCollection.StreamCollection'
    -> Word32
    -- ^ /@index@/: Index of the stream to retrieve
    -> m (Maybe Gst.Stream.Stream)
    -- ^ __Returns:__ A t'GI.Gst.Objects.Stream.Stream'
streamCollectionGetStream :: a -> Word32 -> m (Maybe Stream)
streamCollectionGetStream a
collection Word32
index = IO (Maybe Stream) -> m (Maybe Stream)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Stream) -> m (Maybe Stream))
-> IO (Maybe Stream) -> m (Maybe Stream)
forall a b. (a -> b) -> a -> b
$ do
    Ptr StreamCollection
collection' <- a -> IO (Ptr StreamCollection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
collection
    Ptr Stream
result <- Ptr StreamCollection -> Word32 -> IO (Ptr Stream)
gst_stream_collection_get_stream Ptr StreamCollection
collection' Word32
index
    Maybe Stream
maybeResult <- Ptr Stream -> (Ptr Stream -> IO Stream) -> IO (Maybe Stream)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Stream
result ((Ptr Stream -> IO Stream) -> IO (Maybe Stream))
-> (Ptr Stream -> IO Stream) -> IO (Maybe Stream)
forall a b. (a -> b) -> a -> b
$ \Ptr Stream
result' -> do
        Stream
result'' <- ((ManagedPtr Stream -> Stream) -> Ptr Stream -> IO Stream
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Stream -> Stream
Gst.Stream.Stream) Ptr Stream
result'
        Stream -> IO Stream
forall (m :: * -> *) a. Monad m => a -> m a
return Stream
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
collection
    Maybe Stream -> IO (Maybe Stream)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Stream
maybeResult

#if defined(ENABLE_OVERLOADING)
data StreamCollectionGetStreamMethodInfo
instance (signature ~ (Word32 -> m (Maybe Gst.Stream.Stream)), MonadIO m, IsStreamCollection a) => O.MethodInfo StreamCollectionGetStreamMethodInfo a signature where
    overloadedMethod = streamCollectionGetStream

#endif

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

foreign import ccall "gst_stream_collection_get_upstream_id" gst_stream_collection_get_upstream_id :: 
    Ptr StreamCollection ->                 -- collection : TInterface (Name {namespace = "Gst", name = "StreamCollection"})
    IO CString

-- | Returns the upstream id of the /@collection@/.
-- 
-- /Since: 1.10/
streamCollectionGetUpstreamId ::
    (B.CallStack.HasCallStack, MonadIO m, IsStreamCollection a) =>
    a
    -- ^ /@collection@/: a t'GI.Gst.Objects.StreamCollection.StreamCollection'
    -> m T.Text
    -- ^ __Returns:__ The upstream id
streamCollectionGetUpstreamId :: a -> m Text
streamCollectionGetUpstreamId a
collection = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr StreamCollection
collection' <- a -> IO (Ptr StreamCollection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
collection
    Ptr CChar
result <- Ptr StreamCollection -> IO (Ptr CChar)
gst_stream_collection_get_upstream_id Ptr StreamCollection
collection'
    Text -> Ptr CChar -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"streamCollectionGetUpstreamId" Ptr CChar
result
    Text
result' <- HasCallStack => Ptr CChar -> IO Text
Ptr CChar -> IO Text
cstringToText Ptr CChar
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
collection
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data StreamCollectionGetUpstreamIdMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsStreamCollection a) => O.MethodInfo StreamCollectionGetUpstreamIdMethodInfo a signature where
    overloadedMethod = streamCollectionGetUpstreamId

#endif