{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Extra buffer metadata providing Closed Caption.
-- 
-- /Since: 1.16/

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

module GI.GstVideo.Structs.VideoCaptionMeta
    ( 

-- * Exported types
    VideoCaptionMeta(..)                    ,
    newZeroVideoCaptionMeta                 ,


 -- * Methods
-- ** Overloaded methods #method:Overloaded methods#

#if defined(ENABLE_OVERLOADING)
    ResolveVideoCaptionMetaMethod           ,
#endif


-- ** getInfo #method:getInfo#

    videoCaptionMetaGetInfo                 ,




 -- * Properties
-- ** captionType #attr:captionType#
-- | The type of Closed Caption contained in the meta.

    getVideoCaptionMetaCaptionType          ,
    setVideoCaptionMetaCaptionType          ,
#if defined(ENABLE_OVERLOADING)
    videoCaptionMeta_captionType            ,
#endif


-- ** meta #attr:meta#
-- | parent t'GI.Gst.Structs.Meta.Meta'

    getVideoCaptionMetaMeta                 ,
#if defined(ENABLE_OVERLOADING)
    videoCaptionMeta_meta                   ,
#endif


-- ** size #attr:size#
-- | The size in bytes of /@data@/

    getVideoCaptionMetaSize                 ,
    setVideoCaptionMetaSize                 ,
#if defined(ENABLE_OVERLOADING)
    videoCaptionMeta_size                   ,
#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.BasicTypes as B.Types
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 Control.Monad.IO.Class as MIO
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.GstVideo.Enums as GstVideo.Enums

-- | Memory-managed wrapper type.
newtype VideoCaptionMeta = VideoCaptionMeta (SP.ManagedPtr VideoCaptionMeta)
    deriving (VideoCaptionMeta -> VideoCaptionMeta -> Bool
(VideoCaptionMeta -> VideoCaptionMeta -> Bool)
-> (VideoCaptionMeta -> VideoCaptionMeta -> Bool)
-> Eq VideoCaptionMeta
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VideoCaptionMeta -> VideoCaptionMeta -> Bool
$c/= :: VideoCaptionMeta -> VideoCaptionMeta -> Bool
== :: VideoCaptionMeta -> VideoCaptionMeta -> Bool
$c== :: VideoCaptionMeta -> VideoCaptionMeta -> Bool
Eq)

instance SP.ManagedPtrNewtype VideoCaptionMeta where
    toManagedPtr :: VideoCaptionMeta -> ManagedPtr VideoCaptionMeta
toManagedPtr (VideoCaptionMeta ManagedPtr VideoCaptionMeta
p) = ManagedPtr VideoCaptionMeta
p

instance BoxedPtr VideoCaptionMeta where
    boxedPtrCopy :: VideoCaptionMeta -> IO VideoCaptionMeta
boxedPtrCopy = \VideoCaptionMeta
p -> VideoCaptionMeta
-> (Ptr VideoCaptionMeta -> IO VideoCaptionMeta)
-> IO VideoCaptionMeta
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr VideoCaptionMeta
p (Int -> Ptr VideoCaptionMeta -> IO (Ptr VideoCaptionMeta)
forall a. (HasCallStack, CallocPtr a) => Int -> Ptr a -> IO (Ptr a)
copyBytes Int
40 (Ptr VideoCaptionMeta -> IO (Ptr VideoCaptionMeta))
-> (Ptr VideoCaptionMeta -> IO VideoCaptionMeta)
-> Ptr VideoCaptionMeta
-> IO VideoCaptionMeta
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (ManagedPtr VideoCaptionMeta -> VideoCaptionMeta)
-> Ptr VideoCaptionMeta -> IO VideoCaptionMeta
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.wrapPtr ManagedPtr VideoCaptionMeta -> VideoCaptionMeta
VideoCaptionMeta)
    boxedPtrFree :: VideoCaptionMeta -> IO ()
boxedPtrFree = \VideoCaptionMeta
x -> VideoCaptionMeta -> (Ptr VideoCaptionMeta -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
SP.withManagedPtr VideoCaptionMeta
x Ptr VideoCaptionMeta -> IO ()
forall a. Ptr a -> IO ()
SP.freeMem
instance CallocPtr VideoCaptionMeta where
    boxedPtrCalloc :: IO (Ptr VideoCaptionMeta)
boxedPtrCalloc = Int -> IO (Ptr VideoCaptionMeta)
forall a. Int -> IO (Ptr a)
callocBytes Int
40


-- | Construct a `VideoCaptionMeta` struct initialized to zero.
newZeroVideoCaptionMeta :: MonadIO m => m VideoCaptionMeta
newZeroVideoCaptionMeta :: m VideoCaptionMeta
newZeroVideoCaptionMeta = IO VideoCaptionMeta -> m VideoCaptionMeta
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO VideoCaptionMeta -> m VideoCaptionMeta)
-> IO VideoCaptionMeta -> m VideoCaptionMeta
forall a b. (a -> b) -> a -> b
$ IO (Ptr VideoCaptionMeta)
forall a. CallocPtr a => IO (Ptr a)
boxedPtrCalloc IO (Ptr VideoCaptionMeta)
-> (Ptr VideoCaptionMeta -> IO VideoCaptionMeta)
-> IO VideoCaptionMeta
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr VideoCaptionMeta -> VideoCaptionMeta)
-> Ptr VideoCaptionMeta -> IO VideoCaptionMeta
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr VideoCaptionMeta -> VideoCaptionMeta
VideoCaptionMeta

instance tag ~ 'AttrSet => Constructible VideoCaptionMeta tag where
    new :: (ManagedPtr VideoCaptionMeta -> VideoCaptionMeta)
-> [AttrOp VideoCaptionMeta tag] -> m VideoCaptionMeta
new ManagedPtr VideoCaptionMeta -> VideoCaptionMeta
_ [AttrOp VideoCaptionMeta tag]
attrs = do
        VideoCaptionMeta
o <- m VideoCaptionMeta
forall (m :: * -> *). MonadIO m => m VideoCaptionMeta
newZeroVideoCaptionMeta
        VideoCaptionMeta -> [AttrOp VideoCaptionMeta 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set VideoCaptionMeta
o [AttrOp VideoCaptionMeta tag]
[AttrOp VideoCaptionMeta 'AttrSet]
attrs
        VideoCaptionMeta -> m VideoCaptionMeta
forall (m :: * -> *) a. Monad m => a -> m a
return VideoCaptionMeta
o


-- | 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' videoCaptionMeta #meta
-- @
getVideoCaptionMetaMeta :: MonadIO m => VideoCaptionMeta -> m Gst.Meta.Meta
getVideoCaptionMetaMeta :: VideoCaptionMeta -> m Meta
getVideoCaptionMetaMeta VideoCaptionMeta
s = IO Meta -> m Meta
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Meta -> m Meta) -> IO Meta -> m Meta
forall a b. (a -> b) -> a -> b
$ VideoCaptionMeta -> (Ptr VideoCaptionMeta -> IO Meta) -> IO Meta
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr VideoCaptionMeta
s ((Ptr VideoCaptionMeta -> IO Meta) -> IO Meta)
-> (Ptr VideoCaptionMeta -> IO Meta) -> IO Meta
forall a b. (a -> b) -> a -> b
$ \Ptr VideoCaptionMeta
ptr -> do
    let val :: Ptr Meta
val = Ptr VideoCaptionMeta
ptr Ptr VideoCaptionMeta -> Int -> Ptr Meta
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: (Ptr Gst.Meta.Meta)
    Meta
val' <- ((ManagedPtr Meta -> Meta) -> Ptr Meta -> IO Meta
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr Meta -> Meta
Gst.Meta.Meta) Ptr Meta
val
    Meta -> IO Meta
forall (m :: * -> *) a. Monad m => a -> m a
return Meta
val'

#if defined(ENABLE_OVERLOADING)
data VideoCaptionMetaMetaFieldInfo
instance AttrInfo VideoCaptionMetaMetaFieldInfo where
    type AttrBaseTypeConstraint VideoCaptionMetaMetaFieldInfo = (~) VideoCaptionMeta
    type AttrAllowedOps VideoCaptionMetaMetaFieldInfo = '[ 'AttrGet]
    type AttrSetTypeConstraint VideoCaptionMetaMetaFieldInfo = (~) (Ptr Gst.Meta.Meta)
    type AttrTransferTypeConstraint VideoCaptionMetaMetaFieldInfo = (~)(Ptr Gst.Meta.Meta)
    type AttrTransferType VideoCaptionMetaMetaFieldInfo = (Ptr Gst.Meta.Meta)
    type AttrGetType VideoCaptionMetaMetaFieldInfo = Gst.Meta.Meta
    type AttrLabel VideoCaptionMetaMetaFieldInfo = "meta"
    type AttrOrigin VideoCaptionMetaMetaFieldInfo = VideoCaptionMeta
    attrGet = getVideoCaptionMetaMeta
    attrSet = undefined
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer = undefined

videoCaptionMeta_meta :: AttrLabelProxy "meta"
videoCaptionMeta_meta = AttrLabelProxy

#endif


-- | Get the value of the “@caption_type@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' videoCaptionMeta #captionType
-- @
getVideoCaptionMetaCaptionType :: MonadIO m => VideoCaptionMeta -> m GstVideo.Enums.VideoCaptionType
getVideoCaptionMetaCaptionType :: VideoCaptionMeta -> m VideoCaptionType
getVideoCaptionMetaCaptionType VideoCaptionMeta
s = IO VideoCaptionType -> m VideoCaptionType
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO VideoCaptionType -> m VideoCaptionType)
-> IO VideoCaptionType -> m VideoCaptionType
forall a b. (a -> b) -> a -> b
$ VideoCaptionMeta
-> (Ptr VideoCaptionMeta -> IO VideoCaptionType)
-> IO VideoCaptionType
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr VideoCaptionMeta
s ((Ptr VideoCaptionMeta -> IO VideoCaptionType)
 -> IO VideoCaptionType)
-> (Ptr VideoCaptionMeta -> IO VideoCaptionType)
-> IO VideoCaptionType
forall a b. (a -> b) -> a -> b
$ \Ptr VideoCaptionMeta
ptr -> do
    CUInt
val <- Ptr CUInt -> IO CUInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr VideoCaptionMeta
ptr Ptr VideoCaptionMeta -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) :: IO CUInt
    let val' :: VideoCaptionType
val' = (Int -> VideoCaptionType
forall a. Enum a => Int -> a
toEnum (Int -> VideoCaptionType)
-> (CUInt -> Int) -> CUInt -> VideoCaptionType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
val
    VideoCaptionType -> IO VideoCaptionType
forall (m :: * -> *) a. Monad m => a -> m a
return VideoCaptionType
val'

-- | Set the value of the “@caption_type@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' videoCaptionMeta [ #captionType 'Data.GI.Base.Attributes.:=' value ]
-- @
setVideoCaptionMetaCaptionType :: MonadIO m => VideoCaptionMeta -> GstVideo.Enums.VideoCaptionType -> m ()
setVideoCaptionMetaCaptionType :: VideoCaptionMeta -> VideoCaptionType -> m ()
setVideoCaptionMetaCaptionType VideoCaptionMeta
s VideoCaptionType
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ VideoCaptionMeta -> (Ptr VideoCaptionMeta -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr VideoCaptionMeta
s ((Ptr VideoCaptionMeta -> IO ()) -> IO ())
-> (Ptr VideoCaptionMeta -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr VideoCaptionMeta
ptr -> do
    let val' :: CUInt
val' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (VideoCaptionType -> Int) -> VideoCaptionType -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VideoCaptionType -> Int
forall a. Enum a => a -> Int
fromEnum) VideoCaptionType
val
    Ptr CUInt -> CUInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr VideoCaptionMeta
ptr Ptr VideoCaptionMeta -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) (CUInt
val' :: CUInt)

#if defined(ENABLE_OVERLOADING)
data VideoCaptionMetaCaptionTypeFieldInfo
instance AttrInfo VideoCaptionMetaCaptionTypeFieldInfo where
    type AttrBaseTypeConstraint VideoCaptionMetaCaptionTypeFieldInfo = (~) VideoCaptionMeta
    type AttrAllowedOps VideoCaptionMetaCaptionTypeFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint VideoCaptionMetaCaptionTypeFieldInfo = (~) GstVideo.Enums.VideoCaptionType
    type AttrTransferTypeConstraint VideoCaptionMetaCaptionTypeFieldInfo = (~)GstVideo.Enums.VideoCaptionType
    type AttrTransferType VideoCaptionMetaCaptionTypeFieldInfo = GstVideo.Enums.VideoCaptionType
    type AttrGetType VideoCaptionMetaCaptionTypeFieldInfo = GstVideo.Enums.VideoCaptionType
    type AttrLabel VideoCaptionMetaCaptionTypeFieldInfo = "caption_type"
    type AttrOrigin VideoCaptionMetaCaptionTypeFieldInfo = VideoCaptionMeta
    attrGet = getVideoCaptionMetaCaptionType
    attrSet = setVideoCaptionMetaCaptionType
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

videoCaptionMeta_captionType :: AttrLabelProxy "captionType"
videoCaptionMeta_captionType = AttrLabelProxy

#endif


-- XXX Skipped attribute for "VideoCaptionMeta:data"
-- Not implemented: Don't know how to unpack C array of type TCArray False (-1) 3 (TBasicType TUInt8)
-- | Get the value of the “@size@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' videoCaptionMeta #size
-- @
getVideoCaptionMetaSize :: MonadIO m => VideoCaptionMeta -> m Word64
getVideoCaptionMetaSize :: VideoCaptionMeta -> m Word64
getVideoCaptionMetaSize VideoCaptionMeta
s = 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
$ VideoCaptionMeta
-> (Ptr VideoCaptionMeta -> IO Word64) -> IO Word64
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr VideoCaptionMeta
s ((Ptr VideoCaptionMeta -> IO Word64) -> IO Word64)
-> (Ptr VideoCaptionMeta -> IO Word64) -> IO Word64
forall a b. (a -> b) -> a -> b
$ \Ptr VideoCaptionMeta
ptr -> do
    Word64
val <- Ptr Word64 -> IO Word64
forall a. Storable a => Ptr a -> IO a
peek (Ptr VideoCaptionMeta
ptr Ptr VideoCaptionMeta -> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32) :: IO Word64
    Word64 -> IO Word64
forall (m :: * -> *) a. Monad m => a -> m a
return Word64
val

-- | Set the value of the “@size@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' videoCaptionMeta [ #size 'Data.GI.Base.Attributes.:=' value ]
-- @
setVideoCaptionMetaSize :: MonadIO m => VideoCaptionMeta -> Word64 -> m ()
setVideoCaptionMetaSize :: VideoCaptionMeta -> Word64 -> m ()
setVideoCaptionMetaSize VideoCaptionMeta
s Word64
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ VideoCaptionMeta -> (Ptr VideoCaptionMeta -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr VideoCaptionMeta
s ((Ptr VideoCaptionMeta -> IO ()) -> IO ())
-> (Ptr VideoCaptionMeta -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr VideoCaptionMeta
ptr -> do
    Ptr Word64 -> Word64 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr VideoCaptionMeta
ptr Ptr VideoCaptionMeta -> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32) (Word64
val :: Word64)

#if defined(ENABLE_OVERLOADING)
data VideoCaptionMetaSizeFieldInfo
instance AttrInfo VideoCaptionMetaSizeFieldInfo where
    type AttrBaseTypeConstraint VideoCaptionMetaSizeFieldInfo = (~) VideoCaptionMeta
    type AttrAllowedOps VideoCaptionMetaSizeFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint VideoCaptionMetaSizeFieldInfo = (~) Word64
    type AttrTransferTypeConstraint VideoCaptionMetaSizeFieldInfo = (~)Word64
    type AttrTransferType VideoCaptionMetaSizeFieldInfo = Word64
    type AttrGetType VideoCaptionMetaSizeFieldInfo = Word64
    type AttrLabel VideoCaptionMetaSizeFieldInfo = "size"
    type AttrOrigin VideoCaptionMetaSizeFieldInfo = VideoCaptionMeta
    attrGet = getVideoCaptionMetaSize
    attrSet = setVideoCaptionMetaSize
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

videoCaptionMeta_size :: AttrLabelProxy "size"
videoCaptionMeta_size = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList VideoCaptionMeta
type instance O.AttributeList VideoCaptionMeta = VideoCaptionMetaAttributeList
type VideoCaptionMetaAttributeList = ('[ '("meta", VideoCaptionMetaMetaFieldInfo), '("captionType", VideoCaptionMetaCaptionTypeFieldInfo), '("size", VideoCaptionMetaSizeFieldInfo)] :: [(Symbol, *)])
#endif

-- method VideoCaptionMeta::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_caption_meta_get_info" gst_video_caption_meta_get_info :: 
    IO (Ptr Gst.MetaInfo.MetaInfo)

-- | /No description available in the introspection data./
videoCaptionMetaGetInfo ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m Gst.MetaInfo.MetaInfo
videoCaptionMetaGetInfo :: m MetaInfo
videoCaptionMetaGetInfo  = IO MetaInfo -> m MetaInfo
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO MetaInfo -> m MetaInfo) -> IO MetaInfo -> m MetaInfo
forall a b. (a -> b) -> a -> b
$ do
    Ptr MetaInfo
result <- IO (Ptr MetaInfo)
gst_video_caption_meta_get_info
    Text -> Ptr MetaInfo -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"videoCaptionMetaGetInfo" Ptr MetaInfo
result
    MetaInfo
result' <- ((ManagedPtr MetaInfo -> MetaInfo) -> Ptr MetaInfo -> IO MetaInfo
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr MetaInfo -> MetaInfo
Gst.MetaInfo.MetaInfo) Ptr MetaInfo
result
    MetaInfo -> IO MetaInfo
forall (m :: * -> *) a. Monad m => a -> m a
return MetaInfo
result'

#if defined(ENABLE_OVERLOADING)
#endif

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

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

#endif