-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria

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

module GI.GstAudio.Callbacks
    ( 

 -- * Signals
-- ** AudioBaseSinkCustomSlavingCallback #signal:AudioBaseSinkCustomSlavingCallback#

    AudioBaseSinkCustomSlavingCallback      ,
    AudioBaseSinkCustomSlavingCallback_WithClosures,
    C_AudioBaseSinkCustomSlavingCallback    ,
    drop_closures_AudioBaseSinkCustomSlavingCallback,
    dynamic_AudioBaseSinkCustomSlavingCallback,
    genClosure_AudioBaseSinkCustomSlavingCallback,
    mk_AudioBaseSinkCustomSlavingCallback   ,
    noAudioBaseSinkCustomSlavingCallback    ,
    noAudioBaseSinkCustomSlavingCallback_WithClosures,
    wrap_AudioBaseSinkCustomSlavingCallback ,


-- ** AudioClockGetTimeFunc #signal:AudioClockGetTimeFunc#

    AudioClockGetTimeFunc                   ,
    AudioClockGetTimeFunc_WithClosures      ,
    C_AudioClockGetTimeFunc                 ,
    drop_closures_AudioClockGetTimeFunc     ,
    dynamic_AudioClockGetTimeFunc           ,
    genClosure_AudioClockGetTimeFunc        ,
    mk_AudioClockGetTimeFunc                ,
    noAudioClockGetTimeFunc                 ,
    noAudioClockGetTimeFunc_WithClosures    ,
    wrap_AudioClockGetTimeFunc              ,


-- ** AudioFormatPack #signal:AudioFormatPack#

    AudioFormatPack                         ,
    C_AudioFormatPack                       ,
    dynamic_AudioFormatPack                 ,
    genClosure_AudioFormatPack              ,
    mk_AudioFormatPack                      ,
    noAudioFormatPack                       ,
    wrap_AudioFormatPack                    ,


-- ** AudioFormatUnpack #signal:AudioFormatUnpack#

    AudioFormatUnpack                       ,
    C_AudioFormatUnpack                     ,
    dynamic_AudioFormatUnpack               ,
    genClosure_AudioFormatUnpack            ,
    mk_AudioFormatUnpack                    ,
    noAudioFormatUnpack                     ,
    wrap_AudioFormatUnpack                  ,


-- ** AudioRingBufferCallback #signal:AudioRingBufferCallback#

    AudioRingBufferCallback                 ,
    AudioRingBufferCallback_WithClosures    ,
    C_AudioRingBufferCallback               ,
    drop_closures_AudioRingBufferCallback   ,
    dynamic_AudioRingBufferCallback         ,
    genClosure_AudioRingBufferCallback      ,
    mk_AudioRingBufferCallback              ,
    noAudioRingBufferCallback               ,
    noAudioRingBufferCallback_WithClosures  ,
    wrap_AudioRingBufferCallback            ,




    ) 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.Gst.Objects.Clock as Gst.Clock
