{- |
Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
License    : LGPL-2.1
Maintainer : Iñaki García Etxebarria (inaki@blueleaf.cc)

'GI.GstAudio.Structs.AudioDownmixMeta.AudioDownmixMeta' defines an audio downmix matrix to be send along with
audio buffers. These functions in this module help to create and attach the
meta as well as extracting it.

/Since: 1.16/
-}

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

module GI.GstAudio.Structs.AudioMeta
    (

-- * Exported types
    AudioMeta(..)                           ,
    newZeroAudioMeta                        ,
    noAudioMeta                             ,


 -- * Methods
-- ** getInfo #method:getInfo#

    audioMetaGetInfo                        ,




 -- * Properties
-- ** info #attr:info#
{- | the audio properties of the buffer
-}
#if ENABLE_OVERLOADING
    audioMeta_info                          ,
#endif
    getAudioMetaInfo                        ,


-- ** meta #attr:meta#
{- | parent 'GI.Gst.Structs.Meta.Meta'
-}
#if ENABLE_OVERLOADING
    audioMeta_meta                          ,
#endif
    getAudioMetaMeta                        ,


-- ** offsets #attr:offsets#
{- | the offsets (in bytes) where each channel plane starts in the
  buffer or 'Nothing' if the buffer has interleaved layout; if not 'Nothing', this
  is guaranteed to be an array of /@info@/.channels elements
-}
#if ENABLE_OVERLOADING
    audioMeta_offsets                       ,
#endif
    getAudioMetaOffsets                     ,
    setAudioMetaOffsets                     ,


-- ** samples #attr:samples#
{- | the number of valid samples in the buffer
-}
#if ENABLE_OVERLOADING
    audioMeta_samples                       ,
#endif
    getAudioMetaSamples                     ,
    setAudioMetaSamples                     ,




    ) 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.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.Structs.Meta as Gst.Meta
import qualified GI.Gst.Structs.MetaInfo as Gst.MetaInfo
import {-# SOURCE #-} qualified GI.GstAudio.Structs.AudioInfo as GstAudio.AudioInfo

-- | Memory-managed wrapper type.
newtype AudioMeta = AudioMeta (ManagedPtr AudioMeta)
instance WrappedPtr AudioMeta where
    wrappedPtrCalloc = callocBytes 448
    wrappedPtrCopy = \p -> withManagedPtr p (copyBytes 448 >=> wrapPtr AudioMeta)
    wrappedPtrFree = Just ptr_to_g_free

-- | Construct a `AudioMeta` struct initialized to zero.
newZeroAudioMeta :: MonadIO m => m AudioMeta
newZeroAudioMeta = liftIO $ wrappedPtrCalloc >>= wrapPtr AudioMeta

instance tag ~ 'AttrSet => Constructible AudioMeta tag where
    new _ attrs = do
        o <- newZeroAudioMeta
        GI.Attributes.set o attrs
        return o


-- | A convenience alias for `Nothing` :: `Maybe` `AudioMeta`.
noAudioMeta :: Maybe AudioMeta
noAudioMeta = Nothing

{- |
Get the value of the “@meta@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.get' audioMeta #meta
@
-}
getAudioMetaMeta :: MonadIO m => AudioMeta -> m Gst.Meta.Meta
getAudioMetaMeta s = liftIO $ withManagedPtr s $ \ptr -> do
    let val = ptr `plusPtr` 0 :: (Ptr Gst.Meta.Meta)
    val' <- (newPtr Gst.Meta.Meta) val
    return val'

#if ENABLE_OVERLOADING
data AudioMetaMetaFieldInfo
instance AttrInfo AudioMetaMetaFieldInfo where
    type AttrAllowedOps AudioMetaMetaFieldInfo = '[ 'AttrGet]
    type AttrSetTypeConstraint AudioMetaMetaFieldInfo = (~) (Ptr Gst.Meta.Meta)
    type AttrBaseTypeConstraint AudioMetaMetaFieldInfo = (~) AudioMeta
    type AttrGetType AudioMetaMetaFieldInfo = Gst.Meta.Meta
    type AttrLabel AudioMetaMetaFieldInfo = "meta"
    type AttrOrigin AudioMetaMetaFieldInfo = AudioMeta
    attrGet _ = getAudioMetaMeta
    attrSet _ = undefined
    attrConstruct = undefined
    attrClear _ = undefined

audioMeta_meta :: AttrLabelProxy "meta"
audioMeta_meta = AttrLabelProxy

#endif


{- |
Get the value of the “@info@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.get' audioMeta #info
@
-}
getAudioMetaInfo :: MonadIO m => AudioMeta -> m GstAudio.AudioInfo.AudioInfo
getAudioMetaInfo s = liftIO $ withManagedPtr s $ \ptr -> do
    let val = ptr `plusPtr` 16 :: (Ptr GstAudio.AudioInfo.AudioInfo)
    val' <- (newBoxed GstAudio.AudioInfo.AudioInfo) val
    return val'

