{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Subclasses must use (a subclass of) t'GI.GstAudio.Objects.AudioAggregatorPad.AudioAggregatorPad' for both
-- their source and sink pads,
-- 'GI.Gst.Structs.ElementClass.elementClassAddStaticPadTemplateWithGtype' is a convenient
-- helper.
-- 
-- t'GI.GstAudio.Objects.AudioAggregator.AudioAggregator' can perform conversion on the data arriving
-- on its sink pads, based on the format expected downstream: in order
-- to enable that behaviour, the GType of the sink pads must either be
-- a (subclass of) t'GI.GstAudio.Objects.AudioAggregatorConvertPad.AudioAggregatorConvertPad' to use the default
-- t'GI.GstAudio.Structs.AudioConverter.AudioConverter' implementation, or a subclass of t'GI.GstAudio.Objects.AudioAggregatorPad.AudioAggregatorPad'
-- implementing t'GI.GstAudio.Structs.AudioAggregatorPadClass.AudioAggregatorPadClass'.@/convert_buffer/@.
-- 
-- To allow for the output caps to change, the mechanism is the same as
-- above, with the GType of the source pad.
-- 
-- See @/GstAudioMixer/@ for an example.
-- 
-- When conversion is enabled, t'GI.GstAudio.Objects.AudioAggregator.AudioAggregator' will accept
-- any type of raw audio caps and perform conversion
-- on the data arriving on its sink pads, with whatever downstream
-- expects as the target format.
-- 
-- In case downstream caps are not fully fixated, it will use
-- the first configured sink pad to finish fixating its source pad
-- caps.
-- 
-- A notable exception for now is the sample rate, sink pads must
-- have the same sample rate as either the downstream requirement,
-- or the first configured pad, or a combination of both (when
-- downstream specifies a range or a set of acceptable rates).

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

module GI.GstAudio.Objects.AudioAggregator
    ( 

-- * Exported types
    AudioAggregator(..)                     ,
    IsAudioAggregator                       ,
    toAudioAggregator                       ,
    noAudioAggregator                       ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveAudioAggregatorMethod            ,
#endif


-- ** setSinkCaps #method:setSinkCaps#

#if defined(ENABLE_OVERLOADING)
    AudioAggregatorSetSinkCapsMethodInfo    ,
#endif
    audioAggregatorSetSinkCaps              ,




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

#if defined(ENABLE_OVERLOADING)
    AudioAggregatorAlignmentThresholdPropertyInfo,
#endif
#if defined(ENABLE_OVERLOADING)
    audioAggregatorAlignmentThreshold       ,
#endif
    constructAudioAggregatorAlignmentThreshold,
    getAudioAggregatorAlignmentThreshold    ,
    setAudioAggregatorAlignmentThreshold    ,


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

#if defined(ENABLE_OVERLOADING)
    AudioAggregatorDiscontWaitPropertyInfo  ,
#endif
#if defined(ENABLE_OVERLOADING)
    audioAggregatorDiscontWait              ,
#endif
    constructAudioAggregatorDiscontWait     ,
    getAudioAggregatorDiscontWait           ,
    setAudioAggregatorDiscontWait           ,


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

#if defined(ENABLE_OVERLOADING)
    AudioAggregatorOutputBufferDurationPropertyInfo,
#endif
#if defined(ENABLE_OVERLOADING)
    audioAggregatorOutputBufferDuration     ,
#endif
    constructAudioAggregatorOutputBufferDuration,
    getAudioAggregatorOutputBufferDuration  ,
    setAudioAggregatorOutputBufferDuration  ,




    ) 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.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 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 qualified GI.Gst.Objects.Element as Gst.Element
import qualified GI.Gst.Objects.Object as Gst.Object
import qualified GI.Gst.Structs.Caps as Gst.Caps
import {-# SOURCE #-} qualified GI.GstAudio.Objects.AudioAggregatorPad as GstAudio.AudioAggregatorPad
import qualified GI.GstBase.Objects.Aggregator as GstBase.Aggregator

-- | Memory-managed wrapper type.
newtype AudioAggregator = AudioAggregator (ManagedPtr AudioAggregator)
    deriving (AudioAggregator -> AudioAggregator -> Bool
(AudioAggregator -> AudioAggregator -> Bool)
-> (AudioAggregator -> AudioAggregator -> Bool)
-> Eq AudioAggregator
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AudioAggregator -> AudioAggregator -> Bool
$c/= :: AudioAggregator -> AudioAggregator -> Bool
== :: AudioAggregator -> AudioAggregator -> Bool
$c== :: AudioAggregator -> AudioAggregator -> Bool
Eq)
foreign import ccall "gst_audio_aggregator_get_type"
    c_gst_audio_aggregator_get_type :: IO GType

instance GObject AudioAggregator where
    gobjectType :: IO GType
gobjectType = IO GType
c_gst_audio_aggregator_get_type
    

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

-- | Type class for types which can be safely cast to `AudioAggregator`, for instance with `toAudioAggregator`.
class (GObject o, O.IsDescendantOf AudioAggregator o) => IsAudioAggregator o
instance (GObject o, O.IsDescendantOf AudioAggregator o) => IsAudioAggregator o

instance O.HasParentTypes AudioAggregator
type instance O.ParentTypes AudioAggregator = '[GstBase.Aggregator.Aggregator, Gst.Element.Element, Gst.Object.Object, GObject.Object.Object]

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

-- | A convenience alias for `Nothing` :: `Maybe` `AudioAggregator`.
noAudioAggregator :: Maybe AudioAggregator
noAudioAggregator :: Maybe AudioAggregator
noAudioAggregator = Maybe AudioAggregator
forall a. Maybe a
Nothing

#if defined(ENABLE_OVERLOADING)
type family ResolveAudioAggregatorMethod (t :: Symbol) (o :: *) :: * where
    ResolveAudioAggregatorMethod "abortState" o = Gst.Element.ElementAbortStateMethodInfo
    ResolveAudioAggregatorMethod "addControlBinding" o = Gst.Object.ObjectAddControlBindingMethodInfo
    ResolveAudioAggregatorMethod "addPad" o = Gst.Element.ElementAddPadMethodInfo
    ResolveAudioAggregatorMethod "addPropertyDeepNotifyWatch" o = Gst.Element.ElementAddPropertyDeepNotifyWatchMethodInfo
    ResolveAudioAggregatorMethod "addPropertyNotifyWatch" o = Gst.Element.ElementAddPropertyNotifyWatchMethodInfo
    ResolveAudioAggregatorMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveAudioAggregatorMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveAudioAggregatorMethod "callAsync" o = Gst.Element.ElementCallAsyncMethodInfo
    ResolveAudioAggregatorMethod "changeState" o = Gst.Element.ElementChangeStateMethodInfo
    ResolveAudioAggregatorMethod "continueState" o = Gst.Element.ElementContinueStateMethodInfo
    ResolveAudioAggregatorMethod "createAllPads" o = Gst.Element.ElementCreateAllPadsMethodInfo
    ResolveAudioAggregatorMethod "defaultError" o = Gst.Object.ObjectDefaultErrorMethodInfo
    ResolveAudioAggregatorMethod "finishBuffer" o = GstBase.Aggregator.AggregatorFinishBufferMethodInfo
    ResolveAudioAggregatorMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveAudioAggregatorMethod "foreachPad" o = Gst.Element.ElementForeachPadMethodInfo
    ResolveAudioAggregatorMethod "foreachSinkPad" o = Gst.Element.ElementForeachSinkPadMethodInfo
    ResolveAudioAggregatorMethod "foreachSrcPad" o = Gst.Element.ElementForeachSrcPadMethodInfo
    ResolveAudioAggregatorMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveAudioAggregatorMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveAudioAggregatorMethod "hasActiveControlBindings" o = Gst.Object.ObjectHasActiveControlBindingsMethodInfo
    ResolveAudioAggregatorMethod "hasAncestor" o = Gst.Object.ObjectHasAncestorMethodInfo
    ResolveAudioAggregatorMethod "hasAsAncestor" o = Gst.Object.ObjectHasAsAncestorMethodInfo
    ResolveAudioAggregatorMethod "hasAsParent" o = Gst.Object.ObjectHasAsParentMethodInfo
    ResolveAudioAggregatorMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveAudioAggregatorMethod "isLockedState" o = Gst.Element.ElementIsLockedStateMethodInfo
    ResolveAudioAggregatorMethod "iteratePads" o = Gst.Element.ElementIteratePadsMethodInfo
    ResolveAudioAggregatorMethod "iterateSinkPads" o = Gst.Element.ElementIterateSinkPadsMethodInfo
    ResolveAudioAggregatorMethod "iterateSrcPads" o = Gst.Element.ElementIterateSrcPadsMethodInfo
    ResolveAudioAggregatorMethod "link" o = Gst.Element.ElementLinkMethodInfo
    ResolveAudioAggregatorMethod "linkFiltered" o = Gst.Element.ElementLinkFilteredMethodInfo
    ResolveAudioAggregatorMethod "linkPads" o = Gst.Element.ElementLinkPadsMethodInfo
    ResolveAudioAggregatorMethod "linkPadsFiltered" o = Gst.Element.ElementLinkPadsFilteredMethodInfo
    ResolveAudioAggregatorMethod "linkPadsFull" o = Gst.Element.ElementLinkPadsFullMethodInfo
    ResolveAudioAggregatorMethod "lostState" o = Gst.Element.ElementLostStateMethodInfo
    ResolveAudioAggregatorMethod "messageFull" o = Gst.Element.ElementMessageFullMethodInfo
    ResolveAudioAggregatorMethod "messageFullWithDetails" o = Gst.Element.ElementMessageFullWithDetailsMethodInfo
    ResolveAudioAggregatorMethod "noMorePads" o = Gst.Element.ElementNoMorePadsMethodInfo
    ResolveAudioAggregatorMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveAudioAggregatorMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveAudioAggregatorMethod "postMessage" o = Gst.Element.ElementPostMessageMethodInfo
    ResolveAudioAggregatorMethod "provideClock" o = Gst.Element.ElementProvideClockMethodInfo
    ResolveAudioAggregatorMethod "query" o = Gst.Element.ElementQueryMethodInfo
    ResolveAudioAggregatorMethod "queryConvert" o = Gst.Element.ElementQueryConvertMethodInfo
    ResolveAudioAggregatorMethod "queryDuration" o = Gst.Element.ElementQueryDurationMethodInfo
    ResolveAudioAggregatorMethod "queryPosition" o = Gst.Element.ElementQueryPositionMethodInfo
    ResolveAudioAggregatorMethod "ref" o = Gst.Object.ObjectRefMethodInfo
    ResolveAudioAggregatorMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveAudioAggregatorMethod "releaseRequestPad" o = Gst.Element.ElementReleaseRequestPadMethodInfo
    ResolveAudioAggregatorMethod "removeControlBinding" o = Gst.Object.ObjectRemoveControlBindingMethodInfo
    ResolveAudioAggregatorMethod "removePad" o = Gst.Element.ElementRemovePadMethodInfo
    ResolveAudioAggregatorMethod "removePropertyNotifyWatch" o = Gst.Element.ElementRemovePropertyNotifyWatchMethodInfo
    ResolveAudioAggregatorMethod "requestPad" o = Gst.Element.ElementRequestPadMethodInfo
    ResolveAudioAggregatorMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveAudioAggregatorMethod "seek" o = Gst.Element.ElementSeekMethodInfo
    ResolveAudioAggregatorMethod "seekSimple" o = Gst.Element.ElementSeekSimpleMethodInfo
    ResolveAudioAggregatorMethod "sendEvent" o = Gst.Element.ElementSendEventMethodInfo
    ResolveAudioAggregatorMethod "simpleGetNextTime" o = GstBase.Aggregator.AggregatorSimpleGetNextTimeMethodInfo
    ResolveAudioAggregatorMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveAudioAggregatorMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveAudioAggregatorMethod "suggestNextSync" o = Gst.Object.ObjectSuggestNextSyncMethodInfo
    ResolveAudioAggregatorMethod "syncStateWithParent" o = Gst.Element.ElementSyncStateWithParentMethodInfo
    ResolveAudioAggregatorMethod "syncValues" o = Gst.Object.ObjectSyncValuesMethodInfo
    ResolveAudioAggregatorMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveAudioAggregatorMethod "unlink" o = Gst.Element.ElementUnlinkMethodInfo
    ResolveAudioAggregatorMethod "unlinkPads" o = Gst.Element.ElementUnlinkPadsMethodInfo
    ResolveAudioAggregatorMethod "unparent" o = Gst.Object.ObjectUnparentMethodInfo
    ResolveAudioAggregatorMethod "unref" o = Gst.Object.ObjectUnrefMethodInfo
    ResolveAudioAggregatorMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveAudioAggregatorMethod "getAllocator" o = GstBase.Aggregator.AggregatorGetAllocatorMethodInfo
    ResolveAudioAggregatorMethod "getBaseTime" o = Gst.Element.ElementGetBaseTimeMethodInfo
    ResolveAudioAggregatorMethod "getBufferPool" o = GstBase.Aggregator.AggregatorGetBufferPoolMethodInfo
    ResolveAudioAggregatorMethod "getBus" o = Gst.Element.ElementGetBusMethodInfo
    ResolveAudioAggregatorMethod "getClock" o = Gst.Element.ElementGetClockMethodInfo
    ResolveAudioAggregatorMethod "getCompatiblePad" o = Gst.Element.ElementGetCompatiblePadMethodInfo
    ResolveAudioAggregatorMethod "getCompatiblePadTemplate" o = Gst.Element.ElementGetCompatiblePadTemplateMethodInfo
    ResolveAudioAggregatorMethod "getContext" o = Gst.Element.ElementGetContextMethodInfo
    ResolveAudioAggregatorMethod "getContextUnlocked" o = Gst.Element.ElementGetContextUnlockedMethodInfo
    ResolveAudioAggregatorMethod "getContexts" o = Gst.Element.ElementGetContextsMethodInfo
    ResolveAudioAggregatorMethod "getControlBinding" o = Gst.Object.ObjectGetControlBindingMethodInfo
    ResolveAudioAggregatorMethod "getControlRate" o = Gst.Object.ObjectGetControlRateMethodInfo
    ResolveAudioAggregatorMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveAudioAggregatorMethod "getFactory" o = Gst.Element.ElementGetFactoryMethodInfo
    ResolveAudioAggregatorMethod "getGValueArray" o = Gst.Object.ObjectGetGValueArrayMethodInfo
    ResolveAudioAggregatorMethod "getLatency" o = GstBase.Aggregator.AggregatorGetLatencyMethodInfo
    ResolveAudioAggregatorMethod "getMetadata" o = Gst.Element.ElementGetMetadataMethodInfo
    ResolveAudioAggregatorMethod "getName" o = Gst.Object.ObjectGetNameMethodInfo
    ResolveAudioAggregatorMethod "getPadTemplate" o = Gst.Element.ElementGetPadTemplateMethodInfo
    ResolveAudioAggregatorMethod "getPadTemplateList" o = Gst.Element.ElementGetPadTemplateListMethodInfo
    ResolveAudioAggregatorMethod "getParent" o = Gst.Object.ObjectGetParentMethodInfo
    ResolveAudioAggregatorMethod "getPathString" o = Gst.Object.ObjectGetPathStringMethodInfo
    ResolveAudioAggregatorMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveAudioAggregatorMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveAudioAggregatorMethod "getRequestPad" o = Gst.Element.ElementGetRequestPadMethodInfo
    ResolveAudioAggregatorMethod "getStartTime" o = Gst.Element.ElementGetStartTimeMethodInfo
    ResolveAudioAggregatorMethod "getState" o = Gst.Element.ElementGetStateMethodInfo
    ResolveAudioAggregatorMethod "getStaticPad" o = Gst.Element.ElementGetStaticPadMethodInfo
    ResolveAudioAggregatorMethod "getValue" o = Gst.Object.ObjectGetValueMethodInfo
    ResolveAudioAggregatorMethod "setBaseTime" o = Gst.Element.ElementSetBaseTimeMethodInfo
    ResolveAudioAggregatorMethod "setBus" o = Gst.Element.ElementSetBusMethodInfo
    ResolveAudioAggregatorMethod "setClock" o = Gst.Element.ElementSetClockMethodInfo
    ResolveAudioAggregatorMethod "setContext" o = Gst.Element.ElementSetContextMethodInfo
    ResolveAudioAggregatorMethod "setControlBindingDisabled" o = Gst.Object.ObjectSetControlBindingDisabledMethodInfo
    ResolveAudioAggregatorMethod "setControlBindingsDisabled" o = Gst.Object.ObjectSetControlBindingsDisabledMethodInfo
    ResolveAudioAggregatorMethod "setControlRate" o = Gst.Object.ObjectSetControlRateMethodInfo
    ResolveAudioAggregatorMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveAudioAggregatorMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveAudioAggregatorMethod "setLatency" o = GstBase.Aggregator.AggregatorSetLatencyMethodInfo
    ResolveAudioAggregatorMethod "setLockedState" o = Gst.Element.ElementSetLockedStateMethodInfo
    ResolveAudioAggregatorMethod "setName" o = Gst.Object.ObjectSetNameMethodInfo
    ResolveAudioAggregatorMethod "setParent" o = Gst.Object.ObjectSetParentMethodInfo
    ResolveAudioAggregatorMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveAudioAggregatorMethod "setSinkCaps" o = AudioAggregatorSetSinkCapsMethodInfo
    ResolveAudioAggregatorMethod "setSrcCaps" o = GstBase.Aggregator.AggregatorSetSrcCapsMethodInfo
    ResolveAudioAggregatorMethod "setStartTime" o = Gst.Element.ElementSetStartTimeMethodInfo
    ResolveAudioAggregatorMethod "setState" o = Gst.Element.ElementSetStateMethodInfo
    ResolveAudioAggregatorMethod l o = O.MethodResolutionFailed l o

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

#endif

-- VVV Prop "alignment-threshold"
   -- Type: TBasicType TUInt64
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@alignment-threshold@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' audioAggregator #alignmentThreshold
-- @
getAudioAggregatorAlignmentThreshold :: (MonadIO m, IsAudioAggregator o) => o -> m Word64
getAudioAggregatorAlignmentThreshold :: o -> m Word64
getAudioAggregatorAlignmentThreshold obj :: o
obj = IO Word64 -> m Word64
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word64 -> m Word64) -> IO Word64 -> m Word64
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Word64
forall a. GObject a => a -> String -> IO Word64
B.Properties.getObjectPropertyUInt64 o
obj "alignment-threshold"

-- | Set the value of the “@alignment-threshold@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' audioAggregator [ #alignmentThreshold 'Data.GI.Base.Attributes.:=' value ]
-- @
setAudioAggregatorAlignmentThreshold :: (MonadIO m, IsAudioAggregator o) => o -> Word64 -> m ()
setAudioAggregatorAlignmentThreshold :: o -> Word64 -> m ()
setAudioAggregatorAlignmentThreshold obj :: o
obj val :: Word64
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 -> Word64 -> IO ()
forall a. GObject a => a -> String -> Word64 -> IO ()
B.Properties.setObjectPropertyUInt64 o
obj "alignment-threshold" Word64
val

-- | Construct a `GValueConstruct` with valid value for the “@alignment-threshold@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructAudioAggregatorAlignmentThreshold :: (IsAudioAggregator o) => Word64 -> IO (GValueConstruct o)
constructAudioAggregatorAlignmentThreshold :: Word64 -> IO (GValueConstruct o)
constructAudioAggregatorAlignmentThreshold val :: Word64
val = String -> Word64 -> IO (GValueConstruct o)
forall o. String -> Word64 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyUInt64 "alignment-threshold" Word64
val

#if defined(ENABLE_OVERLOADING)
data AudioAggregatorAlignmentThresholdPropertyInfo
instance AttrInfo AudioAggregatorAlignmentThresholdPropertyInfo where
    type AttrAllowedOps AudioAggregatorAlignmentThresholdPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint AudioAggregatorAlignmentThresholdPropertyInfo = IsAudioAggregator
    type AttrSetTypeConstraint AudioAggregatorAlignmentThresholdPropertyInfo = (~) Word64
    type AttrTransferTypeConstraint AudioAggregatorAlignmentThresholdPropertyInfo = (~) Word64
    type AttrTransferType AudioAggregatorAlignmentThresholdPropertyInfo = Word64
    type AttrGetType AudioAggregatorAlignmentThresholdPropertyInfo = Word64
    type AttrLabel AudioAggregatorAlignmentThresholdPropertyInfo = "alignment-threshold"
    type AttrOrigin AudioAggregatorAlignmentThresholdPropertyInfo = AudioAggregator
    attrGet = getAudioAggregatorAlignmentThreshold
    attrSet = setAudioAggregatorAlignmentThreshold
    attrTransfer _ v = do
        return v
    attrConstruct = constructAudioAggregatorAlignmentThreshold
    attrClear = undefined
#endif

-- VVV Prop "discont-wait"
   -- Type: TBasicType TUInt64
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@discont-wait@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' audioAggregator #discontWait
-- @
getAudioAggregatorDiscontWait :: (MonadIO m, IsAudioAggregator o) => o -> m Word64
getAudioAggregatorDiscontWait :: o -> m Word64
getAudioAggregatorDiscontWait obj :: o
obj = IO Word64 -> m Word64
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word64 -> m Word64) -> IO Word64 -> m Word64
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Word64
forall a. GObject a => a -> String -> IO Word64
B.Properties.getObjectPropertyUInt64 o
obj "discont-wait"

