{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.GstAudio.Structs.AudioChannelMixer
    ( 
    AudioChannelMixer(..)                   ,
 
#if defined(ENABLE_OVERLOADING)
    ResolveAudioChannelMixerMethod          ,
#endif
#if defined(ENABLE_OVERLOADING)
    AudioChannelMixerFreeMethodInfo         ,
#endif
    audioChannelMixerFree                   ,
#if defined(ENABLE_OVERLOADING)
    AudioChannelMixerIsPassthroughMethodInfo,
#endif
    audioChannelMixerIsPassthrough          ,
#if defined(ENABLE_OVERLOADING)
    AudioChannelMixerSamplesMethodInfo      ,
#endif
    audioChannelMixerSamples                ,
    ) where
import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P
import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.Kind as DK
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R
import qualified Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT
#if MIN_VERSION_base(4,18,0)
#else
#endif
newtype AudioChannelMixer = AudioChannelMixer (SP.ManagedPtr AudioChannelMixer)
    deriving (AudioChannelMixer -> AudioChannelMixer -> Bool
(AudioChannelMixer -> AudioChannelMixer -> Bool)
-> (AudioChannelMixer -> AudioChannelMixer -> Bool)
-> Eq AudioChannelMixer
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AudioChannelMixer -> AudioChannelMixer -> Bool
== :: AudioChannelMixer -> AudioChannelMixer -> Bool
$c/= :: AudioChannelMixer -> AudioChannelMixer -> Bool
/= :: AudioChannelMixer -> AudioChannelMixer -> Bool
Eq)
instance SP.ManagedPtrNewtype AudioChannelMixer where
    toManagedPtr :: AudioChannelMixer -> ManagedPtr AudioChannelMixer
toManagedPtr (AudioChannelMixer ManagedPtr AudioChannelMixer
p) = ManagedPtr AudioChannelMixer
p
instance BoxedPtr AudioChannelMixer where
    boxedPtrCopy :: AudioChannelMixer -> IO AudioChannelMixer
boxedPtrCopy = AudioChannelMixer -> IO AudioChannelMixer
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return
    boxedPtrFree :: AudioChannelMixer -> IO ()
boxedPtrFree = \AudioChannelMixer
_x -> () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList AudioChannelMixer
type instance O.AttributeList AudioChannelMixer = AudioChannelMixerAttributeList
type AudioChannelMixerAttributeList = ('[ ] :: [(Symbol, DK.Type)])
#endif
foreign import ccall "gst_audio_channel_mixer_free" gst_audio_channel_mixer_free :: 
    Ptr AudioChannelMixer ->                
    IO ()
audioChannelMixerFree ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AudioChannelMixer
    
    -> m ()
audioChannelMixerFree :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
AudioChannelMixer -> m ()
audioChannelMixerFree AudioChannelMixer
mix = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr AudioChannelMixer
mix' <- AudioChannelMixer -> IO (Ptr AudioChannelMixer)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr AudioChannelMixer
mix
    Ptr AudioChannelMixer -> IO ()
gst_audio_channel_mixer_free Ptr AudioChannelMixer
mix'
    AudioChannelMixer -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AudioChannelMixer
mix
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data AudioChannelMixerFreeMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod AudioChannelMixerFreeMethodInfo AudioChannelMixer signature where
    overloadedMethod = audioChannelMixerFree
instance O.OverloadedMethodInfo AudioChannelMixerFreeMethodInfo AudioChannelMixer where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GstAudio.Structs.AudioChannelMixer.audioChannelMixerFree",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gstaudio-1.0.28/docs/GI-GstAudio-Structs-AudioChannelMixer.html#v:audioChannelMixerFree"
        })
#endif
foreign import ccall "gst_audio_channel_mixer_is_passthrough" gst_audio_channel_mixer_is_passthrough :: 
    Ptr AudioChannelMixer ->                
    IO CInt
audioChannelMixerIsPassthrough ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AudioChannelMixer
    
    -> m Bool
    
