{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- This base class is for audio decoders turning encoded data into
-- raw audio samples.
-- 
-- GstAudioDecoder and subclass should cooperate as follows.
-- 
-- == Configuration
-- 
--   * Initially, GstAudioDecoder calls /@start@/ when the decoder element
--     is activated, which allows subclass to perform any global setup.
--     Base class (context) parameters can already be set according to subclass
--     capabilities (or possibly upon receive more information in subsequent
--     /@setFormat@/).
--   * GstAudioDecoder calls /@setFormat@/ to inform subclass of the format
--     of input audio data that it is about to receive.
--     While unlikely, it might be called more than once, if changing input
--     parameters require reconfiguration.
--   * GstAudioDecoder calls /@stop@/ at end of all processing.
-- 
-- As of configuration stage, and throughout processing, GstAudioDecoder
-- provides various (context) parameters, e.g. describing the format of
-- output audio data (valid when output caps have been set) or current parsing state.
-- Conversely, subclass can and should configure context to inform
-- base class of its expectation w.r.t. buffer handling.
-- 
-- == Data processing
--     * Base class gathers input data, and optionally allows subclass
--       to parse this into subsequently manageable (as defined by subclass)
--       chunks.  Such chunks are subsequently referred to as \'frames\',
--       though they may or may not correspond to 1 (or more) audio format frame.
--     * Input frame is provided to subclass\' /@handleFrame@/.
--     * If codec processing results in decoded data, subclass should call
--       /@gstAudioDecoderFinishFrame@/ to have decoded data pushed
--       downstream.
--     * Just prior to actually pushing a buffer downstream,
--       it is passed to /@prePush@/.  Subclass should either use this callback
--       to arrange for additional downstream pushing or otherwise ensure such
--       custom pushing occurs after at least a method call has finished since
--       setting src pad caps.
--     * During the parsing process GstAudioDecoderClass will handle both
--       srcpad and sinkpad events. Sink events will be passed to subclass
--       if /@event@/ callback has been provided.
-- 
-- == Shutdown phase
-- 
--   * GstAudioDecoder class calls /@stop@/ to inform the subclass that data
--     parsing will be stopped.
-- 
-- Subclass is responsible for providing pad template caps for
-- source and sink pads. The pads need to be named \"sink\" and \"src\". It also
-- needs to set the fixed caps on srcpad, when the format is ensured.  This
-- is typically when base class calls subclass\' /@setFormat@/ function, though
-- it might be delayed until calling /@gstAudioDecoderFinishFrame@/.
-- 
-- In summary, above process should have subclass concentrating on
-- codec data processing while leaving other matters to base class,
-- such as most notably timestamp handling.  While it may exert more control
-- in this area (see e.g. /@prePush@/), it is very much not recommended.
-- 
-- In particular, base class will try to arrange for perfect output timestamps
-- as much as possible while tracking upstream timestamps.
-- To this end, if deviation between the next ideal expected perfect timestamp
-- and upstream exceeds t'GI.GstAudio.Objects.AudioDecoder.AudioDecoder':@/tolerance/@, then resync to upstream
-- occurs (which would happen always if the tolerance mechanism is disabled).
-- 
-- In non-live pipelines, baseclass can also (configurably) arrange for
-- output buffer aggregation which may help to redue large(r) numbers of
-- small(er) buffers being pushed and processed downstream. Note that this
-- feature is only available if the buffer layout is interleaved. For planar
-- buffers, the decoder implementation is fully responsible for the output
-- buffer size.
-- 
-- On the other hand, it should be noted that baseclass only provides limited
-- seeking support (upon explicit subclass request), as full-fledged support
-- should rather be left to upstream demuxer, parser or alike.  This simple
-- approach caters for seeking and duration reporting using estimated input
-- bitrates.
-- 
-- Things that subclass need to take care of:
-- 
--   * Provide pad templates
--   * Set source pad caps when appropriate
--   * Set user-configurable properties to sane defaults for format and
--      implementing codec at hand, and convey some subclass capabilities and
--      expectations in context.
-- 
--   * Accept data in /@handleFrame@/ and provide encoded results to
--      /@gstAudioDecoderFinishFrame@/.  If it is prepared to perform
--      PLC, it should also accept NULL data in /@handleFrame@/ and provide for
--      data for indicated duration.

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

module GI.GstAudio.Objects.AudioDecoder
    ( 

-- * Exported types
    AudioDecoder(..)                        ,
    IsAudioDecoder                          ,
    toAudioDecoder                          ,
    noAudioDecoder                          ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveAudioDecoderMethod               ,
#endif


-- ** allocateOutputBuffer #method:allocateOutputBuffer#

#if defined(ENABLE_OVERLOADING)
    AudioDecoderAllocateOutputBufferMethodInfo,
#endif
    audioDecoderAllocateOutputBuffer        ,


-- ** finishFrame #method:finishFrame#

#if defined(ENABLE_OVERLOADING)
    AudioDecoderFinishFrameMethodInfo       ,
#endif
    audioDecoderFinishFrame                 ,


-- ** finishSubframe #method:finishSubframe#

#if defined(ENABLE_OVERLOADING)
    AudioDecoderFinishSubframeMethodInfo    ,
#endif
    audioDecoderFinishSubframe              ,


-- ** getAllocator #method:getAllocator#

#if defined(ENABLE_OVERLOADING)
    AudioDecoderGetAllocatorMethodInfo      ,
#endif
    audioDecoderGetAllocator                ,


-- ** getAudioInfo #method:getAudioInfo#

#if defined(ENABLE_OVERLOADING)
    AudioDecoderGetAudioInfoMethodInfo      ,
#endif
    audioDecoderGetAudioInfo                ,


-- ** getDelay #method:getDelay#

#if defined(ENABLE_OVERLOADING)
    AudioDecoderGetDelayMethodInfo          ,
#endif
    audioDecoderGetDelay                    ,


-- ** getDrainable #method:getDrainable#

#if defined(ENABLE_OVERLOADING)
    AudioDecoderGetDrainableMethodInfo      ,
#endif
    audioDecoderGetDrainable                ,


-- ** getEstimateRate #method:getEstimateRate#

#if defined(ENABLE_OVERLOADING)
    AudioDecoderGetEstimateRateMethodInfo   ,
#endif
    audioDecoderGetEstimateRate             ,


-- ** getLatency #method:getLatency#

#if defined(ENABLE_OVERLOADING)
    AudioDecoderGetLatencyMethodInfo        ,
#endif
    audioDecoderGetLatency                  ,


-- ** getMaxErrors #method:getMaxErrors#

#if defined(ENABLE_OVERLOADING)
    AudioDecoderGetMaxErrorsMethodInfo      ,
#endif
    audioDecoderGetMaxErrors                ,


-- ** getMinLatency #method:getMinLatency#

#if defined(ENABLE_OVERLOADING)
    AudioDecoderGetMinLatencyMethodInfo     ,
#endif
    audioDecoderGetMinLatency               ,


-- ** getNeedsFormat #method:getNeedsFormat#

#if defined(ENABLE_OVERLOADING)
    AudioDecoderGetNeedsFormatMethodInfo    ,
#endif
    audioDecoderGetNeedsFormat              ,


-- ** getParseState #method:getParseState#

#if defined(ENABLE_OVERLOADING)
    AudioDecoderGetParseStateMethodInfo     ,
#endif
    audioDecoderGetParseState               ,


-- ** getPlc #method:getPlc#

#if defined(ENABLE_OVERLOADING)
    AudioDecoderGetPlcMethodInfo            ,
#endif
    audioDecoderGetPlc                      ,


-- ** getPlcAware #method:getPlcAware#

#if defined(ENABLE_OVERLOADING)
    AudioDecoderGetPlcAwareMethodInfo       ,
#endif
    audioDecoderGetPlcAware                 ,


-- ** getTolerance #method:getTolerance#

#if defined(ENABLE_OVERLOADING)
    AudioDecoderGetToleranceMethodInfo      ,
#endif
    audioDecoderGetTolerance                ,


-- ** mergeTags #method:mergeTags#

#if defined(ENABLE_OVERLOADING)
    AudioDecoderMergeTagsMethodInfo         ,
#endif
    audioDecoderMergeTags                   ,


-- ** negotiate #method:negotiate#

#if defined(ENABLE_OVERLOADING)
    AudioDecoderNegotiateMethodInfo         ,
#endif
    audioDecoderNegotiate                   ,


-- ** proxyGetcaps #method:proxyGetcaps#

#if defined(ENABLE_OVERLOADING)
    AudioDecoderProxyGetcapsMethodInfo      ,
#endif
    audioDecoderProxyGetcaps                ,


-- ** setAllocationCaps #method:setAllocationCaps#

#if defined(ENABLE_OVERLOADING)
    AudioDecoderSetAllocationCapsMethodInfo ,
#endif
    audioDecoderSetAllocationCaps           ,


-- ** setDrainable #method:setDrainable#

#if defined(ENABLE_OVERLOADING)
    AudioDecoderSetDrainableMethodInfo      ,
#endif
    audioDecoderSetDrainable                ,


-- ** setEstimateRate #method:setEstimateRate#

#if defined(ENABLE_OVERLOADING)
    AudioDecoderSetEstimateRateMethodInfo   ,
#endif
    audioDecoderSetEstimateRate             ,


-- ** setLatency #method:setLatency#

#if defined(ENABLE_OVERLOADING)
    AudioDecoderSetLatencyMethodInfo        ,
#endif
    audioDecoderSetLatency                  ,


-- ** setMaxErrors #method:setMaxErrors#

#if defined(ENABLE_OVERLOADING)
    AudioDecoderSetMaxErrorsMethodInfo      ,
#endif
    audioDecoderSetMaxErrors                ,


-- ** setMinLatency #method:setMinLatency#

#if defined(ENABLE_OVERLOADING)
    AudioDecoderSetMinLatencyMethodInfo     ,
#endif
    audioDecoderSetMinLatency               ,


-- ** setNeedsFormat #method:setNeedsFormat#

#if defined(ENABLE_OVERLOADING)
    AudioDecoderSetNeedsFormatMethodInfo    ,
#endif
    audioDecoderSetNeedsFormat              ,


-- ** setOutputCaps #method:setOutputCaps#

#if defined(ENABLE_OVERLOADING)
    AudioDecoderSetOutputCapsMethodInfo     ,
#endif
    audioDecoderSetOutputCaps               ,


-- ** setOutputFormat #method:setOutputFormat#

#if defined(ENABLE_OVERLOADING)
    AudioDecoderSetOutputFormatMethodInfo   ,
#endif
    audioDecoderSetOutputFormat             ,


-- ** setPlc #method:setPlc#

#if defined(ENABLE_OVERLOADING)
    AudioDecoderSetPlcMethodInfo            ,
#endif
    audioDecoderSetPlc                      ,


-- ** setPlcAware #method:setPlcAware#

#if defined(ENABLE_OVERLOADING)
    AudioDecoderSetPlcAwareMethodInfo       ,
#endif
    audioDecoderSetPlcAware                 ,


-- ** setTolerance #method:setTolerance#

#if defined(ENABLE_OVERLOADING)
    AudioDecoderSetToleranceMethodInfo      ,
#endif
    audioDecoderSetTolerance                ,


-- ** setUseDefaultPadAcceptcaps #method:setUseDefaultPadAcceptcaps#

#if defined(ENABLE_OVERLOADING)
    AudioDecoderSetUseDefaultPadAcceptcapsMethodInfo,
#endif
    audioDecoderSetUseDefaultPadAcceptcaps  ,




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

#if defined(ENABLE_OVERLOADING)
    AudioDecoderMinLatencyPropertyInfo      ,
#endif
#if defined(ENABLE_OVERLOADING)
    audioDecoderMinLatency                  ,
#endif
    constructAudioDecoderMinLatency         ,
    getAudioDecoderMinLatency               ,
    setAudioDecoderMinLatency               ,


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

#if defined(ENABLE_OVERLOADING)
    AudioDecoderPlcPropertyInfo             ,
#endif
#if defined(ENABLE_OVERLOADING)
    audioDecoderPlc                         ,
#endif
    constructAudioDecoderPlc                ,
    getAudioDecoderPlc                      ,
    setAudioDecoderPlc                      ,


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

#if defined(ENABLE_OVERLOADING)
    AudioDecoderTolerancePropertyInfo       ,
#endif
#if defined(ENABLE_OVERLOADING)
    audioDecoderTolerance                   ,
#endif
    constructAudioDecoderTolerance          ,
    getAudioDecoderTolerance                ,
    setAudioDecoderTolerance                ,




    ) 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.Enums as Gst.Enums
import qualified GI.Gst.Objects.Allocator as Gst.Allocator
import qualified GI.Gst.Objects.Element as Gst.Element
import qualified GI.Gst.Objects.Object as Gst.Object
import qualified GI.Gst.Structs.AllocationParams as Gst.AllocationParams
import qualified GI.Gst.Structs.Buffer as Gst.Buffer
import qualified GI.Gst.Structs.Caps as Gst.Caps
import qualified GI.Gst.Structs.TagList as Gst.TagList
import {-# SOURCE #-} qualified GI.GstAudio.Structs.AudioInfo as GstAudio.AudioInfo

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

instance GObject AudioDecoder where
    gobjectType :: IO GType
gobjectType = IO GType
c_gst_audio_decoder_get_type
    

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

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

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

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

-- | A convenience alias for `Nothing` :: `Maybe` `AudioDecoder`.
noAudioDecoder :: Maybe AudioDecoder
noAudioDecoder :: Maybe AudioDecoder
noAudioDecoder = Maybe AudioDecoder
forall a. Maybe a
Nothing

#if defined(ENABLE_OVERLOADING)
type family ResolveAudioDecoderMethod (t :: Symbol) (o :: *) :: * where
    ResolveAudioDecoderMethod "abortState" o = Gst.Element.ElementAbortStateMethodInfo
    ResolveAudioDecoderMethod "addControlBinding" o = Gst.Object.ObjectAddControlBindingMethodInfo
    ResolveAudioDecoderMethod "addPad" o = Gst.Element.ElementAddPadMethodInfo
    ResolveAudioDecoderMethod "addPropertyDeepNotifyWatch" o = Gst.Element.ElementAddPropertyDeepNotifyWatchMethodInfo
    ResolveAudioDecoderMethod "addPropertyNotifyWatch" o = Gst.Element.ElementAddPropertyNotifyWatchMethodInfo
    ResolveAudioDecoderMethod "allocateOutputBuffer" o = AudioDecoderAllocateOutputBufferMethodInfo
    ResolveAudioDecoderMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveAudioDecoderMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveAudioDecoderMethod "callAsync" o = Gst.Element.ElementCallAsyncMethodInfo
    ResolveAudioDecoderMethod "changeState" o = Gst.Element.ElementChangeStateMethodInfo
    ResolveAudioDecoderMethod "continueState" o = Gst.Element.ElementContinueStateMethodInfo
    ResolveAudioDecoderMethod "createAllPads" o = Gst.Element.ElementCreateAllPadsMethodInfo
    ResolveAudioDecoderMethod "defaultError" o = Gst.Object.ObjectDefaultErrorMethodInfo
    ResolveAudioDecoderMethod "finishFrame" o = AudioDecoderFinishFrameMethodInfo
    ResolveAudioDecoderMethod "finishSubframe" o = AudioDecoderFinishSubframeMethodInfo
    ResolveAudioDecoderMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveAudioDecoderMethod "foreachPad" o = Gst.Element.ElementForeachPadMethodInfo
    ResolveAudioDecoderMethod "foreachSinkPad" o = Gst.Element.ElementForeachSinkPadMethodInfo
    ResolveAudioDecoderMethod "foreachSrcPad" o = Gst.Element.ElementForeachSrcPadMethodInfo
    ResolveAudioDecoderMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveAudioDecoderMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveAudioDecoderMethod "hasActiveControlBindings" o = Gst.Object.ObjectHasActiveControlBindingsMethodInfo
    ResolveAudioDecoderMethod "hasAncestor" o = Gst.Object.ObjectHasAncestorMethodInfo
    ResolveAudioDecoderMethod "hasAsAncestor" o = Gst.Object.ObjectHasAsAncestorMethodInfo
    ResolveAudioDecoderMethod "hasAsParent" o = Gst.Object.ObjectHasAsParentMethodInfo
    ResolveAudioDecoderMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveAudioDecoderMethod "isLockedState" o = Gst.Element.ElementIsLockedStateMethodInfo
    ResolveAudioDecoderMethod "iteratePads" o = Gst.Element.ElementIteratePadsMethodInfo
    ResolveAudioDecoderMethod "iterateSinkPads" o = Gst.Element.ElementIterateSinkPadsMethodInfo
    ResolveAudioDecoderMethod "iterateSrcPads" o = Gst.Element.ElementIterateSrcPadsMethodInfo
    ResolveAudioDecoderMethod "link" o = Gst.Element.ElementLinkMethodInfo
    ResolveAudioDecoderMethod "linkFiltered" o = Gst.Element.ElementLinkFilteredMethodInfo
    ResolveAudioDecoderMethod "linkPads" o = Gst.Element.ElementLinkPadsMethodInfo
    ResolveAudioDecoderMethod "linkPadsFiltered" o = Gst.Element.ElementLinkPadsFilteredMethodInfo
    ResolveAudioDecoderMethod "linkPadsFull" o = Gst.Element.ElementLinkPadsFullMethodInfo
    ResolveAudioDecoderMethod "lostState" o = Gst.Element.ElementLostStateMethodInfo
    ResolveAudioDecoderMethod "mergeTags" o = AudioDecoderMergeTagsMethodInfo
    ResolveAudioDecoderMethod "messageFull" o = Gst.Element.ElementMessageFullMethodInfo
    ResolveAudioDecoderMethod "messageFullWithDetails" o = Gst.Element.ElementMessageFullWithDetailsMethodInfo
    ResolveAudioDecoderMethod "negotiate" o = AudioDecoderNegotiateMethodInfo
    ResolveAudioDecoderMethod "noMorePads" o = Gst.Element.ElementNoMorePadsMethodInfo
    ResolveAudioDecoderMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveAudioDecoderMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveAudioDecoderMethod "postMessage" o = Gst.Element.ElementPostMessageMethodInfo
    ResolveAudioDecoderMethod "provideClock" o = Gst.Element.ElementProvideClockMethodInfo
    ResolveAudioDecoderMethod "proxyGetcaps" o = AudioDecoderProxyGetcapsMethodInfo
    ResolveAudioDecoderMethod "query" o = Gst.Element.ElementQueryMethodInfo
    ResolveAudioDecoderMethod "queryConvert" o = Gst.Element.ElementQueryConvertMethodInfo
    ResolveAudioDecoderMethod "queryDuration" o = Gst.Element.ElementQueryDurationMethodInfo
    ResolveAudioDecoderMethod "queryPosition" o = Gst.Element.ElementQueryPositionMethodInfo
    ResolveAudioDecoderMethod "ref" o = Gst.Object.ObjectRefMethodInfo
    ResolveAudioDecoderMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveAudioDecoderMethod "releaseRequestPad" o = Gst.Element.ElementReleaseRequestPadMethodInfo
    ResolveAudioDecoderMethod "removeControlBinding" o = Gst.Object.ObjectRemoveControlBindingMethodInfo
    ResolveAudioDecoderMethod "removePad" o = Gst.Element.ElementRemovePadMethodInfo
    ResolveAudioDecoderMethod "removePropertyNotifyWatch" o = Gst.Element.ElementRemovePropertyNotifyWatchMethodInfo
    ResolveAudioDecoderMethod "requestPad" o = Gst.Element.ElementRequestPadMethodInfo
    ResolveAudioDecoderMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveAudioDecoderMethod "seek" o = Gst.Element.ElementSeekMethodInfo
    ResolveAudioDecoderMethod "seekSimple" o = Gst.Element.ElementSeekSimpleMethodInfo
    ResolveAudioDecoderMethod "sendEvent" o = Gst.Element.ElementSendEventMethodInfo
    ResolveAudioDecoderMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveAudioDecoderMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveAudioDecoderMethod "suggestNextSync" o = Gst.Object.ObjectSuggestNextSyncMethodInfo
    ResolveAudioDecoderMethod "syncStateWithParent" o = Gst.Element.ElementSyncStateWithParentMethodInfo
    ResolveAudioDecoderMethod "syncValues" o = Gst.Object.ObjectSyncValuesMethodInfo
    ResolveAudioDecoderMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveAudioDecoderMethod "unlink" o = Gst.Element.ElementUnlinkMethodInfo
    ResolveAudioDecoderMethod "unlinkPads" o = Gst.Element.ElementUnlinkPadsMethodInfo
    ResolveAudioDecoderMethod "unparent" o = Gst.Object.ObjectUnparentMethodInfo
    ResolveAudioDecoderMethod "unref" o = Gst.Object.ObjectUnrefMethodInfo
    ResolveAudioDecoderMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveAudioDecoderMethod "getAllocator" o = AudioDecoderGetAllocatorMethodInfo
    ResolveAudioDecoderMethod "getAudioInfo" o = AudioDecoderGetAudioInfoMethodInfo
    ResolveAudioDecoderMethod "getBaseTime" o = Gst.Element.ElementGetBaseTimeMethodInfo
    ResolveAudioDecoderMethod "getBus" o = Gst.Element.ElementGetBusMethodInfo
    ResolveAudioDecoderMethod "getClock" o = Gst.Element.ElementGetClockMethodInfo
    ResolveAudioDecoderMethod "getCompatiblePad" o = Gst.Element.ElementGetCompatiblePadMethodInfo
    ResolveAudioDecoderMethod "getCompatiblePadTemplate" o = Gst.Element.ElementGetCompatiblePadTemplateMethodInfo
    ResolveAudioDecoderMethod "getContext" o = Gst.Element.ElementGetContextMethodInfo
    ResolveAudioDecoderMethod "getContextUnlocked" o = Gst.Element.ElementGetContextUnlockedMethodInfo
    ResolveAudioDecoderMethod "getContexts" o = Gst.Element.ElementGetContextsMethodInfo
    ResolveAudioDecoderMethod "getControlBinding" o = Gst.Object.ObjectGetControlBindingMethodInfo
    ResolveAudioDecoderMethod "getControlRate" o = Gst.Object.ObjectGetControlRateMethodInfo
    ResolveAudioDecoderMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveAudioDecoderMethod "getDelay" o = AudioDecoderGetDelayMethodInfo
    ResolveAudioDecoderMethod "getDrainable" o = AudioDecoderGetDrainableMethodInfo
    ResolveAudioDecoderMethod "getEstimateRate" o = AudioDecoderGetEstimateRateMethodInfo
    ResolveAudioDecoderMethod "getFactory" o = Gst.Element.ElementGetFactoryMethodInfo
    ResolveAudioDecoderMethod "getGValueArray" o = Gst.Object.ObjectGetGValueArrayMethodInfo
    ResolveAudioDecoderMethod "getLatency" o = AudioDecoderGetLatencyMethodInfo
    ResolveAudioDecoderMethod "getMaxErrors" o = AudioDecoderGetMaxErrorsMethodInfo
    ResolveAudioDecoderMethod "getMetadata" o = Gst.Element.ElementGetMetadataMethodInfo
    ResolveAudioDecoderMethod "getMinLatency" o = AudioDecoderGetMinLatencyMethodInfo
    ResolveAudioDecoderMethod "getName" o = Gst.Object.ObjectGetNameMethodInfo
    ResolveAudioDecoderMethod "getNeedsFormat" o = AudioDecoderGetNeedsFormatMethodInfo
    ResolveAudioDecoderMethod "getPadTemplate" o = Gst.Element.ElementGetPadTemplateMethodInfo
    ResolveAudioDecoderMethod "getPadTemplateList" o = Gst.Element.ElementGetPadTemplateListMethodInfo
    ResolveAudioDecoderMethod "getParent" o = Gst.Object.ObjectGetParentMethodInfo
    ResolveAudioDecoderMethod "getParseState" o = AudioDecoderGetParseStateMethodInfo
    ResolveAudioDecoderMethod "getPathString" o = Gst.Object.ObjectGetPathStringMethodInfo
    ResolveAudioDecoderMethod "getPlc" o = AudioDecoderGetPlcMethodInfo
    ResolveAudioDecoderMethod "getPlcAware" o = AudioDecoderGetPlcAwareMethodInfo
    ResolveAudioDecoderMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveAudioDecoderMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveAudioDecoderMethod "getRequestPad" o = Gst.Element.ElementGetRequestPadMethodInfo
    ResolveAudioDecoderMethod "getStartTime" o = Gst.Element.ElementGetStartTimeMethodInfo
    ResolveAudioDecoderMethod "getState" o = Gst.Element.ElementGetStateMethodInfo
    ResolveAudioDecoderMethod "getStaticPad" o = Gst.Element.ElementGetStaticPadMethodInfo
    ResolveAudioDecoderMethod "getTolerance" o = AudioDecoderGetToleranceMethodInfo
    ResolveAudioDecoderMethod "getValue" o = Gst.Object.ObjectGetValueMethodInfo
    ResolveAudioDecoderMethod "setAllocationCaps" o = AudioDecoderSetAllocationCapsMethodInfo
    ResolveAudioDecoderMethod "setBaseTime" o = Gst.Element.ElementSetBaseTimeMethodInfo
    ResolveAudioDecoderMethod "setBus" o = Gst.Element.ElementSetBusMethodInfo
    ResolveAudioDecoderMethod "setClock" o = Gst.Element.ElementSetClockMethodInfo
    ResolveAudioDecoderMethod "setContext" o = Gst.Element.ElementSetContextMethodInfo
    ResolveAudioDecoderMethod "setControlBindingDisabled" o = Gst.Object.ObjectSetControlBindingDisabledMethodInfo
    ResolveAudioDecoderMethod "setControlBindingsDisabled" o = Gst.Object.ObjectSetControlBindingsDisabledMethodInfo
    ResolveAudioDecoderMethod "setControlRate" o = Gst.Object.ObjectSetControlRateMethodInfo
    ResolveAudioDecoderMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveAudioDecoderMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveAudioDecoderMethod "setDrainable" o = AudioDecoderSetDrainableMethodInfo
    ResolveAudioDecoderMethod "setEstimateRate" o = AudioDecoderSetEstimateRateMethodInfo
    ResolveAudioDecoderMethod "setLatency" o = AudioDecoderSetLatencyMethodInfo
    ResolveAudioDecoderMethod "setLockedState" o = Gst.Element.ElementSetLockedStateMethodInfo
    ResolveAudioDecoderMethod "setMaxErrors" o = AudioDecoderSetMaxErrorsMethodInfo
    ResolveAudioDecoderMethod "setMinLatency" o = AudioDecoderSetMinLatencyMethodInfo
    ResolveAudioDecoderMethod "setName" o = Gst.Object.ObjectSetNameMethodInfo
    ResolveAudioDecoderMethod "setNeedsFormat" o = AudioDecoderSetNeedsFormatMethodInfo
    ResolveAudioDecoderMethod "setOutputCaps" o = AudioDecoderSetOutputCapsMethodInfo
    ResolveAudioDecoderMethod "setOutputFormat" o = AudioDecoderSetOutputFormatMethodInfo
    ResolveAudioDecoderMethod "setParent" o = Gst.Object.ObjectSetParentMethodInfo
    ResolveAudioDecoderMethod "setPlc" o = AudioDecoderSetPlcMethodInfo
    ResolveAudioDecoderMethod "setPlcAware" o = AudioDecoderSetPlcAwareMethodInfo
    ResolveAudioDecoderMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveAudioDecoderMethod "setStartTime" o = Gst.Element.ElementSetStartTimeMethodInfo
    ResolveAudioDecoderMethod "setState" o = Gst.Element.ElementSetStateMethodInfo
    ResolveAudioDecoderMethod "setTolerance" o = AudioDecoderSetToleranceMethodInfo
    ResolveAudioDecoderMethod "setUseDefaultPadAcceptcaps" o = AudioDecoderSetUseDefaultPadAcceptcapsMethodInfo
    ResolveAudioDecoderMethod l o = O.MethodResolutionFailed l o

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

#endif

-- VVV Prop "min-latency"
   -- Type: TBasicType TInt64
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@min-latency@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' audioDecoder #minLatency
-- @
getAudioDecoderMinLatency :: (MonadIO m, IsAudioDecoder o) => o -> m Int64
getAudioDecoderMinLatency :: o -> m Int64
getAudioDecoderMinLatency obj :: o
obj = IO Int64 -> m Int64
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int64 -> m Int64) -> IO Int64 -> m Int64
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int64
forall a. GObject a => a -> String -> IO Int64
B.Properties.getObjectPropertyInt64 o
obj "min-latency"

-- | Set the value of the “@min-latency@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' audioDecoder [ #minLatency 'Data.GI.Base.Attributes.:=' value ]
-- @
setAudioDecoderMinLatency :: (MonadIO m, IsAudioDecoder o) => o -> Int64 -> m ()
setAudioDecoderMinLatency :: o -> Int64 -> m ()
setAudioDecoderMinLatency obj :: o
obj val :: Int64
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 -> Int64 -> IO ()
forall a. GObject a => a -> String -> Int64 -> IO ()
B.Properties.setObjectPropertyInt64 o
obj "min-latency" Int64
val

-- | Construct a `GValueConstruct` with valid value for the “@min-latency@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructAudioDecoderMinLatency :: (IsAudioDecoder o) => Int64 -> IO (GValueConstruct o)
constructAudioDecoderMinLatency :: Int64 -> IO (GValueConstruct o)
constructAudioDecoderMinLatency val :: Int64
val = String -> Int64 -> IO (GValueConstruct o)
forall o. String -> Int64 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt64 "min-latency" Int64
val

#if defined(ENABLE_OVERLOADING)
data AudioDecoderMinLatencyPropertyInfo
instance AttrInfo AudioDecoderMinLatencyPropertyInfo where
    type AttrAllowedOps AudioDecoderMinLatencyPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint AudioDecoderMinLatencyPropertyInfo = IsAudioDecoder
    type AttrSetTypeConstraint AudioDecoderMinLatencyPropertyInfo = (~) Int64
    type AttrTransferTypeConstraint AudioDecoderMinLatencyPropertyInfo = (~) Int64
    type AttrTransferType AudioDecoderMinLatencyPropertyInfo = Int64
    type AttrGetType AudioDecoderMinLatencyPropertyInfo = Int64
    type AttrLabel AudioDecoderMinLatencyPropertyInfo = "min-latency"
    type AttrOrigin AudioDecoderMinLatencyPropertyInfo = AudioDecoder
    attrGet = getAudioDecoderMinLatency
    attrSet = setAudioDecoderMinLatency
    attrTransfer _ v = do
        return v
    attrConstruct = constructAudioDecoderMinLatency
    attrClear = undefined
#endif

-- VVV Prop "plc"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@plc@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' audioDecoder #plc
-- @
getAudioDecoderPlc :: (MonadIO m, IsAudioDecoder o) => o -> m Bool
getAudioDecoderPlc :: o -> m Bool
getAudioDecoderPlc obj :: o
obj = 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
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj "plc"

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

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

#if defined(ENABLE_OVERLOADING)
data AudioDecoderPlcPropertyInfo
instance AttrInfo AudioDecoderPlcPropertyInfo where
    type AttrAllowedOps AudioDecoderPlcPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint AudioDecoderPlcPropertyInfo = IsAudioDecoder
    type AttrSetTypeConstraint AudioDecoderPlcPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint AudioDecoderPlcPropertyInfo = (~) Bool
    type AttrTransferType AudioDecoderPlcPropertyInfo = Bool
    type AttrGetType AudioDecoderPlcPropertyInfo = Bool
    type AttrLabel AudioDecoderPlcPropertyInfo = "plc"
    type AttrOrigin AudioDecoderPlcPropertyInfo = AudioDecoder
    attrGet = getAudioDecoderPlc
    attrSet = setAudioDecoderPlc
    attrTransfer _ v = do
        return v
    attrConstruct = constructAudioDecoderPlc
    attrClear = undefined
#endif

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

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

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

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

#if defined(ENABLE_OVERLOADING)
data AudioDecoderTolerancePropertyInfo
instance AttrInfo AudioDecoderTolerancePropertyInfo where
    type AttrAllowedOps AudioDecoderTolerancePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint AudioDecoderTolerancePropertyInfo = IsAudioDecoder
    type AttrSetTypeConstraint AudioDecoderTolerancePropertyInfo = (~) Int64
    type AttrTransferTypeConstraint AudioDecoderTolerancePropertyInfo = (~) Int64
    type AttrTransferType AudioDecoderTolerancePropertyInfo = Int64
    type AttrGetType AudioDecoderTolerancePropertyInfo = Int64
    type AttrLabel AudioDecoderTolerancePropertyInfo = "tolerance"
    type AttrOrigin AudioDecoderTolerancePropertyInfo = AudioDecoder
    attrGet = getAudioDecoderTolerance
    attrSet = setAudioDecoderTolerance
    attrTransfer _ v = do
        return v
    attrConstruct = constructAudioDecoderTolerance
    attrClear = undefined
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList AudioDecoder
type instance O.AttributeList AudioDecoder = AudioDecoderAttributeList
type AudioDecoderAttributeList = ('[ '("minLatency", AudioDecoderMinLatencyPropertyInfo), '("name", Gst.Object.ObjectNamePropertyInfo), '("parent", Gst.Object.ObjectParentPropertyInfo), '("plc", AudioDecoderPlcPropertyInfo), '("tolerance", AudioDecoderTolerancePropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
audioDecoderMinLatency :: AttrLabelProxy "minLatency"
audioDecoderMinLatency = AttrLabelProxy

audioDecoderPlc :: AttrLabelProxy "plc"
audioDecoderPlc = AttrLabelProxy

audioDecoderTolerance :: AttrLabelProxy "tolerance"
audioDecoderTolerance = AttrLabelProxy

#endif

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

#endif

-- method AudioDecoder::allocate_output_buffer
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "dec"
--           , argType =
--               TInterface Name { namespace = "GstAudio" , name = "AudioDecoder" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstAudioDecoder" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "size"
--           , argType = TBasicType TUInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "size of the buffer" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gst" , name = "Buffer" })
-- throws : False
-- Skip return : False

foreign import ccall "gst_audio_decoder_allocate_output_buffer" gst_audio_decoder_allocate_output_buffer :: 
    Ptr AudioDecoder ->                     -- dec : TInterface (Name {namespace = "GstAudio", name = "AudioDecoder"})
    Word64 ->                               -- size : TBasicType TUInt64
    IO (Ptr Gst.Buffer.Buffer)

-- | Helper function that allocates a buffer to hold an audio frame
-- for /@dec@/\'s current output format.
audioDecoderAllocateOutputBuffer ::
    (B.CallStack.HasCallStack, MonadIO m, IsAudioDecoder a) =>
    a
    -- ^ /@dec@/: a t'GI.GstAudio.Objects.AudioDecoder.AudioDecoder'
    -> Word64
    -- ^ /@size@/: size of the buffer
    -> m Gst.Buffer.Buffer
    -- ^ __Returns:__ allocated buffer
audioDecoderAllocateOutputBuffer :: a -> Word64 -> m Buffer
audioDecoderAllocateOutputBuffer dec :: a
dec size :: Word64
size = IO Buffer -> m Buffer
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Buffer -> m Buffer) -> IO Buffer -> m Buffer
forall a b. (a -> b) -> a -> b
$ do
    Ptr AudioDecoder
dec' <- a -> IO (Ptr AudioDecoder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
dec
    Ptr Buffer
result <- Ptr AudioDecoder -> Word64 -> IO (Ptr Buffer)
gst_audio_decoder_allocate_output_buffer Ptr AudioDecoder
dec' Word64
size
    Text -> Ptr Buffer -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "audioDecoderAllocateOutputBuffer" Ptr Buffer
result
    Buffer
result' <- ((ManagedPtr Buffer -> Buffer) -> Ptr Buffer -> IO Buffer
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Buffer -> Buffer
Gst.Buffer.Buffer) Ptr Buffer
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
dec
    Buffer -> IO Buffer
forall (m :: * -> *) a. Monad m => a -> m a
return Buffer
result'

#if defined(ENABLE_OVERLOADING)
data AudioDecoderAllocateOutputBufferMethodInfo
instance (signature ~ (Word64 -> m Gst.Buffer.Buffer), MonadIO m, IsAudioDecoder a) => O.MethodInfo AudioDecoderAllocateOutputBufferMethodInfo a signature where
    overloadedMethod = audioDecoderAllocateOutputBuffer

#endif

-- method AudioDecoder::finish_frame
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "dec"
--           , argType =
--               TInterface Name { namespace = "GstAudio" , name = "AudioDecoder" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstAudioDecoder" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "buf"
--           , argType = TInterface Name { namespace = "Gst" , name = "Buffer" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "decoded data" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "frames"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "number of decoded frames represented by decoded data"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gst" , name = "FlowReturn" })
-- throws : False
-- Skip return : False

foreign import ccall "gst_audio_decoder_finish_frame" gst_audio_decoder_finish_frame :: 
    Ptr AudioDecoder ->                     -- dec : TInterface (Name {namespace = "GstAudio", name = "AudioDecoder"})
    Ptr Gst.Buffer.Buffer ->                -- buf : TInterface (Name {namespace = "Gst", name = "Buffer"})
    Int32 ->                                -- frames : TBasicType TInt
    IO CInt

-- | Collects decoded data and pushes it downstream.
-- 
-- /@buf@/ may be NULL in which case the indicated number of frames
-- are discarded and considered to have produced no output
-- (e.g. lead-in or setup frames).
-- Otherwise, source pad caps must be set when it is called with valid
-- data in /@buf@/.
-- 
-- Note that a frame received in t'GI.GstAudio.Structs.AudioDecoderClass.AudioDecoderClass'.@/handle_frame/@() may be
-- invalidated by a call to this function.
audioDecoderFinishFrame ::
    (B.CallStack.HasCallStack, MonadIO m, IsAudioDecoder a) =>
    a
    -- ^ /@dec@/: a t'GI.GstAudio.Objects.AudioDecoder.AudioDecoder'
    -> Gst.Buffer.Buffer
    -- ^ /@buf@/: decoded data
    -> Int32
    -- ^ /@frames@/: number of decoded frames represented by decoded data
    -> m Gst.Enums.FlowReturn
    -- ^ __Returns:__ a t'GI.Gst.Enums.FlowReturn' that should be escalated to caller (of caller)
audioDecoderFinishFrame :: a -> Buffer -> Int32 -> m FlowReturn
audioDecoderFinishFrame dec :: a
dec buf :: Buffer
buf frames :: Int32
frames = IO FlowReturn -> m FlowReturn
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO FlowReturn -> m FlowReturn) -> IO FlowReturn -> m FlowReturn
forall a b. (a -> b) -> a -> b
$ do
    Ptr AudioDecoder
dec' <- a -> IO (Ptr AudioDecoder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
dec
    Ptr Buffer
buf' <- Buffer -> IO (Ptr Buffer)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Buffer
buf
    CInt
result <- Ptr AudioDecoder -> Ptr Buffer -> Int32 -> IO CInt
gst_audio_decoder_finish_frame Ptr AudioDecoder
dec' Ptr Buffer
buf' Int32
frames
    let result' :: FlowReturn
result' = (Int -> FlowReturn
forall a. Enum a => Int -> a
toEnum (Int -> FlowReturn) -> (CInt -> Int) -> CInt -> FlowReturn
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
dec
    Buffer -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Buffer
buf
    FlowReturn -> IO FlowReturn
forall (m :: * -> *) a. Monad m => a -> m a
return FlowReturn
result'

#if defined(ENABLE_OVERLOADING)
data AudioDecoderFinishFrameMethodInfo
instance (signature ~ (Gst.Buffer.Buffer -> Int32 -> m Gst.Enums.FlowReturn), MonadIO m, IsAudioDecoder a) => O.MethodInfo AudioDecoderFinishFrameMethodInfo a signature where
    overloadedMethod = audioDecoderFinishFrame

#endif

-- method AudioDecoder::finish_subframe
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "dec"
--           , argType =
--               TInterface Name { namespace = "GstAudio" , name = "AudioDecoder" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstAudioDecoder" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "buf"
--           , argType = TInterface Name { namespace = "Gst" , name = "Buffer" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "decoded data" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gst" , name = "FlowReturn" })
-- throws : False
-- Skip return : False

foreign import ccall "gst_audio_decoder_finish_subframe" gst_audio_decoder_finish_subframe :: 
    Ptr AudioDecoder ->                     -- dec : TInterface (Name {namespace = "GstAudio", name = "AudioDecoder"})
    Ptr Gst.Buffer.Buffer ->                -- buf : TInterface (Name {namespace = "Gst", name = "Buffer"})
    IO CInt

-- | Collects decoded data and pushes it downstream. This function may be called
-- multiple times for a given input frame.
-- 
-- /@buf@/ may be NULL in which case it is assumed that the current input frame is
-- finished. This is equivalent to calling 'GI.GstAudio.Objects.AudioDecoder.audioDecoderFinishSubframe'
-- with a NULL buffer and frames=1 after having pushed out all decoded audio
-- subframes using this function.
-- 
-- When called with valid data in /@buf@/ the source pad caps must have been set
-- already.
-- 
-- Note that a frame received in t'GI.GstAudio.Structs.AudioDecoderClass.AudioDecoderClass'.@/handle_frame/@() may be
-- invalidated by a call to this function.
-- 
-- /Since: 1.16/
audioDecoderFinishSubframe ::
    (B.CallStack.HasCallStack, MonadIO m, IsAudioDecoder a) =>
    a
    -- ^ /@dec@/: a t'GI.GstAudio.Objects.AudioDecoder.AudioDecoder'
    -> Gst.Buffer.Buffer
    -- ^ /@buf@/: decoded data
    -> m Gst.Enums.FlowReturn
    -- ^ __Returns:__ a t'GI.Gst.Enums.FlowReturn' that should be escalated to caller (of caller)
audioDecoderFinishSubframe :: a -> Buffer -> m FlowReturn
audioDecoderFinishSubframe dec :: a
dec buf :: Buffer
buf = IO FlowReturn -> m FlowReturn
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO FlowReturn -> m FlowReturn) -> IO FlowReturn -> m FlowReturn
forall a b. (a -> b) -> a -> b
$ do
    Ptr AudioDecoder
dec' <- a -> IO (Ptr AudioDecoder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
dec
    Ptr Buffer
buf' <- Buffer -> IO (Ptr Buffer)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Buffer
buf
    CInt
result <- Ptr AudioDecoder -> Ptr Buffer -> IO CInt
gst_audio_decoder_finish_subframe Ptr AudioDecoder
dec' Ptr Buffer
buf'
    let result' :: FlowReturn
result' = (Int -> FlowReturn
forall a. Enum a => Int -> a
toEnum (Int -> FlowReturn) -> (CInt -> Int) -> CInt -> FlowReturn
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
dec
    Buffer -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Buffer
buf
    FlowReturn -> IO FlowReturn
forall (m :: * -> *) a. Monad m => a -> m a
return FlowReturn
result'

#if defined(ENABLE_OVERLOADING)
data AudioDecoderFinishSubframeMethodInfo
instance (signature ~ (Gst.Buffer.Buffer -> m Gst.Enums.FlowReturn), MonadIO m, IsAudioDecoder a) => O.MethodInfo AudioDecoderFinishSubframeMethodInfo a signature where
    overloadedMethod = audioDecoderFinishSubframe

#endif

-- method AudioDecoder::get_allocator
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "dec"
--           , argType =
--               TInterface Name { namespace = "GstAudio" , name = "AudioDecoder" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstAudioDecoder" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "allocator"
--           , argType =
--               TInterface Name { namespace = "Gst" , name = "Allocator" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #GstAllocator\nused"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "params"
--           , argType =
--               TInterface Name { namespace = "Gst" , name = "AllocationParams" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the\n#GstAllocationParams of @allocator"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gst_audio_decoder_get_allocator" gst_audio_decoder_get_allocator :: 
    Ptr AudioDecoder ->                     -- dec : TInterface (Name {namespace = "GstAudio", name = "AudioDecoder"})
    Ptr (Ptr Gst.Allocator.Allocator) ->    -- allocator : TInterface (Name {namespace = "Gst", name = "Allocator"})
    Ptr Gst.AllocationParams.AllocationParams -> -- params : TInterface (Name {namespace = "Gst", name = "AllocationParams"})
    IO ()

-- | Lets t'GI.GstAudio.Objects.AudioDecoder.AudioDecoder' sub-classes to know the memory /@allocator@/
-- used by the base class and its /@params@/.
-- 
-- Unref the /@allocator@/ after use it.
audioDecoderGetAllocator ::
    (B.CallStack.HasCallStack, MonadIO m, IsAudioDecoder a) =>
    a
    -- ^ /@dec@/: a t'GI.GstAudio.Objects.AudioDecoder.AudioDecoder'
    -> m ((Gst.Allocator.Allocator, Gst.AllocationParams.AllocationParams))
audioDecoderGetAllocator :: a -> m (Allocator, AllocationParams)
audioDecoderGetAllocator dec :: a
dec = IO (Allocator, AllocationParams) -> m (Allocator, AllocationParams)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Allocator, AllocationParams)
 -> m (Allocator, AllocationParams))
-> IO (Allocator, AllocationParams)
-> m (Allocator, AllocationParams)
forall a b. (a -> b) -> a -> b
$ do
    Ptr AudioDecoder
dec' <- a -> IO (Ptr AudioDecoder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
dec
    Ptr (Ptr Allocator)
allocator <- IO (Ptr (Ptr Allocator))
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr (Ptr Gst.Allocator.Allocator))
    Ptr AllocationParams
params <- Int -> IO (Ptr AllocationParams)
forall a. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes 64 :: IO (Ptr Gst.AllocationParams.AllocationParams)
    Ptr AudioDecoder
-> Ptr (Ptr Allocator) -> Ptr AllocationParams -> IO ()
gst_audio_decoder_get_allocator Ptr AudioDecoder
dec' Ptr (Ptr Allocator)
allocator Ptr AllocationParams
params
    Ptr Allocator
allocator' <- Ptr (Ptr Allocator) -> IO (Ptr Allocator)
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr Allocator)
allocator
    Allocator
allocator'' <- ((ManagedPtr Allocator -> Allocator)
-> Ptr Allocator -> IO Allocator
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Allocator -> Allocator
Gst.Allocator.Allocator) Ptr Allocator
allocator'
    AllocationParams
params' <- ((ManagedPtr AllocationParams -> AllocationParams)
-> Ptr AllocationParams -> IO AllocationParams
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr AllocationParams -> AllocationParams
Gst.AllocationParams.AllocationParams) Ptr AllocationParams
params
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
dec
    Ptr (Ptr Allocator) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr Allocator)
allocator
    (Allocator, AllocationParams) -> IO (Allocator, AllocationParams)
forall (m :: * -> *) a. Monad m => a -> m a
return (Allocator
allocator'', AllocationParams
params')

#if defined(ENABLE_OVERLOADING)
data AudioDecoderGetAllocatorMethodInfo
instance (signature ~ (m ((Gst.Allocator.Allocator, Gst.AllocationParams.AllocationParams))), MonadIO m, IsAudioDecoder a) => O.MethodInfo AudioDecoderGetAllocatorMethodInfo a signature where
    overloadedMethod = audioDecoderGetAllocator

#endif

-- method AudioDecoder::get_audio_info
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "dec"
--           , argType =
--               TInterface Name { namespace = "GstAudio" , name = "AudioDecoder" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstAudioDecoder" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "GstAudio" , name = "AudioInfo" })
-- throws : False
-- Skip return : False

foreign import ccall "gst_audio_decoder_get_audio_info" gst_audio_decoder_get_audio_info :: 
    Ptr AudioDecoder ->                     -- dec : TInterface (Name {namespace = "GstAudio", name = "AudioDecoder"})
    IO (Ptr GstAudio.AudioInfo.AudioInfo)

-- | /No description available in the introspection data./
audioDecoderGetAudioInfo ::
    (B.CallStack.HasCallStack, MonadIO m, IsAudioDecoder a) =>
    a
    -- ^ /@dec@/: a t'GI.GstAudio.Objects.AudioDecoder.AudioDecoder'
    -> m GstAudio.AudioInfo.AudioInfo
    -- ^ __Returns:__ a t'GI.GstAudio.Structs.AudioInfo.AudioInfo' describing the input audio format
audioDecoderGetAudioInfo :: a -> m AudioInfo
audioDecoderGetAudioInfo dec :: a
dec = IO AudioInfo -> m AudioInfo
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO AudioInfo -> m AudioInfo) -> IO AudioInfo -> m AudioInfo
forall a b. (a -> b) -> a -> b
$ do
    Ptr AudioDecoder
dec' <- a -> IO (Ptr AudioDecoder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
dec
    Ptr AudioInfo
result <- Ptr AudioDecoder -> IO (Ptr AudioInfo)
gst_audio_decoder_get_audio_info Ptr AudioDecoder
dec'
    Text -> Ptr AudioInfo -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "audioDecoderGetAudioInfo" Ptr AudioInfo
result
    AudioInfo
result' <- ((ManagedPtr AudioInfo -> AudioInfo)
-> Ptr AudioInfo -> IO AudioInfo
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr AudioInfo -> AudioInfo
GstAudio.AudioInfo.AudioInfo) Ptr AudioInfo
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
dec
    AudioInfo -> IO AudioInfo
forall (m :: * -> *) a. Monad m => a -> m a
return AudioInfo
result'

#if defined(ENABLE_OVERLOADING)
data AudioDecoderGetAudioInfoMethodInfo
instance (signature ~ (m GstAudio.AudioInfo.AudioInfo), MonadIO m, IsAudioDecoder a) => O.MethodInfo AudioDecoderGetAudioInfoMethodInfo a signature where
    overloadedMethod = audioDecoderGetAudioInfo

#endif

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

foreign import ccall "gst_audio_decoder_get_delay" gst_audio_decoder_get_delay :: 
    Ptr AudioDecoder ->                     -- dec : TInterface (Name {namespace = "GstAudio", name = "AudioDecoder"})
    IO Int32

-- | /No description available in the introspection data./
audioDecoderGetDelay ::
    (B.CallStack.HasCallStack, MonadIO m, IsAudioDecoder a) =>
    a
    -- ^ /@dec@/: a t'GI.GstAudio.Objects.AudioDecoder.AudioDecoder'
    -> m Int32
    -- ^ __Returns:__ currently configured decoder delay
audioDecoderGetDelay :: a -> m Int32
audioDecoderGetDelay dec :: a
dec = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr AudioDecoder
dec' <- a -> IO (Ptr AudioDecoder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
dec
    Int32
result <- Ptr AudioDecoder -> IO Int32
gst_audio_decoder_get_delay Ptr AudioDecoder
dec'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
dec
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data AudioDecoderGetDelayMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsAudioDecoder a) => O.MethodInfo AudioDecoderGetDelayMethodInfo a signature where
    overloadedMethod = audioDecoderGetDelay