-- | Set the value of the “@discont-wait@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' audioAggregator [ #discontWait 'Data.GI.Base.Attributes.:=' value ]
-- @
setAudioAggregatorDiscontWait :: (MonadIO m, IsAudioAggregator o) => o -> Word64 -> m ()
setAudioAggregatorDiscontWait :: o -> Word64 -> m ()
setAudioAggregatorDiscontWait obj :: o
obj val :: Word64
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 -> Word64 -> IO ()
forall a. GObject a => a -> String -> Word64 -> IO ()
B.Properties.setObjectPropertyUInt64 o
obj "discont-wait" Word64
val

-- | Construct a `GValueConstruct` with valid value for the “@discont-wait@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructAudioAggregatorDiscontWait :: (IsAudioAggregator o) => Word64 -> IO (GValueConstruct o)
constructAudioAggregatorDiscontWait :: Word64 -> IO (GValueConstruct o)
constructAudioAggregatorDiscontWait val :: Word64
val = String -> Word64 -> IO (GValueConstruct o)
forall o. String -> Word64 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyUInt64 "discont-wait" Word64
val

#if defined(ENABLE_OVERLOADING)
data AudioAggregatorDiscontWaitPropertyInfo
instance AttrInfo AudioAggregatorDiscontWaitPropertyInfo where
    type AttrAllowedOps AudioAggregatorDiscontWaitPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint AudioAggregatorDiscontWaitPropertyInfo = IsAudioAggregator
    type AttrSetTypeConstraint AudioAggregatorDiscontWaitPropertyInfo = (~) Word64
    type AttrTransferTypeConstraint AudioAggregatorDiscontWaitPropertyInfo = (~) Word64
    type AttrTransferType AudioAggregatorDiscontWaitPropertyInfo = Word64
    type AttrGetType AudioAggregatorDiscontWaitPropertyInfo = Word64
    type AttrLabel AudioAggregatorDiscontWaitPropertyInfo = "discont-wait"
    type AttrOrigin AudioAggregatorDiscontWaitPropertyInfo = AudioAggregator
    attrGet = getAudioAggregatorDiscontWait
    attrSet = setAudioAggregatorDiscontWait
    attrTransfer _ v = do
        return v
    attrConstruct = constructAudioAggregatorDiscontWait
    attrClear = undefined
#endif

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

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

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

-- | Construct a `GValueConstruct` with valid value for the “@output-buffer-duration@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructAudioAggregatorOutputBufferDuration :: (IsAudioAggregator o) => Word64 -> IO (GValueConstruct o)
constructAudioAggregatorOutputBufferDuration :: Word64 -> IO (GValueConstruct o)
constructAudioAggregatorOutputBufferDuration val :: Word64
val = String -> Word64 -> IO (GValueConstruct o)
forall o. String -> Word64 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyUInt64 "output-buffer-duration" Word64
val

#if defined(ENABLE_OVERLOADING)
data AudioAggregatorOutputBufferDurationPropertyInfo
instance AttrInfo AudioAggregatorOutputBufferDurationPropertyInfo where
    type AttrAllowedOps AudioAggregatorOutputBufferDurationPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint AudioAggregatorOutputBufferDurationPropertyInfo = IsAudioAggregator
    type AttrSetTypeConstraint AudioAggregatorOutputBufferDurationPropertyInfo = (~) Word64
    type AttrTransferTypeConstraint AudioAggregatorOutputBufferDurationPropertyInfo = (~) Word64
    type AttrTransferType AudioAggregatorOutputBufferDurationPropertyInfo = Word64
    type AttrGetType AudioAggregatorOutputBufferDurationPropertyInfo = Word64
    type AttrLabel AudioAggregatorOutputBufferDurationPropertyInfo = "output-buffer-duration"
    type AttrOrigin AudioAggregatorOutputBufferDurationPropertyInfo = AudioAggregator
    attrGet = getAudioAggregatorOutputBufferDuration
    attrSet = setAudioAggregatorOutputBufferDuration
    attrTransfer _ v = do
        return v
    attrConstruct = constructAudioAggregatorOutputBufferDuration
    attrClear = undefined
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList AudioAggregator
type instance O.AttributeList AudioAggregator = AudioAggregatorAttributeList
type AudioAggregatorAttributeList = ('[ '("alignmentThreshold", AudioAggregatorAlignmentThresholdPropertyInfo), '("discontWait", AudioAggregatorDiscontWaitPropertyInfo), '("latency", GstBase.Aggregator.AggregatorLatencyPropertyInfo), '("minUpstreamLatency", GstBase.Aggregator.AggregatorMinUpstreamLatencyPropertyInfo), '("name", Gst.Object.ObjectNamePropertyInfo), '("outputBufferDuration", AudioAggregatorOutputBufferDurationPropertyInfo), '("parent", Gst.Object.ObjectParentPropertyInfo), '("startTime", GstBase.Aggregator.AggregatorStartTimePropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
audioAggregatorAlignmentThreshold :: AttrLabelProxy "alignmentThreshold"
audioAggregatorAlignmentThreshold = AttrLabelProxy

audioAggregatorDiscontWait :: AttrLabelProxy "discontWait"
audioAggregatorDiscontWait = AttrLabelProxy

audioAggregatorOutputBufferDuration :: AttrLabelProxy "outputBufferDuration"
audioAggregatorOutputBufferDuration = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList AudioAggregator = AudioAggregatorSignalList
type AudioAggregatorSignalList = ('[ '("deepNotify", Gst.Object.ObjectDeepNotifySignalInfo), '("noMorePads", Gst.Element.ElementNoMorePadsSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("padAdded", Gst.Element.ElementPadAddedSignalInfo), '("padRemoved", Gst.Element.ElementPadRemovedSignalInfo)] :: [(Symbol, *)])

