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

Extra buffer metadata describing image properties
-}

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

module GI.GstVideo.Structs.VideoMeta
    (

-- * Exported types
    VideoMeta(..)                           ,
    newZeroVideoMeta                        ,
    noVideoMeta                             ,


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

    videoMetaGetInfo                        ,


-- ** map #method:map#

#if ENABLE_OVERLOADING
    VideoMetaMapMethodInfo                  ,
#endif
    videoMetaMap                            ,


-- ** unmap #method:unmap#

#if ENABLE_OVERLOADING
    VideoMetaUnmapMethodInfo                ,
#endif
    videoMetaUnmap                          ,




 -- * Properties
-- ** buffer #attr:buffer#
{- | the buffer this metadata belongs to
-}
    clearVideoMetaBuffer                    ,
    getVideoMetaBuffer                      ,
    setVideoMetaBuffer                      ,
#if ENABLE_OVERLOADING
    videoMeta_buffer                        ,
#endif


-- ** flags #attr:flags#
{- | additional video flags
-}
    getVideoMetaFlags                       ,
    setVideoMetaFlags                       ,
#if ENABLE_OVERLOADING
    videoMeta_flags                         ,
#endif


-- ** format #attr:format#
{- | the video format
-}
    getVideoMetaFormat                      ,
    setVideoMetaFormat                      ,
#if ENABLE_OVERLOADING
    videoMeta_format                        ,
#endif


-- ** height #attr:height#
{- | the video height
-}
    getVideoMetaHeight                      ,
    setVideoMetaHeight                      ,
#if ENABLE_OVERLOADING
    videoMeta_height                        ,
#endif


-- ** id #attr:id#
{- | identifier of the frame
-}
    getVideoMetaId                          ,
    setVideoMetaId                          ,
#if ENABLE_OVERLOADING
    videoMeta_id                            ,
#endif


-- ** map #attr:map#
{- | /No description available in the introspection data./
-}
    clearVideoMetaMap                       ,
    getVideoMetaMap                         ,
    setVideoMetaMap                         ,
#if ENABLE_OVERLOADING
    videoMeta_map                           ,
#endif


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


-- ** nPlanes #attr:nPlanes#
{- | the number of planes in the image
-}
    getVideoMetaNPlanes                     ,
    setVideoMetaNPlanes                     ,
#if ENABLE_OVERLOADING
    videoMeta_nPlanes                       ,
#endif


-- ** unmap #attr:unmap#
{- | /No description available in the introspection data./
-}
    clearVideoMetaUnmap                     ,
    getVideoMetaUnmap                       ,
    setVideoMetaUnmap                       ,
#if ENABLE_OVERLOADING
    videoMeta_unmap                         ,
#endif


-- ** width #attr:width#
{- | the video width
-}
    getVideoMetaWidth                       ,
    setVideoMetaWidth                       ,
#if ENABLE_OVERLOADING
    videoMeta_width                         ,
#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 qualified GI.Gst.Flags as Gst.Flags
import qualified GI.Gst.Structs.Buffer as Gst.Buffer
import qualified GI.Gst.Structs.MapInfo as Gst.MapInfo
import qualified GI.Gst.Structs.Meta as Gst.Meta
import qualified GI.Gst.Structs.MetaInfo as Gst.MetaInfo
import qualified GI.GstVideo.Callbacks as GstVideo.Callbacks
import {-# SOURCE #-} qualified GI.GstVideo.Enums as GstVideo.Enums
import {-# SOURCE #-} qualified GI.GstVideo.Flags as GstVideo.Flags

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

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

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


-- | A convenience alias for `Nothing` :: `Maybe` `VideoMeta`.
noVideoMeta :: Maybe VideoMeta
noVideoMeta = 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' videoMeta #meta
@
-}
getVideoMetaMeta :: MonadIO m => VideoMeta -> m Gst.Meta.Meta
getVideoMetaMeta 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 VideoMetaMetaFieldInfo
instance AttrInfo VideoMetaMetaFieldInfo where
    type AttrAllowedOps VideoMetaMetaFieldInfo = '[ 'AttrGet]
    type AttrSetTypeConstraint VideoMetaMetaFieldInfo = (~) (Ptr Gst.Meta.Meta)
    type AttrBaseTypeConstraint VideoMetaMetaFieldInfo = (~) VideoMeta
    type AttrGetType VideoMetaMetaFieldInfo = Gst.Meta.Meta
    type AttrLabel VideoMetaMetaFieldInfo = "meta"
    type AttrOrigin VideoMetaMetaFieldInfo = VideoMeta
    attrGet _ = getVideoMetaMeta
    attrSet _ = undefined
    attrConstruct = undefined
    attrClear _ = undefined

videoMeta_meta :: AttrLabelProxy "meta"
videoMeta_meta = 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' videoMeta #buffer
@
-}
getVideoMetaBuffer :: MonadIO m => VideoMeta -> m (Maybe Gst.Buffer.Buffer)
getVideoMetaBuffer 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' videoMeta [ #buffer 'Data.GI.Base.Attributes.:=' value ]
@
-}
setVideoMetaBuffer :: MonadIO m => VideoMeta -> Ptr Gst.Buffer.Buffer -> m ()
setVideoMetaBuffer 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
@
-}
clearVideoMetaBuffer :: MonadIO m => VideoMeta -> m ()
clearVideoMetaBuffer s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 16) (FP.nullPtr :: Ptr Gst.Buffer.Buffer)