#endif

-- method AudioDecoder::get_drainable
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "dec"
--           , argType =
--               TInterface Name { namespace = "GstAudio" , name = "AudioDecoder" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstAudioDecoder" , 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_audio_decoder_get_drainable" gst_audio_decoder_get_drainable :: 
    Ptr AudioDecoder ->                     -- dec : TInterface (Name {namespace = "GstAudio", name = "AudioDecoder"})
    IO CInt

-- | Queries decoder drain handling.
audioDecoderGetDrainable ::
    (B.CallStack.HasCallStack, MonadIO m, IsAudioDecoder a) =>
    a
    -- ^ /@dec@/: a t'GI.GstAudio.Objects.AudioDecoder.AudioDecoder'
    -> m Bool
    -- ^ __Returns:__ TRUE if drainable handling is enabled.
    -- 
    -- MT safe.
audioDecoderGetDrainable :: a -> m Bool
audioDecoderGetDrainable dec :: a
dec = 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 AudioDecoder
dec' <- a -> IO (Ptr AudioDecoder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
dec
    CInt
result <- Ptr AudioDecoder -> IO CInt
gst_audio_decoder_get_drainable Ptr AudioDecoder
dec'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
dec
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data AudioDecoderGetDrainableMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsAudioDecoder a) => O.MethodInfo AudioDecoderGetDrainableMethodInfo a signature where
    overloadedMethod = audioDecoderGetDrainable