audioChannelMixerIsPassthrough :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
AudioChannelMixer -> m Bool
audioChannelMixerIsPassthrough AudioChannelMixer
mix = IO Bool -> m Bool
forall a. IO a -> m a
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 AudioChannelMixer
mix' <- AudioChannelMixer -> IO (Ptr AudioChannelMixer)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr AudioChannelMixer
mix
    CInt
result <- Ptr AudioChannelMixer -> IO CInt
gst_audio_channel_mixer_is_passthrough Ptr AudioChannelMixer
mix'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    AudioChannelMixer -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AudioChannelMixer
mix
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data AudioChannelMixerIsPassthroughMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.OverloadedMethod AudioChannelMixerIsPassthroughMethodInfo AudioChannelMixer signature where
    overloadedMethod = audioChannelMixerIsPassthrough
instance O.OverloadedMethodInfo AudioChannelMixerIsPassthroughMethodInfo AudioChannelMixer where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GstAudio.Structs.AudioChannelMixer.audioChannelMixerIsPassthrough",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gstaudio-1.0.28/docs/GI-GstAudio-Structs-AudioChannelMixer.html#v:audioChannelMixerIsPassthrough"
        })
#endif
foreign import ccall "gst_audio_channel_mixer_samples" gst_audio_channel_mixer_samples :: 
    Ptr AudioChannelMixer ->                
    Ptr () ->                               
    Ptr () ->                               
    Int32 ->                                
    IO ()
audioChannelMixerSamples ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AudioChannelMixer
    
    -> Ptr ()
    
    -> Ptr ()
    
    -> Int32
    
    -> m ()
audioChannelMixerSamples :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
AudioChannelMixer -> Ptr () -> Ptr () -> Int32 -> m ()
audioChannelMixerSamples AudioChannelMixer
mix Ptr ()
in_ Ptr ()
out Int32
samples = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr AudioChannelMixer
mix' <- AudioChannelMixer -> IO (Ptr AudioChannelMixer)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr AudioChannelMixer
mix
    Ptr AudioChannelMixer -> Ptr () -> Ptr () -> Int32 -> IO ()
gst_audio_channel_mixer_samples Ptr AudioChannelMixer
mix' Ptr ()
in_ Ptr ()
out Int32
samples
    AudioChannelMixer -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AudioChannelMixer
mix
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data AudioChannelMixerSamplesMethodInfo
instance (signature ~ (Ptr () -> Ptr () -> Int32 -> m ()), MonadIO m) => O.OverloadedMethod AudioChannelMixerSamplesMethodInfo AudioChannelMixer signature where
    overloadedMethod = audioChannelMixerSamples
instance O.OverloadedMethodInfo AudioChannelMixerSamplesMethodInfo AudioChannelMixer where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GstAudio.Structs.AudioChannelMixer.audioChannelMixerSamples",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gstaudio-1.0.28/docs/GI-GstAudio-Structs-AudioChannelMixer.html#v:audioChannelMixerSamples"
        })
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveAudioChannelMixerMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveAudioChannelMixerMethod "free" o = AudioChannelMixerFreeMethodInfo
    ResolveAudioChannelMixerMethod "isPassthrough" o = AudioChannelMixerIsPassthroughMethodInfo
    ResolveAudioChannelMixerMethod "samples" o = AudioChannelMixerSamplesMethodInfo
    ResolveAudioChannelMixerMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveAudioChannelMixerMethod t AudioChannelMixer, O.OverloadedMethod info AudioChannelMixer p) => OL.IsLabel t (AudioChannelMixer -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif
#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveAudioChannelMixerMethod t AudioChannelMixer, O.OverloadedMethod info AudioChannelMixer p, R.HasField t AudioChannelMixer p) => R.HasField t AudioChannelMixer p where
    getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveAudioChannelMixerMethod t AudioChannelMixer, O.OverloadedMethodInfo info AudioChannelMixer) => OL.IsLabel t (O.MethodProxy info AudioChannelMixer) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif
#endif