#if ENABLE_OVERLOADING
data VideoMetaBufferFieldInfo
instance AttrInfo VideoMetaBufferFieldInfo where
    type AttrAllowedOps VideoMetaBufferFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint VideoMetaBufferFieldInfo = (~) (Ptr Gst.Buffer.Buffer)
    type AttrBaseTypeConstraint VideoMetaBufferFieldInfo = (~) VideoMeta
    type AttrGetType VideoMetaBufferFieldInfo = Maybe Gst.Buffer.Buffer
    type AttrLabel VideoMetaBufferFieldInfo = "buffer"
    type AttrOrigin VideoMetaBufferFieldInfo = VideoMeta
    attrGet _ = getVideoMetaBuffer
    attrSet _ = setVideoMetaBuffer
    attrConstruct = undefined
    attrClear _ = clearVideoMetaBuffer

videoMeta_buffer :: AttrLabelProxy "buffer"
videoMeta_buffer = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' videoMeta #flags
@
-}
getVideoMetaFlags :: MonadIO m => VideoMeta -> m [GstVideo.Flags.VideoFrameFlags]
getVideoMetaFlags s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 24) :: IO CUInt
    let val' = wordToGFlags val
    return val'

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

@
'Data.GI.Base.Attributes.set' videoMeta [ #flags 'Data.GI.Base.Attributes.:=' value ]
@
-}
setVideoMetaFlags :: MonadIO m => VideoMeta -> [GstVideo.Flags.VideoFrameFlags] -> m ()
setVideoMetaFlags s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = gflagsToWord val
    poke (ptr `plusPtr` 24) (val' :: CUInt)

#if ENABLE_OVERLOADING
data VideoMetaFlagsFieldInfo
instance AttrInfo VideoMetaFlagsFieldInfo where
    type AttrAllowedOps VideoMetaFlagsFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint VideoMetaFlagsFieldInfo = (~) [GstVideo.Flags.VideoFrameFlags]
    type AttrBaseTypeConstraint VideoMetaFlagsFieldInfo = (~) VideoMeta
    type AttrGetType VideoMetaFlagsFieldInfo = [GstVideo.Flags.VideoFrameFlags]
    type AttrLabel VideoMetaFlagsFieldInfo = "flags"
    type AttrOrigin VideoMetaFlagsFieldInfo = VideoMeta
    attrGet _ = getVideoMetaFlags
    attrSet _ = setVideoMetaFlags
    attrConstruct = undefined
    attrClear _ = undefined

videoMeta_flags :: AttrLabelProxy "flags"
videoMeta_flags = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' videoMeta #format
@
-}
getVideoMetaFormat :: MonadIO m => VideoMeta -> m GstVideo.Enums.VideoFormat
getVideoMetaFormat s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 28) :: IO CUInt
    let val' = (toEnum . fromIntegral) val
    return val'

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

@
'Data.GI.Base.Attributes.set' videoMeta [ #format 'Data.GI.Base.Attributes.:=' value ]
@
-}
setVideoMetaFormat :: MonadIO m => VideoMeta -> GstVideo.Enums.VideoFormat -> m ()
setVideoMetaFormat s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = (fromIntegral . fromEnum) val
    poke (ptr `plusPtr` 28) (val' :: CUInt)

#if ENABLE_OVERLOADING
data VideoMetaFormatFieldInfo
instance AttrInfo VideoMetaFormatFieldInfo where
    type AttrAllowedOps VideoMetaFormatFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint VideoMetaFormatFieldInfo = (~) GstVideo.Enums.VideoFormat
    type AttrBaseTypeConstraint VideoMetaFormatFieldInfo = (~) VideoMeta
    type AttrGetType VideoMetaFormatFieldInfo = GstVideo.Enums.VideoFormat
    type AttrLabel VideoMetaFormatFieldInfo = "format"
    type AttrOrigin VideoMetaFormatFieldInfo = VideoMeta
    attrGet _ = getVideoMetaFormat
    attrSet _ = setVideoMetaFormat
    attrConstruct = undefined
    attrClear _ = undefined

videoMeta_format :: AttrLabelProxy "format"
videoMeta_format = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' videoMeta #id
@
-}
getVideoMetaId :: MonadIO m => VideoMeta -> m Int32
getVideoMetaId s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 32) :: IO Int32
    return val

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

@
'Data.GI.Base.Attributes.set' videoMeta [ #id 'Data.GI.Base.Attributes.:=' value ]
@
-}
setVideoMetaId :: MonadIO m => VideoMeta -> Int32 -> m ()
setVideoMetaId s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 32) (val :: Int32)

#if ENABLE_OVERLOADING
data VideoMetaIdFieldInfo
instance AttrInfo VideoMetaIdFieldInfo where
    type AttrAllowedOps VideoMetaIdFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint VideoMetaIdFieldInfo = (~) Int32
    type AttrBaseTypeConstraint VideoMetaIdFieldInfo = (~) VideoMeta
    type AttrGetType VideoMetaIdFieldInfo = Int32
    type AttrLabel VideoMetaIdFieldInfo = "id"
    type AttrOrigin VideoMetaIdFieldInfo = VideoMeta
    attrGet _ = getVideoMetaId
    attrSet _ = setVideoMetaId
    attrConstruct = undefined
    attrClear _ = undefined

videoMeta_id :: AttrLabelProxy "id"
videoMeta_id = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' videoMeta #width
@
-}
getVideoMetaWidth :: MonadIO m => VideoMeta -> m Word32
getVideoMetaWidth s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 36) :: IO Word32
    return val

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

@
'Data.GI.Base.Attributes.set' videoMeta [ #width 'Data.GI.Base.Attributes.:=' value ]
@
-}
setVideoMetaWidth :: MonadIO m => VideoMeta -> Word32 -> m ()
setVideoMetaWidth s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 36) (val :: Word32)

#if ENABLE_OVERLOADING
data VideoMetaWidthFieldInfo
instance AttrInfo VideoMetaWidthFieldInfo where
    type AttrAllowedOps VideoMetaWidthFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint VideoMetaWidthFieldInfo = (~) Word32
    type AttrBaseTypeConstraint VideoMetaWidthFieldInfo = (~) VideoMeta
    type AttrGetType VideoMetaWidthFieldInfo = Word32
    type AttrLabel VideoMetaWidthFieldInfo = "width"
    type AttrOrigin VideoMetaWidthFieldInfo = VideoMeta
    attrGet _ = getVideoMetaWidth
    attrSet _ = setVideoMetaWidth
    attrConstruct = undefined
    attrClear _ = undefined

videoMeta_width :: AttrLabelProxy "width"
videoMeta_width = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' videoMeta #height
@
-}
getVideoMetaHeight :: MonadIO m => VideoMeta -> m Word32
getVideoMetaHeight s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 40) :: IO Word32
    return val

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

@
'Data.GI.Base.Attributes.set' videoMeta [ #height 'Data.GI.Base.Attributes.:=' value ]
@
-}
setVideoMetaHeight :: MonadIO m => VideoMeta -> Word32 -> m ()
setVideoMetaHeight s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 40) (val :: Word32)

#if ENABLE_OVERLOADING
data VideoMetaHeightFieldInfo
instance AttrInfo VideoMetaHeightFieldInfo where
    type AttrAllowedOps VideoMetaHeightFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint VideoMetaHeightFieldInfo = (~) Word32
    type AttrBaseTypeConstraint VideoMetaHeightFieldInfo = (~) VideoMeta
    type AttrGetType VideoMetaHeightFieldInfo = Word32
    type AttrLabel VideoMetaHeightFieldInfo = "height"
    type AttrOrigin VideoMetaHeightFieldInfo = VideoMeta
    attrGet _ = getVideoMetaHeight
    attrSet _ = setVideoMetaHeight
    attrConstruct = undefined
    attrClear _ = undefined

videoMeta_height :: AttrLabelProxy "height"
videoMeta_height = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' videoMeta #nPlanes
@
-}
getVideoMetaNPlanes :: MonadIO m => VideoMeta -> m Word32
getVideoMetaNPlanes s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 44) :: IO Word32
    return val

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

@
'Data.GI.Base.Attributes.set' videoMeta [ #nPlanes 'Data.GI.Base.Attributes.:=' value ]
@
-}
setVideoMetaNPlanes :: MonadIO m => VideoMeta -> Word32 -> m ()
setVideoMetaNPlanes s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 44) (val :: Word32)

#if ENABLE_OVERLOADING
data VideoMetaNPlanesFieldInfo
instance AttrInfo VideoMetaNPlanesFieldInfo where
    type AttrAllowedOps VideoMetaNPlanesFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint VideoMetaNPlanesFieldInfo = (~) Word32
    type AttrBaseTypeConstraint VideoMetaNPlanesFieldInfo = (~) VideoMeta
    type AttrGetType VideoMetaNPlanesFieldInfo = Word32
    type AttrLabel VideoMetaNPlanesFieldInfo = "n_planes"
    type AttrOrigin VideoMetaNPlanesFieldInfo = VideoMeta
    attrGet _ = getVideoMetaNPlanes
    attrSet _ = setVideoMetaNPlanes
    attrConstruct = undefined
    attrClear _ = undefined

videoMeta_nPlanes :: AttrLabelProxy "nPlanes"
videoMeta_nPlanes = AttrLabelProxy

#endif


-- XXX Skipped attribute for "VideoMeta:offset" :: Not implemented: "Don't know how to unpack C array of type TCArray False 4 (-1) (TBasicType TUInt64)"
-- XXX Skipped attribute for "VideoMeta:stride" :: Not implemented: "Don't know how to unpack C array of type TCArray False 4 (-1) (TBasicType TInt)"
{- |
Get the value of the “@map@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.get' videoMeta #map
@
-}
getVideoMetaMap :: MonadIO m => VideoMeta -> m (Maybe GstVideo.Callbacks.VideoMetaMapFieldCallback)
getVideoMetaMap s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 96) :: IO (FunPtr GstVideo.Callbacks.C_VideoMetaMapFieldCallback)
    result <- SP.convertFunPtrIfNonNull val $ \val' -> do
        let val'' = GstVideo.Callbacks.dynamic_VideoMetaMapFieldCallback val'
        return val''
    return result

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

@
'Data.GI.Base.Attributes.set' videoMeta [ #map 'Data.GI.Base.Attributes.:=' value ]
@
-}
setVideoMetaMap :: MonadIO m => VideoMeta -> FunPtr GstVideo.Callbacks.C_VideoMetaMapFieldCallback -> m ()
setVideoMetaMap s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 96) (val :: FunPtr GstVideo.Callbacks.C_VideoMetaMapFieldCallback)

{- |
Set the value of the “@map@” 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' #map
@
-}
clearVideoMetaMap :: MonadIO m => VideoMeta -> m ()
clearVideoMetaMap s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 96) (FP.nullFunPtr :: FunPtr GstVideo.Callbacks.C_VideoMetaMapFieldCallback)

#if ENABLE_OVERLOADING
data VideoMetaMapFieldInfo
instance AttrInfo VideoMetaMapFieldInfo where
    type AttrAllowedOps VideoMetaMapFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint VideoMetaMapFieldInfo = (~) (FunPtr GstVideo.Callbacks.C_VideoMetaMapFieldCallback)
    type AttrBaseTypeConstraint VideoMetaMapFieldInfo = (~) VideoMeta
    type AttrGetType VideoMetaMapFieldInfo = Maybe GstVideo.Callbacks.VideoMetaMapFieldCallback
    type AttrLabel VideoMetaMapFieldInfo = "map"
    type AttrOrigin VideoMetaMapFieldInfo = VideoMeta
    attrGet _ = getVideoMetaMap
    attrSet _ = setVideoMetaMap
    attrConstruct = undefined
    attrClear _ = clearVideoMetaMap

videoMeta_map :: AttrLabelProxy "map"
videoMeta_map = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' videoMeta #unmap
@
-}
getVideoMetaUnmap :: MonadIO m => VideoMeta -> m (Maybe GstVideo.Callbacks.VideoMetaUnmapFieldCallback)
getVideoMetaUnmap s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 104) :: IO (FunPtr GstVideo.Callbacks.C_VideoMetaUnmapFieldCallback)
    result <- SP.convertFunPtrIfNonNull val $ \val' -> do
        let val'' = GstVideo.Callbacks.dynamic_VideoMetaUnmapFieldCallback val'
        return val''
    return result

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

@
'Data.GI.Base.Attributes.set' videoMeta [ #unmap 'Data.GI.Base.Attributes.:=' value ]
@
-}
setVideoMetaUnmap :: MonadIO m => VideoMeta -> FunPtr GstVideo.Callbacks.C_VideoMetaUnmapFieldCallback -> m ()
setVideoMetaUnmap s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 104) (val :: FunPtr GstVideo.Callbacks.C_VideoMetaUnmapFieldCallback)

{- |
Set the value of the “@unmap@” 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' #unmap
@
-}
clearVideoMetaUnmap :: MonadIO m => VideoMeta -> m ()
clearVideoMetaUnmap s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 104) (FP.nullFunPtr :: FunPtr GstVideo.Callbacks.C_VideoMetaUnmapFieldCallback)

#if ENABLE_OVERLOADING
data VideoMetaUnmapFieldInfo
instance AttrInfo VideoMetaUnmapFieldInfo where
    type AttrAllowedOps VideoMetaUnmapFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint VideoMetaUnmapFieldInfo = (~) (FunPtr GstVideo.Callbacks.C_VideoMetaUnmapFieldCallback)
    type AttrBaseTypeConstraint VideoMetaUnmapFieldInfo = (~) VideoMeta
    type AttrGetType VideoMetaUnmapFieldInfo = Maybe GstVideo.Callbacks.VideoMetaUnmapFieldCallback
    type AttrLabel VideoMetaUnmapFieldInfo = "unmap"
    type AttrOrigin VideoMetaUnmapFieldInfo = VideoMeta
    attrGet _ = getVideoMetaUnmap
    attrSet _ = setVideoMetaUnmap
    attrConstruct = undefined
    attrClear _ = clearVideoMetaUnmap

videoMeta_unmap :: AttrLabelProxy "unmap"
videoMeta_unmap = AttrLabelProxy

#endif



#if ENABLE_OVERLOADING
instance O.HasAttributeList VideoMeta
type instance O.AttributeList VideoMeta = VideoMetaAttributeList
type VideoMetaAttributeList = ('[ '("meta", VideoMetaMetaFieldInfo), '("buffer", VideoMetaBufferFieldInfo), '("flags", VideoMetaFlagsFieldInfo), '("format", VideoMetaFormatFieldInfo), '("id", VideoMetaIdFieldInfo), '("width", VideoMetaWidthFieldInfo), '("height", VideoMetaHeightFieldInfo), '("nPlanes", VideoMetaNPlanesFieldInfo), '("map", VideoMetaMapFieldInfo), '("unmap", VideoMetaUnmapFieldInfo)] :: [(Symbol, *)])
#endif

-- method VideoMeta::map
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "meta", argType = TInterface (Name {namespace = "GstVideo", name = "VideoMeta"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstVideoMeta", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "plane", argType = TBasicType TUInt, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a plane", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "info", argType = TInterface (Name {namespace = "Gst", name = "MapInfo"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstMapInfo", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "data", argType = TBasicType TPtr, direction = DirectionOut, mayBeNull = True, argDoc = Documentation {rawDocText = Just "the data of @plane", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferEverything},Arg {argCName = "stride", argType = TBasicType TInt, direction = DirectionOut, mayBeNull = False, argDoc = Documentation {rawDocText = Just "the stride of @plane", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferEverything},Arg {argCName = "flags", argType = TInterface (Name {namespace = "Gst", name = "MapFlags"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "@GstMapFlags", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gst_video_meta_map" gst_video_meta_map ::
    Ptr VideoMeta ->                        -- meta : TInterface (Name {namespace = "GstVideo", name = "VideoMeta"})
    Word32 ->                               -- plane : TBasicType TUInt
    Ptr Gst.MapInfo.MapInfo ->              -- info : TInterface (Name {namespace = "Gst", name = "MapInfo"})
    Ptr (Ptr ()) ->                         -- data : TBasicType TPtr
    Ptr Int32 ->                            -- stride : TBasicType TInt
    CUInt ->                                -- flags : TInterface (Name {namespace = "Gst", name = "MapFlags"})
    IO CInt

{- |
Map the video plane with index /@plane@/ in /@meta@/ and return a pointer to the
first byte of the plane and the stride of the plane.
-}
videoMetaMap ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    VideoMeta
    {- ^ /@meta@/: a 'GI.GstVideo.Structs.VideoMeta.VideoMeta' -}
    -> Word32
    {- ^ /@plane@/: a plane -}
    -> Gst.MapInfo.MapInfo
    {- ^ /@info@/: a 'GI.Gst.Structs.MapInfo.MapInfo' -}
    -> [Gst.Flags.MapFlags]
    {- ^ /@flags@/: /@gstMapFlags@/ -}
    -> m ((Bool, Ptr (), Int32))
    {- ^ __Returns:__ TRUE if the map operation was successful. -}
videoMetaMap meta plane info flags = liftIO $ do
    meta' <- unsafeManagedPtrGetPtr meta
    info' <- unsafeManagedPtrGetPtr info
    data_ <- allocMem :: IO (Ptr (Ptr ()))
    stride <- allocMem :: IO (Ptr Int32)
    let flags' = gflagsToWord flags
    result <- gst_video_meta_map meta' plane info' data_ stride flags'
    let result' = (/= 0) result
    data_' <- peek data_
    stride' <- peek stride
    touchManagedPtr meta
    touchManagedPtr info
    freeMem data_
    freeMem stride
    return (result', data_', stride')

#if ENABLE_OVERLOADING
data VideoMetaMapMethodInfo
instance (signature ~ (Word32 -> Gst.MapInfo.MapInfo -> [Gst.Flags.MapFlags] -> m ((Bool, Ptr (), Int32))), MonadIO m) => O.MethodInfo VideoMetaMapMethodInfo VideoMeta signature where
    overloadedMethod _ = videoMetaMap

#endif

-- method VideoMeta::unmap
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "meta", argType = TInterface (Name {namespace = "GstVideo", name = "VideoMeta"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstVideoMeta", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "plane", argType = TBasicType TUInt, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a plane", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "info", argType = TInterface (Name {namespace = "Gst", name = "MapInfo"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstMapInfo", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gst_video_meta_unmap" gst_video_meta_unmap ::
    Ptr VideoMeta ->                        -- meta : TInterface (Name {namespace = "GstVideo", name = "VideoMeta"})
    Word32 ->                               -- plane : TBasicType TUInt
    Ptr Gst.MapInfo.MapInfo ->              -- info : TInterface (Name {namespace = "Gst", name = "MapInfo"})
    IO CInt

{- |
Unmap a previously mapped plane with 'GI.GstVideo.Structs.VideoMeta.videoMetaMap'.
-}
videoMetaUnmap ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    VideoMeta
    {- ^ /@meta@/: a 'GI.GstVideo.Structs.VideoMeta.VideoMeta' -}
    -> Word32
    {- ^ /@plane@/: a plane -}
    -> Gst.MapInfo.MapInfo
    {- ^ /@info@/: a 'GI.Gst.Structs.MapInfo.MapInfo' -}
    -> m Bool
    {- ^ __Returns:__ TRUE if the memory was successfully unmapped. -}
videoMetaUnmap meta plane info = liftIO $ do
    meta' <- unsafeManagedPtrGetPtr meta
    info' <- unsafeManagedPtrGetPtr info
    result <- gst_video_meta_unmap meta' plane info'
    let result' = (/= 0) result
    touchManagedPtr meta
    touchManagedPtr info
    return result'

#if ENABLE_OVERLOADING
data VideoMetaUnmapMethodInfo
instance (signature ~ (Word32 -> Gst.MapInfo.MapInfo -> m Bool), MonadIO m) => O.MethodInfo VideoMetaUnmapMethodInfo VideoMeta signature where
    overloadedMethod _ = videoMetaUnmap

#endif

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

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

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

#if ENABLE_OVERLOADING
#endif

#if ENABLE_OVERLOADING
type family ResolveVideoMetaMethod (t :: Symbol) (o :: *) :: * where
    ResolveVideoMetaMethod "map" o = VideoMetaMapMethodInfo
    ResolveVideoMetaMethod "unmap" o = VideoMetaUnmapMethodInfo
    ResolveVideoMetaMethod l o = O.MethodResolutionFailed l o

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