#endif

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

foreign import ccall "gst_audio_decoder_get_estimate_rate" gst_audio_decoder_get_estimate_rate :: 
    Ptr AudioDecoder ->                     -- dec : TInterface (Name {namespace = "GstAudio", name = "AudioDecoder"})
    IO Int32

-- | /No description available in the introspection data./
audioDecoderGetEstimateRate ::
    (B.CallStack.HasCallStack, MonadIO m, IsAudioDecoder a) =>
    a
    -- ^ /@dec@/: a t'GI.GstAudio.Objects.AudioDecoder.AudioDecoder'
    -> m Int32
    -- ^ __Returns:__ currently configured byte to time conversion setting
audioDecoderGetEstimateRate :: a -> m Int32
audioDecoderGetEstimateRate dec :: a
dec = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr AudioDecoder
dec' <- a -> IO (Ptr AudioDecoder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
dec
    Int32
result <- Ptr AudioDecoder -> IO Int32
gst_audio_decoder_get_estimate_rate Ptr AudioDecoder
dec'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
dec
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data AudioDecoderGetEstimateRateMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsAudioDecoder a) => O.MethodInfo AudioDecoderGetEstimateRateMethodInfo a signature where
    overloadedMethod = audioDecoderGetEstimateRate

#endif

-- method AudioDecoder::get_latency
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "dec"
--           , argType =
--               TInterface Name { namespace = "GstAudio" , name = "AudioDecoder" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstAudioDecoder" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "min"
--           , argType = TBasicType TUInt64
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a pointer to storage to hold minimum latency"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "max"
--           , argType = TBasicType TUInt64
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a pointer to storage to hold maximum latency"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gst_audio_decoder_get_latency" gst_audio_decoder_get_latency :: 
    Ptr AudioDecoder ->                     -- dec : TInterface (Name {namespace = "GstAudio", name = "AudioDecoder"})
    Ptr Word64 ->                           -- min : TBasicType TUInt64
    Ptr Word64 ->                           -- max : TBasicType TUInt64
    IO ()

-- | Sets the variables pointed to by /@min@/ and /@max@/ to the currently configured
-- latency.
audioDecoderGetLatency ::
    (B.CallStack.HasCallStack, MonadIO m, IsAudioDecoder a) =>
    a
    -- ^ /@dec@/: a t'GI.GstAudio.Objects.AudioDecoder.AudioDecoder'
    -> m ((Word64, Word64))
audioDecoderGetLatency :: a -> m (Word64, Word64)
audioDecoderGetLatency dec :: a
dec = IO (Word64, Word64) -> m (Word64, Word64)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Word64, Word64) -> m (Word64, Word64))
-> IO (Word64, Word64) -> m (Word64, Word64)
forall a b. (a -> b) -> a -> b
$ do
    Ptr AudioDecoder
dec' <- a -> IO (Ptr AudioDecoder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
dec
    Ptr Word64
min <- IO (Ptr Word64)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word64)
    Ptr Word64
max <- IO (Ptr Word64)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word64)
    Ptr AudioDecoder -> Ptr Word64 -> Ptr Word64 -> IO ()
gst_audio_decoder_get_latency Ptr AudioDecoder
dec' Ptr Word64
min Ptr Word64
max
    Word64
min' <- Ptr Word64 -> IO Word64
forall a. Storable a => Ptr a -> IO a
peek Ptr Word64
min
    Word64
max' <- Ptr Word64 -> IO Word64
forall a. Storable a => Ptr a -> IO a
peek Ptr Word64
max
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
dec
    Ptr Word64 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word64
min
    Ptr Word64 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word64
max
    (Word64, Word64) -> IO (Word64, Word64)
forall (m :: * -> *) a. Monad m => a -> m a
return (Word64
min', Word64
max')

#if defined(ENABLE_OVERLOADING)
data AudioDecoderGetLatencyMethodInfo
instance (signature ~ (m ((Word64, Word64))), MonadIO m, IsAudioDecoder a) => O.MethodInfo AudioDecoderGetLatencyMethodInfo a signature where
    overloadedMethod = audioDecoderGetLatency

#endif

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

foreign import ccall "gst_audio_decoder_get_max_errors" gst_audio_decoder_get_max_errors :: 
    Ptr AudioDecoder ->                     -- dec : TInterface (Name {namespace = "GstAudio", name = "AudioDecoder"})
    IO Int32

-- | /No description available in the introspection data./
audioDecoderGetMaxErrors ::
    (B.CallStack.HasCallStack, MonadIO m, IsAudioDecoder a) =>
    a
    -- ^ /@dec@/: a t'GI.GstAudio.Objects.AudioDecoder.AudioDecoder'
    -> m Int32
    -- ^ __Returns:__ currently configured decoder tolerated error count.
audioDecoderGetMaxErrors :: a -> m Int32
audioDecoderGetMaxErrors dec :: a
dec = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr AudioDecoder
dec' <- a -> IO (Ptr AudioDecoder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
dec
    Int32
result <- Ptr AudioDecoder -> IO Int32
gst_audio_decoder_get_max_errors Ptr AudioDecoder
dec'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
dec
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data AudioDecoderGetMaxErrorsMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsAudioDecoder a) => O.MethodInfo AudioDecoderGetMaxErrorsMethodInfo a signature where
    overloadedMethod = audioDecoderGetMaxErrors

