{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.GstVideo.Structs.VideoCaptionMeta
(
VideoCaptionMeta(..) ,
newZeroVideoCaptionMeta ,
#if defined(ENABLE_OVERLOADING)
ResolveVideoCaptionMetaMethod ,
#endif
videoCaptionMetaGetInfo ,
getVideoCaptionMetaCaptionType ,
setVideoCaptionMetaCaptionType ,
#if defined(ENABLE_OVERLOADING)
videoCaptionMeta_captionType ,
#endif
getVideoCaptionMetaMeta ,
#if defined(ENABLE_OVERLOADING)
videoCaptionMeta_meta ,
#endif
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.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)
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
#else
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
#endif
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
$c== :: VideoCaptionMeta -> VideoCaptionMeta -> Bool
== :: VideoCaptionMeta -> VideoCaptionMeta -> Bool
$c/= :: VideoCaptionMeta -> VideoCaptionMeta -> Bool
/= :: 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
newZeroVideoCaptionMeta :: MonadIO m => m VideoCaptionMeta
newZeroVideoCaptionMeta :: forall (m :: * -> *). MonadIO m => m VideoCaptionMeta
newZeroVideoCaptionMeta = IO VideoCaptionMeta -> m VideoCaptionMeta
forall a. IO a -> m a
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 a b. IO a -> (a -> IO b) -> IO b
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 :: forall (m :: * -> *).
MonadIO m =>
(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 a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return VideoCaptionMeta
o
getVideoCaptionMetaMeta :: MonadIO m => VideoCaptionMeta -> m Gst.Meta.Meta
getVideoCaptionMetaMeta :: forall (m :: * -> *). MonadIO m => VideoCaptionMeta -> m Meta
getVideoCaptionMetaMeta VideoCaptionMeta
s = IO Meta -> m Meta
forall a. IO a -> m a
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 a. a -> IO a
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
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GstVideo.Structs.VideoCaptionMeta.meta"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gstvideo-1.0.29/docs/GI-GstVideo-Structs-VideoCaptionMeta.html#g:attr:meta"
})
videoCaptionMeta_meta :: AttrLabelProxy "meta"
videoCaptionMeta_meta = AttrLabelProxy
#endif
getVideoCaptionMetaCaptionType :: MonadIO m => VideoCaptionMeta -> m GstVideo.Enums.VideoCaptionType
getVideoCaptionMetaCaptionType :: forall (m :: * -> *).
MonadIO m =>
VideoCaptionMeta -> m VideoCaptionType
getVideoCaptionMetaCaptionType VideoCaptionMeta
s = IO VideoCaptionType -> m VideoCaptionType
forall a. IO a -> m a
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return VideoCaptionType
val'
setVideoCaptionMetaCaptionType :: MonadIO m => VideoCaptionMeta -> GstVideo.Enums.VideoCaptionType -> m ()
setVideoCaptionMetaCaptionType :: forall (m :: * -> *).
MonadIO m =>
VideoCaptionMeta -> VideoCaptionType -> m ()
setVideoCaptionMetaCaptionType VideoCaptionMeta
s VideoCaptionType
val = 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
$ 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
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GstVideo.Structs.VideoCaptionMeta.captionType"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gstvideo-1.0.29/docs/GI-GstVideo-Structs-VideoCaptionMeta.html#g:attr:captionType"
})
videoCaptionMeta_captionType :: AttrLabelProxy "captionType"
videoCaptionMeta_captionType = AttrLabelProxy
#endif
getVideoCaptionMetaSize :: MonadIO m => VideoCaptionMeta -> m FCT.CSize
getVideoCaptionMetaSize :: forall (m :: * -> *). MonadIO m => VideoCaptionMeta -> m CSize
getVideoCaptionMetaSize VideoCaptionMeta
s = IO CSize -> m CSize
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CSize -> m CSize) -> IO CSize -> m CSize
forall a b. (a -> b) -> a -> b
$ VideoCaptionMeta -> (Ptr VideoCaptionMeta -> IO CSize) -> IO CSize
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr VideoCaptionMeta
s ((Ptr VideoCaptionMeta -> IO CSize) -> IO CSize)
-> (Ptr VideoCaptionMeta -> IO CSize) -> IO CSize
forall a b. (a -> b) -> a -> b
$ \Ptr VideoCaptionMeta
ptr -> do
CSize
val <- Ptr CSize -> IO CSize
forall a. Storable a => Ptr a -> IO a
peek (Ptr VideoCaptionMeta
ptr Ptr VideoCaptionMeta -> Int -> Ptr CSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32) :: IO FCT.CSize
CSize -> IO CSize
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CSize
val
setVideoCaptionMetaSize :: MonadIO m => VideoCaptionMeta -> FCT.CSize -> m ()
setVideoCaptionMetaSize :: forall (m :: * -> *).
MonadIO m =>
VideoCaptionMeta -> CSize -> m ()
setVideoCaptionMetaSize VideoCaptionMeta
s CSize
val = 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
$ 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 CSize -> CSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr VideoCaptionMeta
ptr Ptr VideoCaptionMeta -> Int -> Ptr CSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32) (CSize
val :: FCT.CSize)
#if defined(ENABLE_OVERLOADING)
data VideoCaptionMetaSizeFieldInfo
instance AttrInfo VideoCaptionMetaSizeFieldInfo where
type AttrBaseTypeConstraint VideoCaptionMetaSizeFieldInfo = (~) VideoCaptionMeta
type AttrAllowedOps VideoCaptionMetaSizeFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint VideoCaptionMetaSizeFieldInfo = (~) FCT.CSize
type AttrTransferTypeConstraint VideoCaptionMetaSizeFieldInfo = (~)FCT.CSize
type AttrTransferType VideoCaptionMetaSizeFieldInfo = FCT.CSize
type AttrGetType VideoCaptionMetaSizeFieldInfo = FCT.CSize
type AttrLabel VideoCaptionMetaSizeFieldInfo = "size"
type AttrOrigin VideoCaptionMetaSizeFieldInfo = VideoCaptionMeta
attrGet = getVideoCaptionMetaSize
attrSet = setVideoCaptionMetaSize
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GstVideo.Structs.VideoCaptionMeta.size"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gstvideo-1.0.29/docs/GI-GstVideo-Structs-VideoCaptionMeta.html#g:attr:size"
})
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, DK.Type)])
#endif
foreign import ccall "gst_video_caption_meta_get_info" gst_video_caption_meta_get_info ::
IO (Ptr Gst.MetaInfo.MetaInfo)
videoCaptionMetaGetInfo ::
(B.CallStack.HasCallStack, MonadIO m) =>
m Gst.MetaInfo.MetaInfo
videoCaptionMetaGetInfo :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m MetaInfo
videoCaptionMetaGetInfo = IO MetaInfo -> m MetaInfo
forall a. IO a -> m a
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 a. a -> IO a
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 :: DK.Type) :: DK.Type where
ResolveVideoCaptionMetaMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveVideoCaptionMetaMethod t VideoCaptionMeta, O.OverloadedMethod 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
#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveVideoCaptionMetaMethod t VideoCaptionMeta, O.OverloadedMethod info VideoCaptionMeta p, R.HasField t VideoCaptionMeta p) => R.HasField t VideoCaptionMeta p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveVideoCaptionMetaMethod t VideoCaptionMeta, O.OverloadedMethodInfo info VideoCaptionMeta) => OL.IsLabel t (O.MethodProxy info VideoCaptionMeta) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif