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

The 'GI.Gst.Structs.ParentBufferMeta.ParentBufferMeta' is a 'GI.Gst.Structs.Meta.Meta' which can be attached to a 'GI.Gst.Structs.Buffer.Buffer'
to hold a reference to another buffer that is only released when the child
'GI.Gst.Structs.Buffer.Buffer' is released.

Typically, 'GI.Gst.Structs.ParentBufferMeta.ParentBufferMeta' is used when the child buffer is directly
using the 'GI.Gst.Structs.Memory.Memory' of the parent buffer, and wants to prevent the parent
buffer from being returned to a buffer pool until the 'GI.Gst.Structs.Memory.Memory' is available
for re-use.

/Since: 1.6/
-}

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

module GI.Gst.Structs.ParentBufferMeta
    (

-- * Exported types
    ParentBufferMeta(..)                    ,
    newZeroParentBufferMeta                 ,
    noParentBufferMeta                      ,


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

    parentBufferMetaGetInfo                 ,




 -- * Properties
-- ** buffer #attr:buffer#
{- | the 'GI.Gst.Structs.Buffer.Buffer' on which a reference is being held.
-}
    clearParentBufferMetaBuffer             ,
    getParentBufferMetaBuffer               ,
#if ENABLE_OVERLOADING
    parentBufferMeta_buffer                 ,
#endif
    setParentBufferMetaBuffer               ,


-- ** parent #attr:parent#
{- | the parent 'GI.Gst.Structs.Meta.Meta' structure
-}
    getParentBufferMetaParent               ,
#if ENABLE_OVERLOADING
    parentBufferMeta_parent                 ,
#endif




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

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

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

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


-- | A convenience alias for `Nothing` :: `Maybe` `ParentBufferMeta`.
noParentBufferMeta :: Maybe ParentBufferMeta
noParentBufferMeta = Nothing

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

@
'Data.GI.Base.Attributes.get' parentBufferMeta #parent
@
-}
getParentBufferMetaParent :: MonadIO m => ParentBufferMeta -> m Gst.Meta.Meta
getParentBufferMetaParent 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 ParentBufferMetaParentFieldInfo
instance AttrInfo ParentBufferMetaParentFieldInfo where
    type AttrAllowedOps ParentBufferMetaParentFieldInfo = '[ 'AttrGet]
    type AttrSetTypeConstraint ParentBufferMetaParentFieldInfo = (~) (Ptr Gst.Meta.Meta)
    type AttrBaseTypeConstraint ParentBufferMetaParentFieldInfo = (~) ParentBufferMeta
    type AttrGetType ParentBufferMetaParentFieldInfo = Gst.Meta.Meta
    type AttrLabel ParentBufferMetaParentFieldInfo = "parent"
    type AttrOrigin ParentBufferMetaParentFieldInfo = ParentBufferMeta
    attrGet _ = getParentBufferMetaParent
    attrSet _ = undefined
    attrConstruct = undefined
    attrClear _ = undefined

parentBufferMeta_parent :: AttrLabelProxy "parent"
parentBufferMeta_parent = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' parentBufferMeta #buffer
@
-}
getParentBufferMetaBuffer :: MonadIO m => ParentBufferMeta -> m (Maybe Gst.Buffer.Buffer)
getParentBufferMetaBuffer s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 16) :: IO (Ptr Gst.Buffer.Buffer)
    result <- SP.convertIfNonNull val $ \val' -> do
        val'' <- (newBoxed Gst.Buffer.Buffer) val'
        return val''
    return result

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

@
'Data.GI.Base.Attributes.set' parentBufferMeta [ #buffer 'Data.GI.Base.Attributes.:=' value ]
@
-}
setParentBufferMetaBuffer :: MonadIO m => ParentBufferMeta -> Ptr Gst.Buffer.Buffer -> m ()
setParentBufferMetaBuffer s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 16) (val :: Ptr Gst.Buffer.Buffer)

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

@
'Data.GI.Base.Attributes.clear' #buffer
@
-}
clearParentBufferMetaBuffer :: MonadIO m => ParentBufferMeta -> m ()
clearParentBufferMetaBuffer s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 16) (FP.nullPtr :: Ptr Gst.Buffer.Buffer)

#if ENABLE_OVERLOADING
data ParentBufferMetaBufferFieldInfo
instance AttrInfo ParentBufferMetaBufferFieldInfo where
    type AttrAllowedOps ParentBufferMetaBufferFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint ParentBufferMetaBufferFieldInfo = (~) (Ptr Gst.Buffer.Buffer)
    type AttrBaseTypeConstraint ParentBufferMetaBufferFieldInfo = (~) ParentBufferMeta
    type AttrGetType ParentBufferMetaBufferFieldInfo = Maybe Gst.Buffer.Buffer
    type AttrLabel ParentBufferMetaBufferFieldInfo = "buffer"
    type AttrOrigin ParentBufferMetaBufferFieldInfo = ParentBufferMeta
    attrGet _ = getParentBufferMetaBuffer
    attrSet _ = setParentBufferMetaBuffer
    attrConstruct = undefined
    attrClear _ = clearParentBufferMetaBuffer

parentBufferMeta_buffer :: AttrLabelProxy "buffer"
parentBufferMeta_buffer = AttrLabelProxy

#endif



#if ENABLE_OVERLOADING
instance O.HasAttributeList ParentBufferMeta
type instance O.AttributeList ParentBufferMeta = ParentBufferMetaAttributeList
type ParentBufferMetaAttributeList = ('[ '("parent", ParentBufferMetaParentFieldInfo), '("buffer", ParentBufferMetaBufferFieldInfo)] :: [(Symbol, *)])
#endif

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

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

{- |
Get the global 'GI.Gst.Structs.MetaInfo.MetaInfo' describing  the 'GI.Gst.Structs.ParentBufferMeta.ParentBufferMeta' meta.

/Since: 1.6/
-}
parentBufferMetaGetInfo ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m Gst.MetaInfo.MetaInfo
    {- ^ __Returns:__ The 'GI.Gst.Structs.MetaInfo.MetaInfo' -}
parentBufferMetaGetInfo  = liftIO $ do
    result <- gst_parent_buffer_meta_get_info
    checkUnexpectedReturnNULL "parentBufferMetaGetInfo" result
    result' <- (newPtr Gst.MetaInfo.MetaInfo) result
    return result'

#if ENABLE_OVERLOADING
#endif

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

instance (info ~ ResolveParentBufferMetaMethod t ParentBufferMeta, O.MethodInfo info ParentBufferMeta p) => OL.IsLabel t (ParentBufferMeta -> 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