#endif

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

foreign import ccall "gst_audio_decoder_get_min_latency" gst_audio_decoder_get_min_latency :: 
    Ptr AudioDecoder ->                     -- dec : TInterface (Name {namespace = "GstAudio", name = "AudioDecoder"})
    IO Word64

-- | Queries decoder\'s latency aggregation.
audioDecoderGetMinLatency ::
    (B.CallStack.HasCallStack, MonadIO m, IsAudioDecoder a) =>
    a
    -- ^ /@dec@/: a t'GI.GstAudio.Objects.AudioDecoder.AudioDecoder'
    -> m Word64
    -- ^ __Returns:__ aggregation latency.
    -- 
    -- MT safe.
audioDecoderGetMinLatency :: a -> m Word64
audioDecoderGetMinLatency dec :: a
dec = 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
$ do
    Ptr AudioDecoder
dec' <- a -> IO (Ptr AudioDecoder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
dec
    Word64
result <- Ptr AudioDecoder -> IO Word64
gst_audio_decoder_get_min_latency Ptr AudioDecoder
dec'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
dec
    Word64 -> IO Word64
forall (m :: * -> *) a. Monad m => a -> m a
return Word64
result

#if defined(ENABLE_OVERLOADING)
data AudioDecoderGetMinLatencyMethodInfo
instance (signature ~ (m Word64), MonadIO m, IsAudioDecoder a) => O.MethodInfo AudioDecoderGetMinLatencyMethodInfo a signature where
    overloadedMethod = audioDecoderGetMinLatency

#endif

-- method AudioDecoder::get_needs_format
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "dec"
--           , argType =
--               TInterface Name { namespace = "GstAudio" , name = "AudioDecoder" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstAudioDecoder" , 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_audio_decoder_get_needs_format" gst_audio_decoder_get_needs_format :: 
    Ptr AudioDecoder ->                     -- dec : TInterface (Name {namespace = "GstAudio", name = "AudioDecoder"})
    IO CInt

-- | Queries decoder required format handling.
audioDecoderGetNeedsFormat ::
    (B.CallStack.HasCallStack, MonadIO m, IsAudioDecoder a) =>
    a
    -- ^ /@dec@/: a t'GI.GstAudio.Objects.AudioDecoder.AudioDecoder'
    -> m Bool
    -- ^ __Returns:__ TRUE if required format handling is enabled.
    -- 
    -- MT safe.
audioDecoderGetNeedsFormat :: a -> m Bool
audioDecoderGetNeedsFormat dec :: a
dec = 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 AudioDecoder
dec' <- a -> IO (Ptr AudioDecoder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
dec
    CInt
result <- Ptr AudioDecoder -> IO CInt
gst_audio_decoder_get_needs_format Ptr AudioDecoder
dec'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
dec
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data AudioDecoderGetNeedsFormatMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsAudioDecoder a) => O.MethodInfo AudioDecoderGetNeedsFormatMethodInfo a signature where
    overloadedMethod = audioDecoderGetNeedsFormat

#endif

-- method AudioDecoder::get_parse_state
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "dec"
--           , argType =
--               TInterface Name { namespace = "GstAudio" , name = "AudioDecoder" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstAudioDecoder" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "sync"
--           , argType = TBasicType TBoolean
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a pointer to a variable to hold the current sync state"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "eos"
--           , argType = TBasicType TBoolean
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a pointer to a variable to hold the current eos state"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gst_audio_decoder_get_parse_state" gst_audio_decoder_get_parse_state :: 
    Ptr AudioDecoder ->                     -- dec : TInterface (Name {namespace = "GstAudio", name = "AudioDecoder"})
    Ptr CInt ->                             -- sync : TBasicType TBoolean
    Ptr CInt ->                             -- eos : TBasicType TBoolean
    IO ()

-- | Return current parsing (sync and eos) state.
audioDecoderGetParseState ::
    (B.CallStack.HasCallStack, MonadIO m, IsAudioDecoder a) =>
    a
    -- ^ /@dec@/: a t'GI.GstAudio.Objects.AudioDecoder.AudioDecoder'
    -> m ((Bool, Bool))
audioDecoderGetParseState :: a -> m (Bool, Bool)
audioDecoderGetParseState dec :: a
dec = IO (Bool, Bool) -> m (Bool, Bool)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, Bool) -> m (Bool, Bool))
-> IO (Bool, Bool) -> m (Bool, Bool)
forall a b. (a -> b) -> a -> b
$ do
    Ptr AudioDecoder
dec' <- a -> IO (Ptr AudioDecoder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
dec
    Ptr CInt
sync <- IO (Ptr CInt)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CInt)
    Ptr CInt
eos <- IO (Ptr CInt)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CInt)
    Ptr AudioDecoder -> Ptr CInt -> Ptr CInt -> IO ()
gst_audio_decoder_get_parse_state Ptr AudioDecoder
dec' Ptr CInt
sync Ptr CInt
eos
    CInt
sync' <- Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
sync
    let sync'' :: Bool
sync'' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
sync'
    CInt
eos' <- Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
eos
    let eos'' :: Bool
eos'' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
eos'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
dec
    Ptr CInt -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CInt
sync
    Ptr CInt -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CInt
eos
    (Bool, Bool) -> IO (Bool, Bool)
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
sync'', Bool
eos'')

#if defined(ENABLE_OVERLOADING)
data AudioDecoderGetParseStateMethodInfo
instance (signature ~ (m ((Bool, Bool))), MonadIO m, IsAudioDecoder a) => O.MethodInfo AudioDecoderGetParseStateMethodInfo a signature where
    overloadedMethod = audioDecoderGetParseState

#endif