#if ENABLE_OVERLOADING
data AudioMetaInfoFieldInfo
instance AttrInfo AudioMetaInfoFieldInfo where
    type AttrAllowedOps AudioMetaInfoFieldInfo = '[ 'AttrGet]
    type AttrSetTypeConstraint AudioMetaInfoFieldInfo = (~) (Ptr GstAudio.AudioInfo.AudioInfo)
    type AttrBaseTypeConstraint AudioMetaInfoFieldInfo = (~) AudioMeta
    type AttrGetType AudioMetaInfoFieldInfo = GstAudio.AudioInfo.AudioInfo
    type AttrLabel AudioMetaInfoFieldInfo = "info"
    type AttrOrigin AudioMetaInfoFieldInfo = AudioMeta
    attrGet _ = getAudioMetaInfo
    attrSet _ = undefined
    attrConstruct = undefined
    attrClear _ = undefined

audioMeta_info :: AttrLabelProxy "info"
audioMeta_info = AttrLabelProxy

#endif


{- |
Get the value of the “@samples@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.get' audioMeta #samples
@
-}
getAudioMetaSamples :: MonadIO m => AudioMeta -> m Word64
getAudioMetaSamples s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 336) :: IO Word64
    return val

{- |
Set the value of the “@samples@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.set' audioMeta [ #samples 'Data.GI.Base.Attributes.:=' value ]
@
-}
setAudioMetaSamples :: MonadIO m => AudioMeta -> Word64 -> m ()
setAudioMetaSamples s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 336) (val :: Word64)

#if ENABLE_OVERLOADING
data AudioMetaSamplesFieldInfo
instance AttrInfo AudioMetaSamplesFieldInfo where
    type AttrAllowedOps AudioMetaSamplesFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint AudioMetaSamplesFieldInfo = (~) Word64
    type AttrBaseTypeConstraint AudioMetaSamplesFieldInfo = (~) AudioMeta
    type AttrGetType AudioMetaSamplesFieldInfo = Word64
    type AttrLabel AudioMetaSamplesFieldInfo = "samples"
    type AttrOrigin AudioMetaSamplesFieldInfo = AudioMeta
    attrGet _ = getAudioMetaSamples
    attrSet _ = setAudioMetaSamples
    attrConstruct = undefined
    attrClear _ = undefined

audioMeta_samples :: AttrLabelProxy "samples"
audioMeta_samples = AttrLabelProxy

#endif


{- |
Get the value of the “@offsets@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.get' audioMeta #offsets
@
-}
getAudioMetaOffsets :: MonadIO m => AudioMeta -> m Word64
getAudioMetaOffsets s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 344) :: IO Word64
    return val

{- |
Set the value of the “@offsets@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.set' audioMeta [ #offsets 'Data.GI.Base.Attributes.:=' value ]
@
-}
setAudioMetaOffsets :: MonadIO m => AudioMeta -> Word64 -> m ()
setAudioMetaOffsets s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 344) (val :: Word64)

#if ENABLE_OVERLOADING
data AudioMetaOffsetsFieldInfo
instance AttrInfo AudioMetaOffsetsFieldInfo where
    type AttrAllowedOps AudioMetaOffsetsFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint AudioMetaOffsetsFieldInfo = (~) Word64
    type AttrBaseTypeConstraint AudioMetaOffsetsFieldInfo = (~) AudioMeta
    type AttrGetType AudioMetaOffsetsFieldInfo = Word64
    type AttrLabel AudioMetaOffsetsFieldInfo = "offsets"
    type AttrOrigin AudioMetaOffsetsFieldInfo = AudioMeta
    attrGet _ = getAudioMetaOffsets
    attrSet _ = setAudioMetaOffsets
    attrConstruct = undefined
    attrClear _ = undefined

audioMeta_offsets :: AttrLabelProxy "offsets"
audioMeta_offsets = AttrLabelProxy

#endif



#if ENABLE_OVERLOADING
instance O.HasAttributeList AudioMeta
type instance O.AttributeList AudioMeta = AudioMetaAttributeList
type AudioMetaAttributeList = ('[ '("meta", AudioMetaMetaFieldInfo), '("info", AudioMetaInfoFieldInfo), '("samples", AudioMetaSamplesFieldInfo), '("offsets", AudioMetaOffsetsFieldInfo)] :: [(Symbol, *)])
#endif

-- method AudioMeta::get_info
-- method type : MemberFunction
-- Args : []
-- Lengths : []
-- returnType : Just (TInterface (Name {namespace = "Gst", name = "MetaInfo"}))
-- throws : False
-- Skip return : False

foreign import ccall "gst_audio_meta_get_info" gst_audio_meta_get_info ::
    IO (Ptr Gst.MetaInfo.MetaInfo)

{- |
/No description available in the introspection data./
-}
audioMetaGetInfo ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m Gst.MetaInfo.MetaInfo
audioMetaGetInfo  = liftIO $ do
    result <- gst_audio_meta_get_info
    checkUnexpectedReturnNULL "audioMetaGetInfo" result
    result' <- (newPtr Gst.MetaInfo.MetaInfo) result
    return result'

#if ENABLE_OVERLOADING
#endif

#if ENABLE_OVERLOADING
type family ResolveAudioMetaMethod (t :: Symbol) (o :: *) :: * where
    ResolveAudioMetaMethod l o = O.MethodResolutionFailed l o

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

#endif