#endif

-- method AudioAggregator::set_sink_caps
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "aagg"
--           , argType =
--               TInterface
--                 Name { namespace = "GstAudio" , name = "AudioAggregator" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "pad"
--           , argType =
--               TInterface
--                 Name { namespace = "GstAudio" , name = "AudioAggregatorPad" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "caps"
--           , argType = TInterface Name { namespace = "Gst" , name = "Caps" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gst_audio_aggregator_set_sink_caps" gst_audio_aggregator_set_sink_caps :: 
    Ptr AudioAggregator ->                  -- aagg : TInterface (Name {namespace = "GstAudio", name = "AudioAggregator"})
    Ptr GstAudio.AudioAggregatorPad.AudioAggregatorPad -> -- pad : TInterface (Name {namespace = "GstAudio", name = "AudioAggregatorPad"})
    Ptr Gst.Caps.Caps ->                    -- caps : TInterface (Name {namespace = "Gst", name = "Caps"})
    IO ()

-- | /No description available in the introspection data./
audioAggregatorSetSinkCaps ::
    (B.CallStack.HasCallStack, MonadIO m, IsAudioAggregator a, GstAudio.AudioAggregatorPad.IsAudioAggregatorPad b) =>
    a
    -> b
    -> Gst.Caps.Caps
    -> m ()
audioAggregatorSetSinkCaps :: a -> b -> Caps -> m ()
audioAggregatorSetSinkCaps aagg :: a
aagg pad :: b
pad caps :: Caps
caps = 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 AudioAggregator
aagg' <- a -> IO (Ptr AudioAggregator)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
aagg
    Ptr AudioAggregatorPad
pad' <- b -> IO (Ptr AudioAggregatorPad)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
pad
    Ptr Caps
caps' <- Caps -> IO (Ptr Caps)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Caps
caps
    Ptr AudioAggregator -> Ptr AudioAggregatorPad -> Ptr Caps -> IO ()
gst_audio_aggregator_set_sink_caps Ptr AudioAggregator
aagg' Ptr AudioAggregatorPad
pad' Ptr Caps
caps'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
aagg
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
pad
    Caps -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Caps
caps
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data AudioAggregatorSetSinkCapsMethodInfo
instance (signature ~ (b -> Gst.Caps.Caps -> m ()), MonadIO m, IsAudioAggregator a, GstAudio.AudioAggregatorPad.IsAudioAggregatorPad b) => O.MethodInfo AudioAggregatorSetSinkCapsMethodInfo a signature where
    overloadedMethod = audioAggregatorSetSinkCaps

#endif