-- method AudioDecoder::get_plc
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "dec"
--           , argType =
--               TInterface Name { namespace = "GstAudio" , name = "AudioDecoder" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstAudioDecoder" , 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_audio_decoder_get_plc" gst_audio_decoder_get_plc :: 
    Ptr AudioDecoder ->                     -- dec : TInterface (Name {namespace = "GstAudio", name = "AudioDecoder"})
    IO CInt

-- | Queries decoder packet loss concealment handling.
audioDecoderGetPlc ::
    (B.CallStack.HasCallStack, MonadIO m, IsAudioDecoder a) =>
    a
    -- ^ /@dec@/: a t'GI.GstAudio.Objects.AudioDecoder.AudioDecoder'
    -> m Bool
    -- ^ __Returns:__ TRUE if packet loss concealment is enabled.
    -- 
    -- MT safe.
audioDecoderGetPlc :: a -> m Bool
audioDecoderGetPlc dec :: a
dec = 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 AudioDecoder
dec' <- a -> IO (Ptr AudioDecoder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
dec
    CInt
result <- Ptr AudioDecoder -> IO CInt
gst_audio_decoder_get_plc Ptr AudioDecoder
dec'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
dec
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data AudioDecoderGetPlcMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsAudioDecoder a) => O.MethodInfo AudioDecoderGetPlcMethodInfo a signature where
    overloadedMethod = audioDecoderGetPlc

#endif

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

foreign import ccall "gst_audio_decoder_get_plc_aware" gst_audio_decoder_get_plc_aware :: 
    Ptr AudioDecoder ->                     -- dec : TInterface (Name {namespace = "GstAudio", name = "AudioDecoder"})
    IO Int32

-- | /No description available in the introspection data./
audioDecoderGetPlcAware ::
    (B.CallStack.HasCallStack, MonadIO m, IsAudioDecoder a) =>
    a
    -- ^ /@dec@/: a t'GI.GstAudio.Objects.AudioDecoder.AudioDecoder'
    -> m Int32
    -- ^ __Returns:__ currently configured plc handling
audioDecoderGetPlcAware :: a -> m Int32
audioDecoderGetPlcAware dec :: a
dec = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr AudioDecoder
dec' <- a -> IO (Ptr AudioDecoder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
dec
    Int32
result <- Ptr AudioDecoder -> IO Int32
gst_audio_decoder_get_plc_aware Ptr AudioDecoder
dec'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
dec
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data AudioDecoderGetPlcAwareMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsAudioDecoder a) => O.MethodInfo AudioDecoderGetPlcAwareMethodInfo a signature where
    overloadedMethod = audioDecoderGetPlcAware

#endif

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

foreign import ccall "gst_audio_decoder_get_tolerance" gst_audio_decoder_get_tolerance :: 
    Ptr AudioDecoder ->                     -- dec : TInterface (Name {namespace = "GstAudio", name = "AudioDecoder"})
    IO Word64

-- | Queries current audio jitter tolerance threshold.
audioDecoderGetTolerance ::
    (B.CallStack.HasCallStack, MonadIO m, IsAudioDecoder a) =>
    a
    -- ^ /@dec@/: a t'GI.GstAudio.Objects.AudioDecoder.AudioDecoder'
    -> m Word64
    -- ^ __Returns:__ decoder audio jitter tolerance threshold.
    -- 
    -- MT safe.
audioDecoderGetTolerance :: a -> m Word64
audioDecoderGetTolerance dec :: a
dec = 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
$ do
    Ptr AudioDecoder
dec' <- a -> IO (Ptr AudioDecoder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
dec
    Word64
result <- Ptr AudioDecoder -> IO Word64
gst_audio_decoder_get_tolerance Ptr AudioDecoder
dec'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
dec
    Word64 -> IO Word64
forall (m :: * -> *) a. Monad m => a -> m a
return Word64
result

#if defined(ENABLE_OVERLOADING)
data AudioDecoderGetToleranceMethodInfo
instance (signature ~ (m Word64), MonadIO m, IsAudioDecoder a) => O.MethodInfo AudioDecoderGetToleranceMethodInfo a signature where
    overloadedMethod = audioDecoderGetTolerance

#endif