import {-# SOURCE #-} qualified GI.GstAudio.Enums as GstAudio.Enums
import {-# SOURCE #-} qualified GI.GstAudio.Flags as GstAudio.Flags
import {-# SOURCE #-} qualified GI.GstAudio.Objects.AudioBaseSink as GstAudio.AudioBaseSink
import {-# SOURCE #-} qualified GI.GstAudio.Objects.AudioRingBuffer as GstAudio.AudioRingBuffer
import {-# SOURCE #-} qualified GI.GstAudio.Structs.AudioFormatInfo as GstAudio.AudioFormatInfo

-- callback AudioRingBufferCallback
--          -> Callable {returnType = Nothing, returnMayBeNull = False, returnTransfer = TransferNothing, returnDocumentation = Documentation {rawDocText = Nothing, sinceVersion = Nothing}, args = [Arg {argCName = "rbuf", argType = TInterface (Name {namespace = "GstAudio", name = "AudioRingBuffer"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstAudioRingBuffer", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "data", argType = TCArray False (-1) 2 (TBasicType TUInt8), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "target to fill", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "len", argType = TBasicType TUInt, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "amount to fill", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "user_data", argType = TBasicType TPtr, direction = DirectionIn, mayBeNull = True, argDoc = Documentation {rawDocText = Just "user data", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = 3, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}], skipReturn = False, callableThrows = False, callableDeprecated = Nothing, callableDocumentation = Documentation {rawDocText = Just "This function is set with gst_audio_ring_buffer_set_callback() and is\ncalled to fill the memory at @data with @len bytes of samples.", sinceVersion = Nothing}}
-- | Type for the callback on the (unwrapped) C side.
type C_AudioRingBufferCallback =
    Ptr GstAudio.AudioRingBuffer.AudioRingBuffer ->
    Ptr Word8 ->
    Word32 ->
    Ptr () ->
    IO ()

-- Args: [ Arg
--           { argCName = "rbuf"
--           , argType =
--               TInterface
--                 Name { namespace = "GstAudio" , name = "AudioRingBuffer" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstAudioRingBuffer"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "data"
--           , argType = TCArray False (-1) 2 (TBasicType TUInt8)
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "target to fill" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "len"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "amount to fill" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "user data" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = 3
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "len"
--              , argType = TBasicType TUInt
--              , direction = DirectionIn
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText = Just "amount to fill" , sinceVersion = Nothing }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferNothing
--              }
--          ]
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "dynamic" __dynamic_C_AudioRingBufferCallback :: FunPtr C_AudioRingBufferCallback -> C_AudioRingBufferCallback

-- | Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
dynamic_AudioRingBufferCallback ::
    (B.CallStack.HasCallStack, MonadIO m, GstAudio.AudioRingBuffer.IsAudioRingBuffer a) =>
    FunPtr C_AudioRingBufferCallback
    -> a
    -- ^ /@rbuf@/: a t'GI.GstAudio.Objects.AudioRingBuffer.AudioRingBuffer'
    -> ByteString
    -- ^ /@data@/: target to fill
    -> Ptr ()
    -- ^ /@userData@/: user data
    -> m ()
dynamic_AudioRingBufferCallback :: FunPtr C_AudioRingBufferCallback
-> a -> ByteString -> Ptr () -> m ()
dynamic_AudioRingBufferCallback __funPtr :: FunPtr C_AudioRingBufferCallback
__funPtr rbuf :: a
rbuf data_ :: ByteString
data_ userData :: Ptr ()
userData = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    let len :: Word32
len = Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word32) -> Int -> Word32
forall a b. (a -> b) -> a -> b
$ ByteString -> Int
B.length ByteString
data_
    Ptr AudioRingBuffer
rbuf' <- a -> IO (Ptr AudioRingBuffer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
rbuf
    Ptr Word8
data_' <- ByteString -> IO (Ptr Word8)
packByteString ByteString
data_
    (FunPtr C_AudioRingBufferCallback -> C_AudioRingBufferCallback
__dynamic_C_AudioRingBufferCallback FunPtr C_AudioRingBufferCallback
__funPtr) Ptr AudioRingBuffer
rbuf' Ptr Word8
data_' Word32
len Ptr ()
userData
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
rbuf
    Ptr Word8 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word8
data_'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

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

-- | This function is set with @/gst_audio_ring_buffer_set_callback()/@ and is
-- called to fill the memory at /@data@/ with /@len@/ bytes of samples.
type AudioRingBufferCallback =
    GstAudio.AudioRingBuffer.AudioRingBuffer
    -- ^ /@rbuf@/: a t'GI.GstAudio.Objects.AudioRingBuffer.AudioRingBuffer'
    -> ByteString
    -- ^ /@data@/: target to fill
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `AudioRingBufferCallback`@.
noAudioRingBufferCallback :: Maybe AudioRingBufferCallback
noAudioRingBufferCallback :: Maybe AudioRingBufferCallback
noAudioRingBufferCallback = Maybe AudioRingBufferCallback
forall a. Maybe a
Nothing

-- | This function is set with @/gst_audio_ring_buffer_set_callback()/@ and is
-- called to fill the memory at /@data@/ with /@len@/ bytes of samples.
type AudioRingBufferCallback_WithClosures =
    GstAudio.AudioRingBuffer.AudioRingBuffer
    -- ^ /@rbuf@/: a t'GI.GstAudio.Objects.AudioRingBuffer.AudioRingBuffer'
    -> ByteString
    -- ^ /@data@/: target to fill
    -> Ptr ()
    -- ^ /@userData@/: user data
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `AudioRingBufferCallback_WithClosures`@.
noAudioRingBufferCallback_WithClosures :: Maybe AudioRingBufferCallback_WithClosures
noAudioRingBufferCallback_WithClosures :: Maybe AudioRingBufferCallback_WithClosures
noAudioRingBufferCallback_WithClosures = Maybe AudioRingBufferCallback_WithClosures
forall a. Maybe a
Nothing

-- | A simple wrapper that ignores the closure arguments.
drop_closures_AudioRingBufferCallback :: AudioRingBufferCallback -> AudioRingBufferCallback_WithClosures
drop_closures_AudioRingBufferCallback :: AudioRingBufferCallback -> AudioRingBufferCallback_WithClosures
drop_closures_AudioRingBufferCallback _f :: AudioRingBufferCallback
_f rbuf :: AudioRingBuffer
rbuf data_ :: ByteString
data_ _ = AudioRingBufferCallback
_f AudioRingBuffer
rbuf ByteString
data_

-- | Wrap the callback into a `GClosure`.
genClosure_AudioRingBufferCallback :: MonadIO m => AudioRingBufferCallback -> m (GClosure C_AudioRingBufferCallback)
genClosure_AudioRingBufferCallback :: AudioRingBufferCallback -> m (GClosure C_AudioRingBufferCallback)
genClosure_AudioRingBufferCallback cb :: AudioRingBufferCallback
cb = IO (GClosure C_AudioRingBufferCallback)
-> m (GClosure C_AudioRingBufferCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_AudioRingBufferCallback)
 -> m (GClosure C_AudioRingBufferCallback))
-> IO (GClosure C_AudioRingBufferCallback)
-> m (GClosure C_AudioRingBufferCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: AudioRingBufferCallback_WithClosures
cb' = AudioRingBufferCallback -> AudioRingBufferCallback_WithClosures
drop_closures_AudioRingBufferCallback AudioRingBufferCallback
cb
    let cb'' :: C_AudioRingBufferCallback
cb'' = Maybe (Ptr (FunPtr C_AudioRingBufferCallback))
-> AudioRingBufferCallback_WithClosures
-> C_AudioRingBufferCallback
wrap_AudioRingBufferCallback Maybe (Ptr (FunPtr C_AudioRingBufferCallback))
forall a. Maybe a
Nothing AudioRingBufferCallback_WithClosures
cb'
    C_AudioRingBufferCallback -> IO (FunPtr C_AudioRingBufferCallback)
mk_AudioRingBufferCallback C_AudioRingBufferCallback
cb'' IO (FunPtr C_AudioRingBufferCallback)
-> (FunPtr C_AudioRingBufferCallback
    -> IO (GClosure C_AudioRingBufferCallback))
-> IO (GClosure C_AudioRingBufferCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_AudioRingBufferCallback
-> IO (GClosure C_AudioRingBufferCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `AudioRingBufferCallback` into a `C_AudioRingBufferCallback`.
wrap_AudioRingBufferCallback ::
    Maybe (Ptr (FunPtr C_AudioRingBufferCallback)) ->
    AudioRingBufferCallback_WithClosures ->
    C_AudioRingBufferCallback
wrap_AudioRingBufferCallback :: Maybe (Ptr (FunPtr C_AudioRingBufferCallback))
-> AudioRingBufferCallback_WithClosures
-> C_AudioRingBufferCallback
wrap_AudioRingBufferCallback funptrptr :: Maybe (Ptr (FunPtr C_AudioRingBufferCallback))
funptrptr _cb :: AudioRingBufferCallback_WithClosures
_cb rbuf :: Ptr AudioRingBuffer
rbuf data_ :: Ptr Word8
data_ len :: Word32
len userData :: Ptr ()
userData = do
    AudioRingBuffer
rbuf' <- ((ManagedPtr AudioRingBuffer -> AudioRingBuffer)
-> Ptr AudioRingBuffer -> IO AudioRingBuffer
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr AudioRingBuffer -> AudioRingBuffer
GstAudio.AudioRingBuffer.AudioRingBuffer) Ptr AudioRingBuffer
rbuf
    ByteString
data_' <- (Word32 -> Ptr Word8 -> IO ByteString
forall a. Integral a => a -> Ptr Word8 -> IO ByteString
unpackByteStringWithLength Word32
len) Ptr Word8
data_
    AudioRingBufferCallback_WithClosures
_cb  AudioRingBuffer
rbuf' ByteString
data_' Ptr ()
userData
    Maybe (Ptr (FunPtr C_AudioRingBufferCallback)) -> IO ()
forall a. Maybe (Ptr (FunPtr a)) -> IO ()
maybeReleaseFunPtr Maybe (Ptr (FunPtr C_AudioRingBufferCallback))
funptrptr


-- callback AudioFormatUnpack
--          -> Callable {returnType = Nothing, returnMayBeNull = False, returnTransfer = TransferNothing, returnDocumentation = Documentation {rawDocText = Nothing, sinceVersion = Nothing}, args = [Arg {argCName = "info", argType = TInterface (Name {namespace = "GstAudio", name = "AudioFormatInfo"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstAudioFormatInfo", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "flags", argType = TInterface (Name {namespace = "GstAudio", name = "AudioPackFlags"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "#GstAudioPackFlags", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "dest", argType = TCArray False (-1) (-1) (TBasicType TUInt8), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a destination array", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "data", argType = TCArray False (-1) (-1) (TBasicType TUInt8), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "pointer to the audio data", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "length", argType = TBasicType TInt, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "the amount of samples to unpack.", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}], skipReturn = False, callableThrows = False, callableDeprecated = Nothing, callableDocumentation = Documentation {rawDocText = Just "Unpacks @length samples from the given data of format @info.\nThe samples will be unpacked into @dest which each channel\ninterleaved. @dest should at least be big enough to hold @length *\nchannels * size(unpack_format) bytes.", sinceVersion = Nothing}}
-- | Type for the callback on the (unwrapped) C side.
type C_AudioFormatUnpack =
    Ptr GstAudio.AudioFormatInfo.AudioFormatInfo ->
    CUInt ->
    Ptr Word8 ->
    Ptr Word8 ->
    Int32 ->
    IO ()

-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface
--                 Name { namespace = "GstAudio" , name = "AudioFormatInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstAudioFormatInfo"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface
--                 Name { namespace = "GstAudio" , name = "AudioPackFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "#GstAudioPackFlags" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "dest"
--           , argType = TCArray False (-1) (-1) (TBasicType TUInt8)
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a destination array"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "data"
--           , argType = TCArray False (-1) (-1) (TBasicType TUInt8)
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "pointer to the audio data"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "length"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the amount of samples to unpack."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "dynamic" __dynamic_C_AudioFormatUnpack :: FunPtr C_AudioFormatUnpack -> C_AudioFormatUnpack

-- | Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
dynamic_AudioFormatUnpack ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    FunPtr C_AudioFormatUnpack
    -> GstAudio.AudioFormatInfo.AudioFormatInfo
    -- ^ /@info@/: a t'GI.GstAudio.Structs.AudioFormatInfo.AudioFormatInfo'
    -> [GstAudio.Flags.AudioPackFlags]
    -- ^ /@flags@/: t'GI.GstAudio.Flags.AudioPackFlags'
    -> Ptr Word8
    -- ^ /@dest@/: a destination array
    -> Ptr Word8
    -- ^ /@data@/: pointer to the audio data
    -> Int32
    -- ^ /@length@/: the amount of samples to unpack.
    -> m ()
dynamic_AudioFormatUnpack :: FunPtr C_AudioFormatUnpack
-> AudioFormatInfo
-> [AudioPackFlags]
-> Ptr Word8
-> Ptr Word8
-> Int32
-> m ()
dynamic_AudioFormatUnpack __funPtr :: FunPtr C_AudioFormatUnpack
__funPtr info :: AudioFormatInfo
info flags :: [AudioPackFlags]
flags dest :: Ptr Word8
dest data_ :: Ptr Word8
data_ length_ :: Int32
length_ = 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 AudioFormatInfo
info' <- AudioFormatInfo -> IO (Ptr AudioFormatInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr AudioFormatInfo
info
    let flags' :: CUInt
flags' = [AudioPackFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [AudioPackFlags]
flags
    (FunPtr C_AudioFormatUnpack -> C_AudioFormatUnpack
__dynamic_C_AudioFormatUnpack FunPtr C_AudioFormatUnpack
__funPtr) Ptr AudioFormatInfo
info' CUInt
flags' Ptr Word8
dest Ptr Word8
data_ Int32
length_
    AudioFormatInfo -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AudioFormatInfo
info
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

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

-- | Unpacks /@length@/ samples from the given data of format /@info@/.
-- The samples will be unpacked into /@dest@/ which each channel
-- interleaved. /@dest@/ should at least be big enough to hold /@length@/ *
-- channels * size(unpack_format) bytes.
type AudioFormatUnpack =
    GstAudio.AudioFormatInfo.AudioFormatInfo
    -- ^ /@info@/: a t'GI.GstAudio.Structs.AudioFormatInfo.AudioFormatInfo'
    -> [GstAudio.Flags.AudioPackFlags]
    -- ^ /@flags@/: t'GI.GstAudio.Flags.AudioPackFlags'
    -> Ptr Word8
    -- ^ /@dest@/: a destination array
    -> Ptr Word8
    -- ^ /@data@/: pointer to the audio data
    -> Int32
    -- ^ /@length@/: the amount of samples to unpack.
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `AudioFormatUnpack`@.
noAudioFormatUnpack :: Maybe AudioFormatUnpack
noAudioFormatUnpack :: Maybe AudioFormatUnpack
noAudioFormatUnpack = Maybe AudioFormatUnpack
forall a. Maybe a
Nothing

-- | Wrap the callback into a `GClosure`.
genClosure_AudioFormatUnpack :: MonadIO m => AudioFormatUnpack -> m (GClosure C_AudioFormatUnpack)
genClosure_AudioFormatUnpack :: AudioFormatUnpack -> m (GClosure C_AudioFormatUnpack)
genClosure_AudioFormatUnpack cb :: AudioFormatUnpack
cb = IO (GClosure C_AudioFormatUnpack)
-> m (GClosure C_AudioFormatUnpack)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_AudioFormatUnpack)
 -> m (GClosure C_AudioFormatUnpack))
-> IO (GClosure C_AudioFormatUnpack)
-> m (GClosure C_AudioFormatUnpack)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_AudioFormatUnpack
cb' = Maybe (Ptr (FunPtr C_AudioFormatUnpack))
-> AudioFormatUnpack -> C_AudioFormatUnpack
wrap_AudioFormatUnpack Maybe (Ptr (FunPtr C_AudioFormatUnpack))
forall a. Maybe a
Nothing AudioFormatUnpack
cb
    C_AudioFormatUnpack -> IO (FunPtr C_AudioFormatUnpack)
mk_AudioFormatUnpack C_AudioFormatUnpack
cb' IO (FunPtr C_AudioFormatUnpack)
-> (FunPtr C_AudioFormatUnpack
    -> IO (GClosure C_AudioFormatUnpack))
-> IO (GClosure C_AudioFormatUnpack)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_AudioFormatUnpack -> IO (GClosure C_AudioFormatUnpack)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `AudioFormatUnpack` into a `C_AudioFormatUnpack`.
wrap_AudioFormatUnpack ::
    Maybe (Ptr (FunPtr C_AudioFormatUnpack)) ->
    AudioFormatUnpack ->
    C_AudioFormatUnpack
wrap_AudioFormatUnpack :: Maybe (Ptr (FunPtr C_AudioFormatUnpack))
-> AudioFormatUnpack -> C_AudioFormatUnpack
wrap_AudioFormatUnpack funptrptr :: Maybe (Ptr (FunPtr C_AudioFormatUnpack))
funptrptr _cb :: AudioFormatUnpack
_cb info :: Ptr AudioFormatInfo
info flags :: CUInt
flags dest :: Ptr Word8
dest data_ :: Ptr Word8
data_ length_ :: Int32
length_ = do
    AudioFormatInfo
info' <- ((ManagedPtr AudioFormatInfo -> AudioFormatInfo)
-> Ptr AudioFormatInfo -> IO AudioFormatInfo
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr AudioFormatInfo -> AudioFormatInfo
GstAudio.AudioFormatInfo.AudioFormatInfo) Ptr AudioFormatInfo
info
    let flags' :: [AudioPackFlags]
flags' = CUInt -> [AudioPackFlags]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
flags
    AudioFormatUnpack
_cb  AudioFormatInfo
info' [AudioPackFlags]
flags' Ptr Word8
dest Ptr Word8
data_ Int32
length_
    Maybe (Ptr (FunPtr C_AudioFormatUnpack)) -> IO ()
forall a. Maybe (Ptr (FunPtr a)) -> IO ()
maybeReleaseFunPtr Maybe (Ptr (FunPtr C_AudioFormatUnpack))
funptrptr


-- callback AudioFormatPack
--          -> Callable {returnType = Nothing, returnMayBeNull = False, returnTransfer = TransferNothing, returnDocumentation = Documentation {rawDocText = Nothing, sinceVersion = Nothing}, args = [Arg {argCName = "info", argType = TInterface (Name {namespace = "GstAudio", name = "AudioFormatInfo"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstAudioFormatInfo", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "flags", argType = TInterface (Name {namespace = "GstAudio", name = "AudioPackFlags"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "#GstAudioPackFlags", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "src", argType = TCArray False (-1) (-1) (TBasicType TUInt8), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a source array", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "data", argType = TCArray False (-1) (-1) (TBasicType TUInt8), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "pointer to the destination\n  data", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "length", argType = TBasicType TInt, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "the amount of samples to pack.", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}], skipReturn = False, callableThrows = False, callableDeprecated = Nothing, callableDocumentation = Documentation {rawDocText = Just "Packs @length samples from @src to the data array in format @info.\nThe samples from source have each channel interleaved\nand will be packed into @data.", sinceVersion = Nothing}}
-- | Type for the callback on the (unwrapped) C side.
type C_AudioFormatPack =
    Ptr GstAudio.AudioFormatInfo.AudioFormatInfo ->
    CUInt ->
    Ptr Word8 ->
    Ptr Word8 ->
    Int32 ->
    IO ()

-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface
--                 Name { namespace = "GstAudio" , name = "AudioFormatInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstAudioFormatInfo"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface
--                 Name { namespace = "GstAudio" , name = "AudioPackFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "#GstAudioPackFlags" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "src"
--           , argType = TCArray False (-1) (-1) (TBasicType TUInt8)
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a source array" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "data"
--           , argType = TCArray False (-1) (-1) (TBasicType TUInt8)
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "pointer to the destination\n  data"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "length"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the amount of samples to pack."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "dynamic" __dynamic_C_AudioFormatPack :: FunPtr C_AudioFormatPack -> C_AudioFormatPack

-- | Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
dynamic_AudioFormatPack ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    FunPtr C_AudioFormatPack
    -> GstAudio.AudioFormatInfo.AudioFormatInfo
    -- ^ /@info@/: a t'GI.GstAudio.Structs.AudioFormatInfo.AudioFormatInfo'
    -> [GstAudio.Flags.AudioPackFlags]
    -- ^ /@flags@/: t'GI.GstAudio.Flags.AudioPackFlags'
    -> Ptr Word8
    -- ^ /@src@/: a source array
    -> Ptr Word8
    -- ^ /@data@/: pointer to the destination
    --   data
    -> Int32
    -- ^ /@length@/: the amount of samples to pack.
    -> m ()
dynamic_AudioFormatPack :: FunPtr C_AudioFormatUnpack
-> AudioFormatInfo
-> [AudioPackFlags]
-> Ptr Word8
-> Ptr Word8
-> Int32
-> m ()
dynamic_AudioFormatPack __funPtr :: FunPtr C_AudioFormatUnpack
__funPtr info :: AudioFormatInfo
info flags :: [AudioPackFlags]
flags src :: Ptr Word8
src data_ :: Ptr Word8
data_ length_ :: Int32
length_ = 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 AudioFormatInfo
info' <- AudioFormatInfo -> IO (Ptr AudioFormatInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr AudioFormatInfo
info
    let flags' :: CUInt
flags' = [AudioPackFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [AudioPackFlags]
flags
    (FunPtr C_AudioFormatUnpack -> C_AudioFormatUnpack
__dynamic_C_AudioFormatPack FunPtr C_AudioFormatUnpack
__funPtr) Ptr AudioFormatInfo
info' CUInt
flags' Ptr Word8
src Ptr Word8
data_ Int32
length_
    AudioFormatInfo -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AudioFormatInfo
info
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

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

-- | Packs /@length@/ samples from /@src@/ to the data array in format /@info@/.
-- The samples from source have each channel interleaved
-- and will be packed into /@data@/.
type AudioFormatPack =
    GstAudio.AudioFormatInfo.AudioFormatInfo
    -- ^ /@info@/: a t'GI.GstAudio.Structs.AudioFormatInfo.AudioFormatInfo'
    -> [GstAudio.Flags.AudioPackFlags]
    -- ^ /@flags@/: t'GI.GstAudio.Flags.AudioPackFlags'
    -> Ptr Word8
    -- ^ /@src@/: a source array
    -> Ptr Word8
    -- ^ /@data@/: pointer to the destination
    --   data
    -> Int32
    -- ^ /@length@/: the amount of samples to pack.
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `AudioFormatPack`@.
noAudioFormatPack :: Maybe AudioFormatPack
noAudioFormatPack :: Maybe AudioFormatUnpack
noAudioFormatPack = Maybe AudioFormatUnpack
forall a. Maybe a
Nothing

-- | Wrap the callback into a `GClosure`.
genClosure_AudioFormatPack :: MonadIO m => AudioFormatPack -> m (GClosure C_AudioFormatPack)
genClosure_AudioFormatPack :: AudioFormatUnpack -> m (GClosure C_AudioFormatUnpack)
genClosure_AudioFormatPack cb :: AudioFormatUnpack
cb = IO (GClosure C_AudioFormatUnpack)
-> m (GClosure C_AudioFormatUnpack)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_AudioFormatUnpack)
 -> m (GClosure C_AudioFormatUnpack))
-> IO (GClosure C_AudioFormatUnpack)
-> m (GClosure C_AudioFormatUnpack)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_AudioFormatUnpack
cb' = Maybe (Ptr (FunPtr C_AudioFormatUnpack))
-> AudioFormatUnpack -> C_AudioFormatUnpack
wrap_AudioFormatPack Maybe (Ptr (FunPtr C_AudioFormatUnpack))
forall a. Maybe a
Nothing AudioFormatUnpack
cb
    C_AudioFormatUnpack -> IO (FunPtr C_AudioFormatUnpack)
mk_AudioFormatPack C_AudioFormatUnpack
cb' IO (FunPtr C_AudioFormatUnpack)
-> (FunPtr C_AudioFormatUnpack
    -> IO (GClosure C_AudioFormatUnpack))
-> IO (GClosure C_AudioFormatUnpack)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_AudioFormatUnpack -> IO (GClosure C_AudioFormatUnpack)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `AudioFormatPack` into a `C_AudioFormatPack`.
wrap_AudioFormatPack ::
    Maybe (Ptr (FunPtr C_AudioFormatPack)) ->
    AudioFormatPack ->
    C_AudioFormatPack
wrap_AudioFormatPack :: Maybe (Ptr (FunPtr C_AudioFormatUnpack))
-> AudioFormatUnpack -> C_AudioFormatUnpack
wrap_AudioFormatPack funptrptr :: Maybe (Ptr (FunPtr C_AudioFormatUnpack))
funptrptr _cb :: AudioFormatUnpack
_cb info :: Ptr AudioFormatInfo
info flags :: CUInt
flags src :: Ptr Word8
src data_ :: Ptr Word8
data_ length_ :: Int32
length_ = do
    AudioFormatInfo
info' <- ((ManagedPtr AudioFormatInfo -> AudioFormatInfo)
-> Ptr AudioFormatInfo -> IO AudioFormatInfo
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr AudioFormatInfo -> AudioFormatInfo
GstAudio.AudioFormatInfo.AudioFormatInfo) Ptr AudioFormatInfo
info
    let flags' :: [AudioPackFlags]
flags' = CUInt -> [AudioPackFlags]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
flags
    AudioFormatUnpack
_cb  AudioFormatInfo
info' [AudioPackFlags]
flags' Ptr Word8
src Ptr Word8
data_ Int32
length_
    Maybe (Ptr (FunPtr C_AudioFormatUnpack)) -> IO ()
forall a. Maybe (Ptr (FunPtr a)) -> IO ()
maybeReleaseFunPtr Maybe (Ptr (FunPtr C_AudioFormatUnpack))
funptrptr


-- callback AudioClockGetTimeFunc
--          -> Callable {returnType = Just (TBasicType TUInt64), returnMayBeNull = False, returnTransfer = TransferNothing, returnDocumentation = Documentation {rawDocText = Just "the current time or #GST_CLOCK_TIME_NONE if the previous time should\nbe used.", sinceVersion = Nothing}, args = [Arg {argCName = "clock", argType = TInterface (Name {namespace = "Gst", name = "Clock"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "the #GstAudioClock", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "user_data", argType = TBasicType TPtr, direction = DirectionIn, mayBeNull = True, argDoc = Documentation {rawDocText = Just "user data", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = 1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}], skipReturn = False, callableThrows = False, callableDeprecated = Nothing, callableDocumentation = Documentation {rawDocText = Just "This function will be called whenever the current clock time needs to be\ncalculated. If this function returns #GST_CLOCK_TIME_NONE, the last reported\ntime will be returned by the clock.", sinceVersion = Nothing}}
-- | Type for the callback on the (unwrapped) C side.
type C_AudioClockGetTimeFunc =
    Ptr Gst.Clock.Clock ->
    Ptr () ->
    IO Word64

-- Args: [ Arg
--           { argCName = "clock"
--           , argType = TInterface Name { namespace = "Gst" , name = "Clock" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #GstAudioClock" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "user data" , 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 "dynamic" __dynamic_C_AudioClockGetTimeFunc :: FunPtr C_AudioClockGetTimeFunc -> C_AudioClockGetTimeFunc

-- | Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
dynamic_AudioClockGetTimeFunc ::
    (B.CallStack.HasCallStack, MonadIO m, Gst.Clock.IsClock a) =>
    FunPtr C_AudioClockGetTimeFunc
    -> a
    -- ^ /@clock@/: the t'GI.GstAudio.Objects.AudioClock.AudioClock'
    -> Ptr ()
    -- ^ /@userData@/: user data
    -> m Word64
    -- ^ __Returns:__ the current time or 'GI.Gst.Constants.CLOCK_TIME_NONE' if the previous time should
    -- be used.
dynamic_AudioClockGetTimeFunc :: FunPtr C_AudioClockGetTimeFunc -> a -> Ptr () -> m Word64
dynamic_AudioClockGetTimeFunc __funPtr :: FunPtr C_AudioClockGetTimeFunc
__funPtr clock :: a
clock userData :: Ptr ()
userData = 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 Clock
clock' <- a -> IO (Ptr Clock)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
clock
    Word64
result <- (FunPtr C_AudioClockGetTimeFunc -> C_AudioClockGetTimeFunc
__dynamic_C_AudioClockGetTimeFunc FunPtr C_AudioClockGetTimeFunc
__funPtr) Ptr Clock
clock' Ptr ()
userData
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
clock
    Word64 -> IO Word64
forall (m :: * -> *) a. Monad m => a -> m a
return Word64
result

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

-- | This function will be called whenever the current clock time needs to be
-- calculated. If this function returns 'GI.Gst.Constants.CLOCK_TIME_NONE', the last reported
-- time will be returned by the clock.
type AudioClockGetTimeFunc =
    Gst.Clock.Clock
    -- ^ /@clock@/: the t'GI.GstAudio.Objects.AudioClock.AudioClock'
    -> IO Word64
    -- ^ __Returns:__ the current time or 'GI.Gst.Constants.CLOCK_TIME_NONE' if the previous time should
    -- be used.

-- | A convenience synonym for @`Nothing` :: `Maybe` `AudioClockGetTimeFunc`@.
noAudioClockGetTimeFunc :: Maybe AudioClockGetTimeFunc
noAudioClockGetTimeFunc :: Maybe AudioClockGetTimeFunc
noAudioClockGetTimeFunc = Maybe AudioClockGetTimeFunc
forall a. Maybe a
Nothing

-- | This function will be called whenever the current clock time needs to be
-- calculated. If this function returns 'GI.Gst.Constants.CLOCK_TIME_NONE', the last reported
-- time will be returned by the clock.
type AudioClockGetTimeFunc_WithClosures =
    Gst.Clock.Clock
    -- ^ /@clock@/: the t'GI.GstAudio.Objects.AudioClock.AudioClock'
    -> Ptr ()
    -- ^ /@userData@/: user data
    -> IO Word64
    -- ^ __Returns:__ the current time or 'GI.Gst.Constants.CLOCK_TIME_NONE' if the previous time should
    -- be used.

-- | A convenience synonym for @`Nothing` :: `Maybe` `AudioClockGetTimeFunc_WithClosures`@.
noAudioClockGetTimeFunc_WithClosures :: Maybe AudioClockGetTimeFunc_WithClosures
noAudioClockGetTimeFunc_WithClosures :: Maybe AudioClockGetTimeFunc_WithClosures
noAudioClockGetTimeFunc_WithClosures = Maybe AudioClockGetTimeFunc_WithClosures
forall a. Maybe a
Nothing

-- | A simple wrapper that ignores the closure arguments.
drop_closures_AudioClockGetTimeFunc :: AudioClockGetTimeFunc -> AudioClockGetTimeFunc_WithClosures
drop_closures_AudioClockGetTimeFunc :: AudioClockGetTimeFunc -> AudioClockGetTimeFunc_WithClosures
drop_closures_AudioClockGetTimeFunc _f :: AudioClockGetTimeFunc
_f clock :: Clock
clock _ = AudioClockGetTimeFunc
_f Clock
clock

-- | Wrap the callback into a `GClosure`.
genClosure_AudioClockGetTimeFunc :: MonadIO m => AudioClockGetTimeFunc -> m (GClosure C_AudioClockGetTimeFunc)
genClosure_AudioClockGetTimeFunc :: AudioClockGetTimeFunc -> m (GClosure C_AudioClockGetTimeFunc)
genClosure_AudioClockGetTimeFunc cb :: AudioClockGetTimeFunc
cb = IO (GClosure C_AudioClockGetTimeFunc)
-> m (GClosure C_AudioClockGetTimeFunc)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_AudioClockGetTimeFunc)
 -> m (GClosure C_AudioClockGetTimeFunc))
-> IO (GClosure C_AudioClockGetTimeFunc)
-> m (GClosure C_AudioClockGetTimeFunc)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: AudioClockGetTimeFunc_WithClosures
cb' = AudioClockGetTimeFunc -> AudioClockGetTimeFunc_WithClosures
drop_closures_AudioClockGetTimeFunc AudioClockGetTimeFunc
cb
    let cb'' :: C_AudioClockGetTimeFunc
cb'' = Maybe (Ptr (FunPtr C_AudioClockGetTimeFunc))
-> AudioClockGetTimeFunc_WithClosures -> C_AudioClockGetTimeFunc
wrap_AudioClockGetTimeFunc Maybe (Ptr (FunPtr C_AudioClockGetTimeFunc))
forall a. Maybe a
Nothing AudioClockGetTimeFunc_WithClosures
cb'
    C_AudioClockGetTimeFunc -> IO (FunPtr C_AudioClockGetTimeFunc)
mk_AudioClockGetTimeFunc C_AudioClockGetTimeFunc
cb'' IO (FunPtr C_AudioClockGetTimeFunc)
-> (FunPtr C_AudioClockGetTimeFunc
    -> IO (GClosure C_AudioClockGetTimeFunc))
-> IO (GClosure C_AudioClockGetTimeFunc)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_AudioClockGetTimeFunc
-> IO (GClosure C_AudioClockGetTimeFunc)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `AudioClockGetTimeFunc` into a `C_AudioClockGetTimeFunc`.
wrap_AudioClockGetTimeFunc ::
    Maybe (Ptr (FunPtr C_AudioClockGetTimeFunc)) ->
    AudioClockGetTimeFunc_WithClosures ->
    C_AudioClockGetTimeFunc
wrap_AudioClockGetTimeFunc :: Maybe (Ptr (FunPtr C_AudioClockGetTimeFunc))
-> AudioClockGetTimeFunc_WithClosures -> C_AudioClockGetTimeFunc
wrap_AudioClockGetTimeFunc funptrptr :: Maybe (Ptr (FunPtr C_AudioClockGetTimeFunc))
funptrptr _cb :: AudioClockGetTimeFunc_WithClosures
_cb clock :: Ptr Clock
clock userData :: Ptr ()
userData = do
    Clock
clock' <- ((ManagedPtr Clock -> Clock) -> Ptr Clock -> IO Clock
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Clock -> Clock
Gst.Clock.Clock) Ptr Clock
clock
    Word64
result <- AudioClockGetTimeFunc_WithClosures
_cb  Clock
clock' Ptr ()
userData
    Maybe (Ptr (FunPtr C_AudioClockGetTimeFunc)) -> IO ()
forall a. Maybe (Ptr (FunPtr a)) -> IO ()
maybeReleaseFunPtr Maybe (Ptr (FunPtr C_AudioClockGetTimeFunc))
funptrptr
    Word64 -> IO Word64
forall (m :: * -> *) a. Monad m => a -> m a
return Word64
result


-- callback AudioBaseSinkCustomSlavingCallback
--          -> Callable {returnType = Nothing, returnMayBeNull = False, returnTransfer = TransferNothing, returnDocumentation = Documentation {rawDocText = Nothing, sinceVersion = Nothing}, args = [Arg {argCName = "sink", argType = TInterface (Name {namespace = "GstAudio", name = "AudioBaseSink"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstAudioBaseSink", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "etime", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "external clock time", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "itime", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "internal clock time", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "requested_skew", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "skew amount requested by the callback", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "discont_reason", argType = TInterface (Name {namespace = "GstAudio", name = "AudioBaseSinkDiscontReason"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "reason for discontinuity (if any)", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "user_data", argType = TBasicType TPtr, direction = DirectionIn, mayBeNull = True, argDoc = Documentation {rawDocText = Just "user data", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = 5, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}], skipReturn = False, callableThrows = False, callableDeprecated = Nothing, callableDocumentation = Documentation {rawDocText = Just "This function is set with gst_audio_base_sink_set_custom_slaving_callback()\nand is called during playback. It receives the current time of external and\ninternal clocks, which the callback can then use to apply any custom\nslaving/synchronization schemes.\n\nThe external clock is the sink's element clock, the internal one is the\ninternal audio clock. The internal audio clock's calibration is applied to\nthe timestamps before they are passed to the callback. The difference between\netime and itime is the skew; how much internal and external clock lie apart\nfrom each other. A skew of 0 means both clocks are perfectly in sync.\nitime > etime means the external clock is going slower, while itime < etime\nmeans it is going faster than the internal clock. etime and itime are always\nvalid timestamps, except for when a discontinuity happens.\n\nrequested_skew is an output value the callback can write to. It informs the\nsink of whether or not it should move the playout pointer, and if so, by how\nmuch. This pointer is only NULL if a discontinuity occurs; otherwise, it is\nsafe to write to *requested_skew. The default skew is 0.\n\nThe sink may experience discontinuities. If one happens, discont is TRUE,\nitime, etime are set to GST_CLOCK_TIME_NONE, and requested_skew is NULL.\nThis makes it possible to reset custom clock slaving algorithms when a\ndiscontinuity happens.", sinceVersion = Just "1.6"}}
-- | Type for the callback on the (unwrapped) C side.
type C_AudioBaseSinkCustomSlavingCallback =
    Ptr GstAudio.AudioBaseSink.AudioBaseSink ->
    Word64 ->
    Word64 ->
    Int64 ->
    CUInt ->
    Ptr () ->
    IO ()

-- Args: [ Arg
--           { argCName = "sink"
--           , argType =
--               TInterface Name { namespace = "GstAudio" , name = "AudioBaseSink" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstAudioBaseSink"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "etime"
--           , argType = TBasicType TUInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "external clock time"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "itime"
--           , argType = TBasicType TUInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "internal clock time"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "requested_skew"
--           , argType = TBasicType TInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "skew amount requested by the callback"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "discont_reason"
--           , argType =
--               TInterface
--                 Name
--                   { namespace = "GstAudio" , name = "AudioBaseSinkDiscontReason" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "reason for discontinuity (if any)"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "user data" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = 5
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "dynamic" __dynamic_C_AudioBaseSinkCustomSlavingCallback :: FunPtr C_AudioBaseSinkCustomSlavingCallback -> C_AudioBaseSinkCustomSlavingCallback

-- | Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
dynamic_AudioBaseSinkCustomSlavingCallback ::
    (B.CallStack.HasCallStack, MonadIO m, GstAudio.AudioBaseSink.IsAudioBaseSink a) =>
    FunPtr C_AudioBaseSinkCustomSlavingCallback
    -> a
    -- ^ /@sink@/: a t'GI.GstAudio.Objects.AudioBaseSink.AudioBaseSink'
    -> Word64
    -- ^ /@etime@/: external clock time
    -> Word64
    -- ^ /@itime@/: internal clock time
    -> Int64
    -- ^ /@requestedSkew@/: skew amount requested by the callback
    -> GstAudio.Enums.AudioBaseSinkDiscontReason
    -- ^ /@discontReason@/: reason for discontinuity (if any)
    -> Ptr ()
    -- ^ /@userData@/: user data
    -> m ()
dynamic_AudioBaseSinkCustomSlavingCallback :: FunPtr C_AudioBaseSinkCustomSlavingCallback
-> a
-> Word64
-> Word64
-> Int64
-> AudioBaseSinkDiscontReason
-> Ptr ()
-> m ()
dynamic_AudioBaseSinkCustomSlavingCallback __funPtr :: FunPtr C_AudioBaseSinkCustomSlavingCallback
__funPtr sink :: a
sink etime :: Word64
etime itime :: Word64
itime requestedSkew :: Int64
requestedSkew discontReason :: AudioBaseSinkDiscontReason
discontReason userData :: Ptr ()
userData = 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 AudioBaseSink
sink' <- a -> IO (Ptr AudioBaseSink)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
sink
    let discontReason' :: CUInt
discontReason' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (AudioBaseSinkDiscontReason -> Int)
-> AudioBaseSinkDiscontReason
-> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AudioBaseSinkDiscontReason -> Int
forall a. Enum a => a -> Int
fromEnum) AudioBaseSinkDiscontReason
discontReason
    (FunPtr C_AudioBaseSinkCustomSlavingCallback
-> C_AudioBaseSinkCustomSlavingCallback
__dynamic_C_AudioBaseSinkCustomSlavingCallback FunPtr C_AudioBaseSinkCustomSlavingCallback
__funPtr) Ptr AudioBaseSink
sink' Word64
etime Word64
itime Int64
requestedSkew CUInt
discontReason' Ptr ()
userData
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
sink
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

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

-- | This function is set with 'GI.GstAudio.Objects.AudioBaseSink.audioBaseSinkSetCustomSlavingCallback'
-- and is called during playback. It receives the current time of external and
-- internal clocks, which the callback can then use to apply any custom
-- slaving\/synchronization schemes.
-- 
-- The external clock is the sink\'s element clock, the internal one is the
-- internal audio clock. The internal audio clock\'s calibration is applied to
-- the timestamps before they are passed to the callback. The difference between
-- etime and itime is the skew; how much internal and external clock lie apart
-- from each other. A skew of 0 means both clocks are perfectly in sync.
-- itime > etime means the external clock is going slower, while itime \< etime
-- means it is going faster than the internal clock. etime and itime are always
-- valid timestamps, except for when a discontinuity happens.
-- 
-- requested_skew is an output value the callback can write to. It informs the
-- sink of whether or not it should move the playout pointer, and if so, by how
-- much. This pointer is only NULL if a discontinuity occurs; otherwise, it is
-- safe to write to *requested_skew. The default skew is 0.
-- 
-- The sink may experience discontinuities. If one happens, discont is TRUE,
-- itime, etime are set to GST_CLOCK_TIME_NONE, and requested_skew is NULL.
-- This makes it possible to reset custom clock slaving algorithms when a
-- discontinuity happens.
-- 
-- /Since: 1.6/
type AudioBaseSinkCustomSlavingCallback =
    GstAudio.AudioBaseSink.AudioBaseSink
    -- ^ /@sink@/: a t'GI.GstAudio.Objects.AudioBaseSink.AudioBaseSink'
    -> Word64
    -- ^ /@etime@/: external clock time
    -> Word64
    -- ^ /@itime@/: internal clock time
    -> Int64
    -- ^ /@requestedSkew@/: skew amount requested by the callback
    -> GstAudio.Enums.AudioBaseSinkDiscontReason
    -- ^ /@discontReason@/: reason for discontinuity (if any)
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `AudioBaseSinkCustomSlavingCallback`@.
noAudioBaseSinkCustomSlavingCallback :: Maybe AudioBaseSinkCustomSlavingCallback
noAudioBaseSinkCustomSlavingCallback :: Maybe AudioBaseSinkCustomSlavingCallback
noAudioBaseSinkCustomSlavingCallback = Maybe AudioBaseSinkCustomSlavingCallback
forall a. Maybe a
Nothing

-- | This function is set with 'GI.GstAudio.Objects.AudioBaseSink.audioBaseSinkSetCustomSlavingCallback'
-- and is called during playback. It receives the current time of external and
-- internal clocks, which the callback can then use to apply any custom
-- slaving\/synchronization schemes.
-- 
-- The external clock is the sink\'s element clock, the internal one is the
-- internal audio clock. The internal audio clock\'s calibration is applied to
-- the timestamps before they are passed to the callback. The difference between
-- etime and itime is the skew; how much internal and external clock lie apart
-- from each other. A skew of 0 means both clocks are perfectly in sync.
-- itime > etime means the external clock is going slower, while itime \< etime
-- means it is going faster than the internal clock. etime and itime are always
-- valid timestamps, except for when a discontinuity happens.
-- 
-- requested_skew is an output value the callback can write to. It informs the
-- sink of whether or not it should move the playout pointer, and if so, by how
-- much. This pointer is only NULL if a discontinuity occurs; otherwise, it is
-- safe to write to *requested_skew. The default skew is 0.
-- 
-- The sink may experience discontinuities. If one happens, discont is TRUE,
-- itime, etime are set to GST_CLOCK_TIME_NONE, and requested_skew is NULL.
-- This makes it possible to reset custom clock slaving algorithms when a
-- discontinuity happens.
-- 
-- /Since: 1.6/
type AudioBaseSinkCustomSlavingCallback_WithClosures =
    GstAudio.AudioBaseSink.AudioBaseSink
    -- ^ /@sink@/: a t'GI.GstAudio.Objects.AudioBaseSink.AudioBaseSink'
    -> Word64
    -- ^ /@etime@/: external clock time
    -> Word64
    -- ^ /@itime@/: internal clock time
    -> Int64
    -- ^ /@requestedSkew@/: skew amount requested by the callback
    -> GstAudio.Enums.AudioBaseSinkDiscontReason
    -- ^ /@discontReason@/: reason for discontinuity (if any)
    -> Ptr ()
    -- ^ /@userData@/: user data
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `AudioBaseSinkCustomSlavingCallback_WithClosures`@.
noAudioBaseSinkCustomSlavingCallback_WithClosures :: Maybe AudioBaseSinkCustomSlavingCallback_WithClosures
noAudioBaseSinkCustomSlavingCallback_WithClosures :: Maybe AudioBaseSinkCustomSlavingCallback_WithClosures
noAudioBaseSinkCustomSlavingCallback_WithClosures = Maybe AudioBaseSinkCustomSlavingCallback_WithClosures
forall a. Maybe a
Nothing

-- | A simple wrapper that ignores the closure arguments.
drop_closures_AudioBaseSinkCustomSlavingCallback :: AudioBaseSinkCustomSlavingCallback -> AudioBaseSinkCustomSlavingCallback_WithClosures
drop_closures_AudioBaseSinkCustomSlavingCallback :: AudioBaseSinkCustomSlavingCallback
-> AudioBaseSinkCustomSlavingCallback_WithClosures
drop_closures_AudioBaseSinkCustomSlavingCallback _f :: AudioBaseSinkCustomSlavingCallback
_f sink :: AudioBaseSink
sink etime :: Word64
etime itime :: Word64
itime requestedSkew :: Int64
requestedSkew discontReason :: AudioBaseSinkDiscontReason
discontReason _ = AudioBaseSinkCustomSlavingCallback
_f AudioBaseSink
sink Word64
etime Word64
itime Int64
requestedSkew AudioBaseSinkDiscontReason
discontReason

-- | Wrap the callback into a `GClosure`.
genClosure_AudioBaseSinkCustomSlavingCallback :: MonadIO m => AudioBaseSinkCustomSlavingCallback -> m (GClosure C_AudioBaseSinkCustomSlavingCallback)
genClosure_AudioBaseSinkCustomSlavingCallback :: AudioBaseSinkCustomSlavingCallback
-> m (GClosure C_AudioBaseSinkCustomSlavingCallback)
genClosure_AudioBaseSinkCustomSlavingCallback cb :: AudioBaseSinkCustomSlavingCallback
cb = IO (GClosure C_AudioBaseSinkCustomSlavingCallback)
-> m (GClosure C_AudioBaseSinkCustomSlavingCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_AudioBaseSinkCustomSlavingCallback)
 -> m (GClosure C_AudioBaseSinkCustomSlavingCallback))
-> IO (GClosure C_AudioBaseSinkCustomSlavingCallback)
-> m (GClosure C_AudioBaseSinkCustomSlavingCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: AudioBaseSinkCustomSlavingCallback_WithClosures
cb' = AudioBaseSinkCustomSlavingCallback
-> AudioBaseSinkCustomSlavingCallback_WithClosures
drop_closures_AudioBaseSinkCustomSlavingCallback AudioBaseSinkCustomSlavingCallback
cb
    let cb'' :: C_AudioBaseSinkCustomSlavingCallback
cb'' = Maybe (Ptr (FunPtr C_AudioBaseSinkCustomSlavingCallback))
-> AudioBaseSinkCustomSlavingCallback_WithClosures
-> C_AudioBaseSinkCustomSlavingCallback
wrap_AudioBaseSinkCustomSlavingCallback Maybe (Ptr (FunPtr C_AudioBaseSinkCustomSlavingCallback))
forall a. Maybe a
Nothing AudioBaseSinkCustomSlavingCallback_WithClosures
cb'
    C_AudioBaseSinkCustomSlavingCallback
-> IO (FunPtr C_AudioBaseSinkCustomSlavingCallback)
mk_AudioBaseSinkCustomSlavingCallback C_AudioBaseSinkCustomSlavingCallback
cb'' IO (FunPtr C_AudioBaseSinkCustomSlavingCallback)
-> (FunPtr C_AudioBaseSinkCustomSlavingCallback
    -> IO (GClosure C_AudioBaseSinkCustomSlavingCallback))
-> IO (GClosure C_AudioBaseSinkCustomSlavingCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_AudioBaseSinkCustomSlavingCallback
-> IO (GClosure C_AudioBaseSinkCustomSlavingCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `AudioBaseSinkCustomSlavingCallback` into a `C_AudioBaseSinkCustomSlavingCallback`.
wrap_AudioBaseSinkCustomSlavingCallback ::
    Maybe (Ptr (FunPtr C_AudioBaseSinkCustomSlavingCallback)) ->
    AudioBaseSinkCustomSlavingCallback_WithClosures ->
    C_AudioBaseSinkCustomSlavingCallback
wrap_AudioBaseSinkCustomSlavingCallback :: Maybe (Ptr (FunPtr C_AudioBaseSinkCustomSlavingCallback))
-> AudioBaseSinkCustomSlavingCallback_WithClosures
-> C_AudioBaseSinkCustomSlavingCallback
wrap_AudioBaseSinkCustomSlavingCallback funptrptr :: Maybe (Ptr (FunPtr C_AudioBaseSinkCustomSlavingCallback))
funptrptr _cb :: AudioBaseSinkCustomSlavingCallback_WithClosures
_cb sink :: Ptr AudioBaseSink
sink etime :: Word64
etime itime :: Word64
itime requestedSkew :: Int64
requestedSkew discontReason :: CUInt
discontReason userData :: Ptr ()
userData = do
    AudioBaseSink
sink' <- ((ManagedPtr AudioBaseSink -> AudioBaseSink)
-> Ptr AudioBaseSink -> IO AudioBaseSink
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr AudioBaseSink -> AudioBaseSink
GstAudio.AudioBaseSink.AudioBaseSink) Ptr AudioBaseSink
sink
    let discontReason' :: AudioBaseSinkDiscontReason
discontReason' = (Int -> AudioBaseSinkDiscontReason
forall a. Enum a => Int -> a
toEnum (Int -> AudioBaseSinkDiscontReason)
-> (CUInt -> Int) -> CUInt -> AudioBaseSinkDiscontReason
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
discontReason
    AudioBaseSinkCustomSlavingCallback_WithClosures
_cb  AudioBaseSink
sink' Word64
etime Word64
itime Int64
requestedSkew AudioBaseSinkDiscontReason
discontReason' Ptr ()
userData
    Maybe (Ptr (FunPtr C_AudioBaseSinkCustomSlavingCallback)) -> IO ()
forall a. Maybe (Ptr (FunPtr a)) -> IO ()
maybeReleaseFunPtr Maybe (Ptr (FunPtr C_AudioBaseSinkCustomSlavingCallback))
funptrptr