-- method AudioDecoder::merge_tags
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "dec"
--           , argType =
--               TInterface Name { namespace = "GstAudio" , name = "AudioDecoder" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstAudioDecoder" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "tags"
--           , argType =
--               TInterface Name { namespace = "Gst" , name = "TagList" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstTagList to merge, or NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "mode"
--           , argType =
--               TInterface Name { namespace = "Gst" , name = "TagMergeMode" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the #GstTagMergeMode to use, usually #GST_TAG_MERGE_REPLACE"
--                 , 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_decoder_merge_tags" gst_audio_decoder_merge_tags :: 
    Ptr AudioDecoder ->                     -- dec : TInterface (Name {namespace = "GstAudio", name = "AudioDecoder"})
    Ptr Gst.TagList.TagList ->              -- tags : TInterface (Name {namespace = "Gst", name = "TagList"})
    CUInt ->                                -- mode : TInterface (Name {namespace = "Gst", name = "TagMergeMode"})
    IO ()

-- | Sets the audio decoder tags and how they should be merged with any
-- upstream stream tags. This will override any tags previously-set
-- with 'GI.GstAudio.Objects.AudioDecoder.audioDecoderMergeTags'.
-- 
-- Note that this is provided for convenience, and the subclass is
-- not required to use this and can still do tag handling on its own.
audioDecoderMergeTags ::
    (B.CallStack.HasCallStack, MonadIO m, IsAudioDecoder a) =>
    a
    -- ^ /@dec@/: a t'GI.GstAudio.Objects.AudioDecoder.AudioDecoder'
    -> Maybe (Gst.TagList.TagList)
    -- ^ /@tags@/: a t'GI.Gst.Structs.TagList.TagList' to merge, or NULL
    -> Gst.Enums.TagMergeMode
    -- ^ /@mode@/: the t'GI.Gst.Enums.TagMergeMode' to use, usually @/GST_TAG_MERGE_REPLACE/@
    -> m ()
audioDecoderMergeTags :: a -> Maybe TagList -> TagMergeMode -> m ()
audioDecoderMergeTags dec :: a
dec tags :: Maybe TagList
tags mode :: TagMergeMode
mode = 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 AudioDecoder
dec' <- a -> IO (Ptr AudioDecoder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
dec
    Ptr TagList
maybeTags <- case Maybe TagList
tags of
        Nothing -> Ptr TagList -> IO (Ptr TagList)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr TagList
forall a. Ptr a
nullPtr
        Just jTags :: TagList
jTags -> do
            Ptr TagList
jTags' <- TagList -> IO (Ptr TagList)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TagList
jTags
            Ptr TagList -> IO (Ptr TagList)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr TagList
jTags'
    let mode' :: CUInt
mode' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (TagMergeMode -> Int) -> TagMergeMode -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TagMergeMode -> Int
forall a. Enum a => a -> Int
fromEnum) TagMergeMode
mode
    Ptr AudioDecoder -> Ptr TagList -> CUInt -> IO ()
gst_audio_decoder_merge_tags Ptr AudioDecoder
dec' Ptr TagList
maybeTags CUInt
mode'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
dec
    Maybe TagList -> (TagList -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe TagList
tags TagList -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data AudioDecoderMergeTagsMethodInfo
instance (signature ~ (Maybe (Gst.TagList.TagList) -> Gst.Enums.TagMergeMode -> m ()), MonadIO m, IsAudioDecoder a) => O.MethodInfo AudioDecoderMergeTagsMethodInfo a signature where
    overloadedMethod = audioDecoderMergeTags

#endif

-- method AudioDecoder::negotiate
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "dec"
--           , argType =
--               TInterface Name { namespace = "GstAudio" , name = "AudioDecoder" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstAudioDecoder" , 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_audio_decoder_negotiate" gst_audio_decoder_negotiate :: 
    Ptr AudioDecoder ->                     -- dec : TInterface (Name {namespace = "GstAudio", name = "AudioDecoder"})
    IO CInt

-- | Negotiate with downstream elements to currently configured t'GI.GstAudio.Structs.AudioInfo.AudioInfo'.
-- Unmark GST_PAD_FLAG_NEED_RECONFIGURE in any case. But mark it again if
-- negotiate fails.
audioDecoderNegotiate ::
    (B.CallStack.HasCallStack, MonadIO m, IsAudioDecoder a) =>
    a
    -- ^ /@dec@/: a t'GI.GstAudio.Objects.AudioDecoder.AudioDecoder'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the negotiation succeeded, else 'P.False'.
audioDecoderNegotiate :: a -> m Bool
audioDecoderNegotiate dec :: a
dec = 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 AudioDecoder
dec' <- a -> IO (Ptr AudioDecoder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
dec
    CInt
result <- Ptr AudioDecoder -> IO CInt
gst_audio_decoder_negotiate Ptr AudioDecoder
dec'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
dec
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data AudioDecoderNegotiateMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsAudioDecoder a) => O.MethodInfo AudioDecoderNegotiateMethodInfo a signature where
    overloadedMethod = audioDecoderNegotiate

#endif

-- method AudioDecoder::proxy_getcaps
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "decoder"
--           , argType =
--               TInterface Name { namespace = "GstAudio" , name = "AudioDecoder" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstAudioDecoder" , 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 = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "initial caps" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "filter"
--           , argType = TInterface Name { namespace = "Gst" , name = "Caps" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "filter caps" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gst" , name = "Caps" })
-- throws : False
-- Skip return : False

foreign import ccall "gst_audio_decoder_proxy_getcaps" gst_audio_decoder_proxy_getcaps :: 
    Ptr AudioDecoder ->                     -- decoder : TInterface (Name {namespace = "GstAudio", name = "AudioDecoder"})
    Ptr Gst.Caps.Caps ->                    -- caps : TInterface (Name {namespace = "Gst", name = "Caps"})
    Ptr Gst.Caps.Caps ->                    -- filter : TInterface (Name {namespace = "Gst", name = "Caps"})
    IO (Ptr Gst.Caps.Caps)

-- | Returns caps that express /@caps@/ (or sink template caps if /@caps@/ == NULL)
-- restricted to rate\/channels\/... combinations supported by downstream
-- elements.
-- 
-- /Since: 1.6/
audioDecoderProxyGetcaps ::
    (B.CallStack.HasCallStack, MonadIO m, IsAudioDecoder a) =>
    a
    -- ^ /@decoder@/: a t'GI.GstAudio.Objects.AudioDecoder.AudioDecoder'
    -> Maybe (Gst.Caps.Caps)
    -- ^ /@caps@/: initial caps
    -> Maybe (Gst.Caps.Caps)
    -- ^ /@filter@/: filter caps
    -> m Gst.Caps.Caps
    -- ^ __Returns:__ a t'GI.Gst.Structs.Caps.Caps' owned by caller
audioDecoderProxyGetcaps :: a -> Maybe Caps -> Maybe Caps -> m Caps
audioDecoderProxyGetcaps decoder :: a
decoder caps :: Maybe Caps
caps filter :: Maybe Caps
filter = IO Caps -> m Caps
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Caps -> m Caps) -> IO Caps -> m Caps
forall a b. (a -> b) -> a -> b
$ do
    Ptr AudioDecoder
decoder' <- a -> IO (Ptr AudioDecoder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
decoder
    Ptr Caps
maybeCaps <- case Maybe Caps
caps of
        Nothing -> Ptr Caps -> IO (Ptr Caps)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Caps
forall a. Ptr a
nullPtr
        Just jCaps :: Caps
jCaps -> do
            Ptr Caps
jCaps' <- Caps -> IO (Ptr Caps)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Caps
jCaps
            Ptr Caps -> IO (Ptr Caps)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Caps
jCaps'
    Ptr Caps
maybeFilter <- case Maybe Caps
filter of
        Nothing -> Ptr Caps -> IO (Ptr Caps)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Caps
forall a. Ptr a
nullPtr
        Just jFilter :: Caps
jFilter -> do
            Ptr Caps
jFilter' <- Caps -> IO (Ptr Caps)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Caps
jFilter
            Ptr Caps -> IO (Ptr Caps)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Caps
jFilter'
    Ptr Caps
result <- Ptr AudioDecoder -> Ptr Caps -> Ptr Caps -> IO (Ptr Caps)
gst_audio_decoder_proxy_getcaps Ptr AudioDecoder
decoder' Ptr Caps
maybeCaps Ptr Caps
maybeFilter
    Text -> Ptr Caps -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "audioDecoderProxyGetcaps" Ptr Caps
result
    Caps
result' <- ((ManagedPtr Caps -> Caps) -> Ptr Caps -> IO Caps
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Caps -> Caps
Gst.Caps.Caps) Ptr Caps
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
decoder
    Maybe Caps -> (Caps -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe Caps
caps Caps -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    Maybe Caps -> (Caps -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe Caps
filter Caps -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    Caps -> IO Caps
forall (m :: * -> *) a. Monad m => a -> m a
return Caps
result'

#if defined(ENABLE_OVERLOADING)
data AudioDecoderProxyGetcapsMethodInfo
instance (signature ~ (Maybe (Gst.Caps.Caps) -> Maybe (Gst.Caps.Caps) -> m Gst.Caps.Caps), MonadIO m, IsAudioDecoder a) => O.MethodInfo AudioDecoderProxyGetcapsMethodInfo a signature where
    overloadedMethod = audioDecoderProxyGetcaps

#endif

-- method AudioDecoder::set_allocation_caps
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "dec"
--           , argType =
--               TInterface Name { namespace = "GstAudio" , name = "AudioDecoder" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstAudioDecoder" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "allocation_caps"
--           , argType = TInterface Name { namespace = "Gst" , name = "Caps" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstCaps or %NULL"
--                 , 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_decoder_set_allocation_caps" gst_audio_decoder_set_allocation_caps :: 
    Ptr AudioDecoder ->                     -- dec : TInterface (Name {namespace = "GstAudio", name = "AudioDecoder"})
    Ptr Gst.Caps.Caps ->                    -- allocation_caps : TInterface (Name {namespace = "Gst", name = "Caps"})
    IO ()

-- | Sets a caps in allocation query which are different from the set
-- pad\'s caps. Use this function before calling
-- 'GI.GstAudio.Objects.AudioDecoder.audioDecoderNegotiate'. Setting to 'P.Nothing' the allocation
-- query will use the caps from the pad.
-- 
-- /Since: 1.10/
audioDecoderSetAllocationCaps ::
    (B.CallStack.HasCallStack, MonadIO m, IsAudioDecoder a) =>
    a
    -- ^ /@dec@/: a t'GI.GstAudio.Objects.AudioDecoder.AudioDecoder'
    -> Maybe (Gst.Caps.Caps)
    -- ^ /@allocationCaps@/: a t'GI.Gst.Structs.Caps.Caps' or 'P.Nothing'
    -> m ()
audioDecoderSetAllocationCaps :: a -> Maybe Caps -> m ()
audioDecoderSetAllocationCaps dec :: a
dec allocationCaps :: Maybe Caps
allocationCaps = 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 AudioDecoder
dec' <- a -> IO (Ptr AudioDecoder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
dec
    Ptr Caps
maybeAllocationCaps <- case Maybe Caps
allocationCaps of
        Nothing -> Ptr Caps -> IO (Ptr Caps)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Caps
forall a. Ptr a
nullPtr
        Just jAllocationCaps :: Caps
jAllocationCaps -> do
            Ptr Caps
jAllocationCaps' <- Caps -> IO (Ptr Caps)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Caps
jAllocationCaps
            Ptr Caps -> IO (Ptr Caps)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Caps
jAllocationCaps'
    Ptr AudioDecoder -> Ptr Caps -> IO ()
gst_audio_decoder_set_allocation_caps Ptr AudioDecoder
dec' Ptr Caps
maybeAllocationCaps
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
dec
    Maybe Caps -> (Caps -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe Caps
allocationCaps Caps -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data AudioDecoderSetAllocationCapsMethodInfo
instance (signature ~ (Maybe (Gst.Caps.Caps) -> m ()), MonadIO m, IsAudioDecoder a) => O.MethodInfo AudioDecoderSetAllocationCapsMethodInfo a signature where
    overloadedMethod = audioDecoderSetAllocationCaps

#endif

-- method AudioDecoder::set_drainable
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "dec"
--           , argType =
--               TInterface Name { namespace = "GstAudio" , name = "AudioDecoder" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstAudioDecoder" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "enabled"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "new state" , 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_decoder_set_drainable" gst_audio_decoder_set_drainable :: 
    Ptr AudioDecoder ->                     -- dec : TInterface (Name {namespace = "GstAudio", name = "AudioDecoder"})
    CInt ->                                 -- enabled : TBasicType TBoolean
    IO ()

-- | Configures decoder drain handling.  If drainable, subclass might
-- be handed a NULL buffer to have it return any leftover decoded data.
-- Otherwise, it is not considered so capable and will only ever be passed
-- real data.
-- 
-- MT safe.
audioDecoderSetDrainable ::
    (B.CallStack.HasCallStack, MonadIO m, IsAudioDecoder a) =>
    a
    -- ^ /@dec@/: a t'GI.GstAudio.Objects.AudioDecoder.AudioDecoder'
    -> Bool
    -- ^ /@enabled@/: new state
    -> m ()
audioDecoderSetDrainable :: a -> Bool -> m ()
audioDecoderSetDrainable dec :: a
dec enabled :: Bool
enabled = 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 AudioDecoder
dec' <- a -> IO (Ptr AudioDecoder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
dec
    let enabled' :: CInt
enabled' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
enabled
    Ptr AudioDecoder -> CInt -> IO ()
gst_audio_decoder_set_drainable Ptr AudioDecoder
dec' CInt
enabled'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
dec
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data AudioDecoderSetDrainableMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsAudioDecoder a) => O.MethodInfo AudioDecoderSetDrainableMethodInfo a signature where
    overloadedMethod = audioDecoderSetDrainable

#endif

-- method AudioDecoder::set_estimate_rate
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "dec"
--           , argType =
--               TInterface Name { namespace = "GstAudio" , name = "AudioDecoder" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstAudioDecoder" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "enabled"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "whether to enable byte to time conversion"
--                 , 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_decoder_set_estimate_rate" gst_audio_decoder_set_estimate_rate :: 
    Ptr AudioDecoder ->                     -- dec : TInterface (Name {namespace = "GstAudio", name = "AudioDecoder"})
    CInt ->                                 -- enabled : TBasicType TBoolean
    IO ()

-- | Allows baseclass to perform byte to time estimated conversion.
audioDecoderSetEstimateRate ::
    (B.CallStack.HasCallStack, MonadIO m, IsAudioDecoder a) =>
    a
    -- ^ /@dec@/: a t'GI.GstAudio.Objects.AudioDecoder.AudioDecoder'
    -> Bool
    -- ^ /@enabled@/: whether to enable byte to time conversion
    -> m ()
audioDecoderSetEstimateRate :: a -> Bool -> m ()
audioDecoderSetEstimateRate dec :: a
dec enabled :: Bool
enabled = 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 AudioDecoder
dec' <- a -> IO (Ptr AudioDecoder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
dec
    let enabled' :: CInt
enabled' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
enabled
    Ptr AudioDecoder -> CInt -> IO ()
gst_audio_decoder_set_estimate_rate Ptr AudioDecoder
dec' CInt
enabled'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
dec
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data AudioDecoderSetEstimateRateMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsAudioDecoder a) => O.MethodInfo AudioDecoderSetEstimateRateMethodInfo a signature where
    overloadedMethod = audioDecoderSetEstimateRate

#endif

-- method AudioDecoder::set_latency
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "dec"
--           , argType =
--               TInterface Name { namespace = "GstAudio" , name = "AudioDecoder" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstAudioDecoder" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "min"
--           , argType = TBasicType TUInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "minimum latency" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "max"
--           , argType = TBasicType TUInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "maximum latency" , 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_decoder_set_latency" gst_audio_decoder_set_latency :: 
    Ptr AudioDecoder ->                     -- dec : TInterface (Name {namespace = "GstAudio", name = "AudioDecoder"})
    Word64 ->                               -- min : TBasicType TUInt64
    Word64 ->                               -- max : TBasicType TUInt64
    IO ()

-- | Sets decoder latency.
audioDecoderSetLatency ::
    (B.CallStack.HasCallStack, MonadIO m, IsAudioDecoder a) =>
    a
    -- ^ /@dec@/: a t'GI.GstAudio.Objects.AudioDecoder.AudioDecoder'
    -> Word64
    -- ^ /@min@/: minimum latency
    -> Word64
    -- ^ /@max@/: maximum latency
    -> m ()
audioDecoderSetLatency :: a -> Word64 -> Word64 -> m ()
audioDecoderSetLatency dec :: a
dec min :: Word64
min max :: Word64
max = 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 AudioDecoder
dec' <- a -> IO (Ptr AudioDecoder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
dec
    Ptr AudioDecoder -> Word64 -> Word64 -> IO ()
gst_audio_decoder_set_latency Ptr AudioDecoder
dec' Word64
min Word64
max
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
dec
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data AudioDecoderSetLatencyMethodInfo
instance (signature ~ (Word64 -> Word64 -> m ()), MonadIO m, IsAudioDecoder a) => O.MethodInfo AudioDecoderSetLatencyMethodInfo a signature where
    overloadedMethod = audioDecoderSetLatency

#endif

-- method AudioDecoder::set_max_errors
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "dec"
--           , argType =
--               TInterface Name { namespace = "GstAudio" , name = "AudioDecoder" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstAudioDecoder" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "num"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "max tolerated errors"
--                 , 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_decoder_set_max_errors" gst_audio_decoder_set_max_errors :: 
    Ptr AudioDecoder ->                     -- dec : TInterface (Name {namespace = "GstAudio", name = "AudioDecoder"})
    Int32 ->                                -- num : TBasicType TInt
    IO ()

-- | Sets numbers of tolerated decoder errors, where a tolerated one is then only
-- warned about, but more than tolerated will lead to fatal error. You can set
-- -1 for never returning fatal errors. Default is set to
-- GST_AUDIO_DECODER_MAX_ERRORS.
audioDecoderSetMaxErrors ::
    (B.CallStack.HasCallStack, MonadIO m, IsAudioDecoder a) =>
    a
    -- ^ /@dec@/: a t'GI.GstAudio.Objects.AudioDecoder.AudioDecoder'
    -> Int32
    -- ^ /@num@/: max tolerated errors
    -> m ()
audioDecoderSetMaxErrors :: a -> Int32 -> m ()
audioDecoderSetMaxErrors dec :: a
dec num :: Int32
num = 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 AudioDecoder
dec' <- a -> IO (Ptr AudioDecoder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
dec
    Ptr AudioDecoder -> Int32 -> IO ()
gst_audio_decoder_set_max_errors Ptr AudioDecoder
dec' Int32
num
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
dec
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data AudioDecoderSetMaxErrorsMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsAudioDecoder a) => O.MethodInfo AudioDecoderSetMaxErrorsMethodInfo a signature where
    overloadedMethod = audioDecoderSetMaxErrors

#endif

-- method AudioDecoder::set_min_latency
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "dec"
--           , argType =
--               TInterface Name { namespace = "GstAudio" , name = "AudioDecoder" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstAudioDecoder" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "num"
--           , argType = TBasicType TUInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "new minimum latency"
--                 , 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_decoder_set_min_latency" gst_audio_decoder_set_min_latency :: 
    Ptr AudioDecoder ->                     -- dec : TInterface (Name {namespace = "GstAudio", name = "AudioDecoder"})
    Word64 ->                               -- num : TBasicType TUInt64
    IO ()

-- | Sets decoder minimum aggregation latency.
-- 
-- MT safe.
audioDecoderSetMinLatency ::
    (B.CallStack.HasCallStack, MonadIO m, IsAudioDecoder a) =>
    a
    -- ^ /@dec@/: a t'GI.GstAudio.Objects.AudioDecoder.AudioDecoder'
    -> Word64
    -- ^ /@num@/: new minimum latency
    -> m ()
audioDecoderSetMinLatency :: a -> Word64 -> m ()
audioDecoderSetMinLatency dec :: a
dec num :: Word64
num = 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 AudioDecoder
dec' <- a -> IO (Ptr AudioDecoder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
dec
    Ptr AudioDecoder -> Word64 -> IO ()
gst_audio_decoder_set_min_latency Ptr AudioDecoder
dec' Word64
num
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
dec
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data AudioDecoderSetMinLatencyMethodInfo
instance (signature ~ (Word64 -> m ()), MonadIO m, IsAudioDecoder a) => O.MethodInfo AudioDecoderSetMinLatencyMethodInfo a signature where
    overloadedMethod = audioDecoderSetMinLatency

#endif

-- method AudioDecoder::set_needs_format
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "dec"
--           , argType =
--               TInterface Name { namespace = "GstAudio" , name = "AudioDecoder" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstAudioDecoder" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "enabled"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "new state" , 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_decoder_set_needs_format" gst_audio_decoder_set_needs_format :: 
    Ptr AudioDecoder ->                     -- dec : TInterface (Name {namespace = "GstAudio", name = "AudioDecoder"})
    CInt ->                                 -- enabled : TBasicType TBoolean
    IO ()

-- | Configures decoder format needs.  If enabled, subclass needs to be
-- negotiated with format caps before it can process any data.  It will then
-- never be handed any data before it has been configured.
-- Otherwise, it might be handed data without having been configured and
-- is then expected being able to do so either by default
-- or based on the input data.
-- 
-- MT safe.
audioDecoderSetNeedsFormat ::
    (B.CallStack.HasCallStack, MonadIO m, IsAudioDecoder a) =>
    a
    -- ^ /@dec@/: a t'GI.GstAudio.Objects.AudioDecoder.AudioDecoder'
    -> Bool
    -- ^ /@enabled@/: new state
    -> m ()
audioDecoderSetNeedsFormat :: a -> Bool -> m ()
audioDecoderSetNeedsFormat dec :: a
dec enabled :: Bool
enabled = 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 AudioDecoder
dec' <- a -> IO (Ptr AudioDecoder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
dec
    let enabled' :: CInt
enabled' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
enabled
    Ptr AudioDecoder -> CInt -> IO ()
gst_audio_decoder_set_needs_format Ptr AudioDecoder
dec' CInt
enabled'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
dec
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data AudioDecoderSetNeedsFormatMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsAudioDecoder a) => O.MethodInfo AudioDecoderSetNeedsFormatMethodInfo a signature where
    overloadedMethod = audioDecoderSetNeedsFormat

#endif

-- method AudioDecoder::set_output_caps
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "dec"
--           , argType =
--               TInterface Name { namespace = "GstAudio" , name = "AudioDecoder" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstAudioDecoder" , 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 = Just "(fixed) #GstCaps" , 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_audio_decoder_set_output_caps" gst_audio_decoder_set_output_caps :: 
    Ptr AudioDecoder ->                     -- dec : TInterface (Name {namespace = "GstAudio", name = "AudioDecoder"})
    Ptr Gst.Caps.Caps ->                    -- caps : TInterface (Name {namespace = "Gst", name = "Caps"})
    IO CInt

-- | Configure output caps on the srcpad of /@dec@/. Similar to
-- 'GI.GstAudio.Objects.AudioDecoder.audioDecoderSetOutputFormat', but allows subclasses to specify
-- output caps that can\'t be expressed via t'GI.GstAudio.Structs.AudioInfo.AudioInfo' e.g. caps that have
-- caps features.
-- 
-- /Since: 1.16/
audioDecoderSetOutputCaps ::
    (B.CallStack.HasCallStack, MonadIO m, IsAudioDecoder a) =>
    a
    -- ^ /@dec@/: a t'GI.GstAudio.Objects.AudioDecoder.AudioDecoder'
    -> Gst.Caps.Caps
    -- ^ /@caps@/: (fixed) t'GI.Gst.Structs.Caps.Caps'
    -> m Bool
    -- ^ __Returns:__ 'P.True' on success.
audioDecoderSetOutputCaps :: a -> Caps -> m Bool
audioDecoderSetOutputCaps dec :: a
dec caps :: Caps
caps = 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 AudioDecoder
dec' <- a -> IO (Ptr AudioDecoder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
dec
    Ptr Caps
caps' <- Caps -> IO (Ptr Caps)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Caps
caps
    CInt
result <- Ptr AudioDecoder -> Ptr Caps -> IO CInt
gst_audio_decoder_set_output_caps Ptr AudioDecoder
dec' Ptr Caps
caps'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
dec
    Caps -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Caps
caps
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data AudioDecoderSetOutputCapsMethodInfo
instance (signature ~ (Gst.Caps.Caps -> m Bool), MonadIO m, IsAudioDecoder a) => O.MethodInfo AudioDecoderSetOutputCapsMethodInfo a signature where
    overloadedMethod = audioDecoderSetOutputCaps

#endif

-- method AudioDecoder::set_output_format
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "dec"
--           , argType =
--               TInterface Name { namespace = "GstAudio" , name = "AudioDecoder" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstAudioDecoder" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "GstAudio" , name = "AudioInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "#GstAudioInfo" , 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_audio_decoder_set_output_format" gst_audio_decoder_set_output_format :: 
    Ptr AudioDecoder ->                     -- dec : TInterface (Name {namespace = "GstAudio", name = "AudioDecoder"})
    Ptr GstAudio.AudioInfo.AudioInfo ->     -- info : TInterface (Name {namespace = "GstAudio", name = "AudioInfo"})
    IO CInt

-- | Configure output info on the srcpad of /@dec@/.
audioDecoderSetOutputFormat ::
    (B.CallStack.HasCallStack, MonadIO m, IsAudioDecoder a) =>
    a
    -- ^ /@dec@/: a t'GI.GstAudio.Objects.AudioDecoder.AudioDecoder'
    -> GstAudio.AudioInfo.AudioInfo
    -- ^ /@info@/: t'GI.GstAudio.Structs.AudioInfo.AudioInfo'
    -> m Bool
    -- ^ __Returns:__ 'P.True' on success.
audioDecoderSetOutputFormat :: a -> AudioInfo -> m Bool
audioDecoderSetOutputFormat dec :: a
dec info :: AudioInfo
info = 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 AudioDecoder
dec' <- a -> IO (Ptr AudioDecoder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
dec
    Ptr AudioInfo
info' <- AudioInfo -> IO (Ptr AudioInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr AudioInfo
info
    CInt
result <- Ptr AudioDecoder -> Ptr AudioInfo -> IO CInt
gst_audio_decoder_set_output_format Ptr AudioDecoder
dec' Ptr AudioInfo
info'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
dec
    AudioInfo -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AudioInfo
info
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data AudioDecoderSetOutputFormatMethodInfo
instance (signature ~ (GstAudio.AudioInfo.AudioInfo -> m Bool), MonadIO m, IsAudioDecoder a) => O.MethodInfo AudioDecoderSetOutputFormatMethodInfo a signature where
    overloadedMethod = audioDecoderSetOutputFormat

#endif

-- method AudioDecoder::set_plc
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "dec"
--           , argType =
--               TInterface Name { namespace = "GstAudio" , name = "AudioDecoder" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstAudioDecoder" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "enabled"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "new state" , 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_decoder_set_plc" gst_audio_decoder_set_plc :: 
    Ptr AudioDecoder ->                     -- dec : TInterface (Name {namespace = "GstAudio", name = "AudioDecoder"})
    CInt ->                                 -- enabled : TBasicType TBoolean
    IO ()

-- | Enable or disable decoder packet loss concealment, provided subclass
-- and codec are capable and allow handling plc.
-- 
-- MT safe.
audioDecoderSetPlc ::
    (B.CallStack.HasCallStack, MonadIO m, IsAudioDecoder a) =>
    a
    -- ^ /@dec@/: a t'GI.GstAudio.Objects.AudioDecoder.AudioDecoder'
    -> Bool
    -- ^ /@enabled@/: new state
    -> m ()
audioDecoderSetPlc :: a -> Bool -> m ()
audioDecoderSetPlc dec :: a
dec enabled :: Bool
enabled = 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 AudioDecoder
dec' <- a -> IO (Ptr AudioDecoder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
dec
    let enabled' :: CInt
enabled' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
enabled
    Ptr AudioDecoder -> CInt -> IO ()
gst_audio_decoder_set_plc Ptr AudioDecoder
dec' CInt
enabled'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
dec
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data AudioDecoderSetPlcMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsAudioDecoder a) => O.MethodInfo AudioDecoderSetPlcMethodInfo a signature where
    overloadedMethod = audioDecoderSetPlc

#endif

-- method AudioDecoder::set_plc_aware
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "dec"
--           , argType =
--               TInterface Name { namespace = "GstAudio" , name = "AudioDecoder" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstAudioDecoder" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "plc"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "new plc state" , 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_decoder_set_plc_aware" gst_audio_decoder_set_plc_aware :: 
    Ptr AudioDecoder ->                     -- dec : TInterface (Name {namespace = "GstAudio", name = "AudioDecoder"})
    CInt ->                                 -- plc : TBasicType TBoolean
    IO ()

-- | Indicates whether or not subclass handles packet loss concealment (plc).
audioDecoderSetPlcAware ::
    (B.CallStack.HasCallStack, MonadIO m, IsAudioDecoder a) =>
    a
    -- ^ /@dec@/: a t'GI.GstAudio.Objects.AudioDecoder.AudioDecoder'
    -> Bool
    -- ^ /@plc@/: new plc state
    -> m ()
audioDecoderSetPlcAware :: a -> Bool -> m ()
audioDecoderSetPlcAware dec :: a
dec plc :: Bool
plc = 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 AudioDecoder
dec' <- a -> IO (Ptr AudioDecoder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
dec
    let plc' :: CInt
plc' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
plc
    Ptr AudioDecoder -> CInt -> IO ()
gst_audio_decoder_set_plc_aware Ptr AudioDecoder
dec' CInt
plc'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
dec
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data AudioDecoderSetPlcAwareMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsAudioDecoder a) => O.MethodInfo AudioDecoderSetPlcAwareMethodInfo a signature where
    overloadedMethod = audioDecoderSetPlcAware

#endif

-- method AudioDecoder::set_tolerance
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "dec"
--           , argType =
--               TInterface Name { namespace = "GstAudio" , name = "AudioDecoder" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstAudioDecoder" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "tolerance"
--           , argType = TBasicType TUInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "new tolerance" , 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_decoder_set_tolerance" gst_audio_decoder_set_tolerance :: 
    Ptr AudioDecoder ->                     -- dec : TInterface (Name {namespace = "GstAudio", name = "AudioDecoder"})
    Word64 ->                               -- tolerance : TBasicType TUInt64
    IO ()

-- | Configures decoder audio jitter tolerance threshold.
-- 
-- MT safe.
audioDecoderSetTolerance ::
    (B.CallStack.HasCallStack, MonadIO m, IsAudioDecoder a) =>
    a
    -- ^ /@dec@/: a t'GI.GstAudio.Objects.AudioDecoder.AudioDecoder'
    -> Word64
    -- ^ /@tolerance@/: new tolerance
    -> m ()
audioDecoderSetTolerance :: a -> Word64 -> m ()
audioDecoderSetTolerance dec :: a
dec tolerance :: Word64
tolerance = 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 AudioDecoder
dec' <- a -> IO (Ptr AudioDecoder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
dec
    Ptr AudioDecoder -> Word64 -> IO ()
gst_audio_decoder_set_tolerance Ptr AudioDecoder
dec' Word64
tolerance
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
dec
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data AudioDecoderSetToleranceMethodInfo
instance (signature ~ (Word64 -> m ()), MonadIO m, IsAudioDecoder a) => O.MethodInfo AudioDecoderSetToleranceMethodInfo a signature where
    overloadedMethod = audioDecoderSetTolerance

#endif

-- method AudioDecoder::set_use_default_pad_acceptcaps
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "decoder"
--           , argType =
--               TInterface Name { namespace = "GstAudio" , name = "AudioDecoder" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstAudioDecoder" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "use"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "if the default pad accept-caps query handling should be used"
--                 , 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_decoder_set_use_default_pad_acceptcaps" gst_audio_decoder_set_use_default_pad_acceptcaps :: 
    Ptr AudioDecoder ->                     -- decoder : TInterface (Name {namespace = "GstAudio", name = "AudioDecoder"})
    CInt ->                                 -- use : TBasicType TBoolean
    IO ()

-- | Lets t'GI.GstAudio.Objects.AudioDecoder.AudioDecoder' sub-classes decide if they want the sink pad
-- to use the default pad query handler to reply to accept-caps queries.
-- 
-- By setting this to true it is possible to further customize the default
-- handler with @/GST_PAD_SET_ACCEPT_INTERSECT/@ and
-- @/GST_PAD_SET_ACCEPT_TEMPLATE/@
-- 
-- /Since: 1.6/
audioDecoderSetUseDefaultPadAcceptcaps ::
    (B.CallStack.HasCallStack, MonadIO m, IsAudioDecoder a) =>
    a
    -- ^ /@decoder@/: a t'GI.GstAudio.Objects.AudioDecoder.AudioDecoder'
    -> Bool
    -- ^ /@use@/: if the default pad accept-caps query handling should be used
    -> m ()
audioDecoderSetUseDefaultPadAcceptcaps :: a -> Bool -> m ()
audioDecoderSetUseDefaultPadAcceptcaps decoder :: a
decoder use :: Bool
use = 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 AudioDecoder
decoder' <- a -> IO (Ptr AudioDecoder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
decoder
    let use' :: CInt
use' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
use
    Ptr AudioDecoder -> CInt -> IO ()
gst_audio_decoder_set_use_default_pad_acceptcaps Ptr AudioDecoder
decoder' CInt
use'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
decoder
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data AudioDecoderSetUseDefaultPadAcceptcapsMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsAudioDecoder a) => O.MethodInfo AudioDecoderSetUseDefaultPadAcceptcapsMethodInfo a signature where
    overloadedMethod = audioDecoderSetUseDefaultPadAcceptcaps

#endif