{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gst.Structs.MetaInfo
    ( 
    MetaInfo(..)                            ,
    newZeroMetaInfo                         ,
 
#if defined(ENABLE_OVERLOADING)
    ResolveMetaInfoMethod                   ,
#endif
#if defined(ENABLE_OVERLOADING)
    MetaInfoIsCustomMethodInfo              ,
#endif
    metaInfoIsCustom                        ,
 
    getMetaInfoApi                          ,
#if defined(ENABLE_OVERLOADING)
    metaInfo_api                            ,
#endif
    setMetaInfoApi                          ,
    clearMetaInfoFreeFunc                   ,
    getMetaInfoFreeFunc                     ,
#if defined(ENABLE_OVERLOADING)
    metaInfo_freeFunc                       ,
#endif
    setMetaInfoFreeFunc                     ,
    clearMetaInfoInitFunc                   ,
    getMetaInfoInitFunc                     ,
#if defined(ENABLE_OVERLOADING)
    metaInfo_initFunc                       ,
#endif
    setMetaInfoInitFunc                     ,
    getMetaInfoSize                         ,
#if defined(ENABLE_OVERLOADING)
    metaInfo_size                           ,
#endif
    setMetaInfoSize                         ,
    clearMetaInfoTransformFunc              ,
    getMetaInfoTransformFunc                ,
#if defined(ENABLE_OVERLOADING)
    metaInfo_transformFunc                  ,
#endif
    setMetaInfoTransformFunc                ,
    getMetaInfoType                         ,
#if defined(ENABLE_OVERLOADING)
    metaInfo_type                           ,
#endif
    setMetaInfoType                         ,
    ) 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 GI.Gst.Callbacks as Gst.Callbacks
newtype MetaInfo = MetaInfo (SP.ManagedPtr MetaInfo)
    deriving (MetaInfo -> MetaInfo -> Bool
(MetaInfo -> MetaInfo -> Bool)
-> (MetaInfo -> MetaInfo -> Bool) -> Eq MetaInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: MetaInfo -> MetaInfo -> Bool
== :: MetaInfo -> MetaInfo -> Bool
$c/= :: MetaInfo -> MetaInfo -> Bool
/= :: MetaInfo -> MetaInfo -> Bool
Eq)
instance SP.ManagedPtrNewtype MetaInfo where
    toManagedPtr :: MetaInfo -> ManagedPtr MetaInfo
toManagedPtr (MetaInfo ManagedPtr MetaInfo
p) = ManagedPtr MetaInfo
p
instance BoxedPtr MetaInfo where
    boxedPtrCopy :: MetaInfo -> IO MetaInfo
boxedPtrCopy = \MetaInfo
p -> MetaInfo -> (Ptr MetaInfo -> IO MetaInfo) -> IO MetaInfo
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr MetaInfo
p (Int -> Ptr MetaInfo -> IO (Ptr MetaInfo)
forall a. (HasCallStack, CallocPtr a) => Int -> Ptr a -> IO (Ptr a)
copyBytes Int
48 (Ptr MetaInfo -> IO (Ptr MetaInfo))
-> (Ptr MetaInfo -> IO MetaInfo) -> Ptr MetaInfo -> IO MetaInfo
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (ManagedPtr MetaInfo -> MetaInfo) -> Ptr MetaInfo -> IO MetaInfo
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.wrapPtr ManagedPtr MetaInfo -> MetaInfo
MetaInfo)
    boxedPtrFree :: MetaInfo -> IO ()
boxedPtrFree = \MetaInfo
x -> MetaInfo -> (Ptr MetaInfo -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
SP.withManagedPtr MetaInfo
x Ptr MetaInfo -> IO ()
forall a. Ptr a -> IO ()
SP.freeMem
instance CallocPtr MetaInfo where
    boxedPtrCalloc :: IO (Ptr MetaInfo)
boxedPtrCalloc = Int -> IO (Ptr MetaInfo)
forall a. Int -> IO (Ptr a)
callocBytes Int
48
newZeroMetaInfo :: MonadIO m => m MetaInfo
newZeroMetaInfo :: forall (m :: * -> *). MonadIO m => m MetaInfo
newZeroMetaInfo = 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
$ IO (Ptr MetaInfo)
forall a. CallocPtr a => IO (Ptr a)
boxedPtrCalloc IO (Ptr MetaInfo) -> (Ptr MetaInfo -> IO MetaInfo) -> IO MetaInfo
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr MetaInfo -> MetaInfo) -> Ptr MetaInfo -> IO MetaInfo
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr MetaInfo -> MetaInfo
MetaInfo
instance tag ~ 'AttrSet => Constructible MetaInfo tag where
    new :: forall (m :: * -> *).
MonadIO m =>
(ManagedPtr MetaInfo -> MetaInfo)
-> [AttrOp MetaInfo tag] -> m MetaInfo
new ManagedPtr MetaInfo -> MetaInfo
_ [AttrOp MetaInfo tag]
attrs = do
        MetaInfo
o <- m MetaInfo
forall (m :: * -> *). MonadIO m => m MetaInfo
newZeroMetaInfo
        MetaInfo -> [AttrOp MetaInfo 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set MetaInfo
o [AttrOp MetaInfo tag]
[AttrOp MetaInfo 'AttrSet]
attrs
        MetaInfo -> m MetaInfo
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return MetaInfo
o
getMetaInfoApi :: MonadIO m => MetaInfo -> m GType
getMetaInfoApi :: forall (m :: * -> *). MonadIO m => MetaInfo -> m GType
getMetaInfoApi MetaInfo
s = IO GType -> m GType
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO GType -> m GType) -> IO GType -> m GType
forall a b. (a -> b) -> a -> b
$ MetaInfo -> (Ptr MetaInfo -> IO GType) -> IO GType
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr MetaInfo
s ((Ptr MetaInfo -> IO GType) -> IO GType)
-> (Ptr MetaInfo -> IO GType) -> IO GType
forall a b. (a -> b) -> a -> b
$ \Ptr MetaInfo
ptr -> do
    CGType
val <- Ptr CGType -> IO CGType
forall a. Storable a => Ptr a -> IO a
peek (Ptr MetaInfo
ptr Ptr MetaInfo -> Int -> Ptr CGType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) :: IO CGType
    let val' :: GType
val' = CGType -> GType
GType CGType
val
    GType -> IO GType
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return GType
val'
setMetaInfoApi :: MonadIO m => MetaInfo -> GType -> m ()
setMetaInfoApi :: forall (m :: * -> *). MonadIO m => MetaInfo -> GType -> m ()
setMetaInfoApi MetaInfo
s GType
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
$ MetaInfo -> (Ptr MetaInfo -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr MetaInfo
s ((Ptr MetaInfo -> IO ()) -> IO ())
-> (Ptr MetaInfo -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr MetaInfo
ptr -> do
    let val' :: CGType
val' = GType -> CGType
gtypeToCGType GType
val
    Ptr CGType -> CGType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr MetaInfo
ptr Ptr MetaInfo -> Int -> Ptr CGType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) (CGType
val' :: CGType)
#if defined(ENABLE_OVERLOADING)
data MetaInfoApiFieldInfo
instance AttrInfo MetaInfoApiFieldInfo where
    type AttrBaseTypeConstraint MetaInfoApiFieldInfo = (~) MetaInfo
    type AttrAllowedOps MetaInfoApiFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint MetaInfoApiFieldInfo = (~) GType
    type AttrTransferTypeConstraint MetaInfoApiFieldInfo = (~)GType
    type AttrTransferType MetaInfoApiFieldInfo = GType
    type AttrGetType MetaInfoApiFieldInfo = GType
    type AttrLabel MetaInfoApiFieldInfo = "api"
    type AttrOrigin MetaInfoApiFieldInfo = MetaInfo
    attrGet = getMetaInfoApi
    attrSet = setMetaInfoApi
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gst.Structs.MetaInfo.api"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gst-1.0.28/docs/GI-Gst-Structs-MetaInfo.html#g:attr:api"
        })
metaInfo_api :: AttrLabelProxy "api"
metaInfo_api = AttrLabelProxy
#endif
getMetaInfoType :: MonadIO m => MetaInfo -> m GType
getMetaInfoType :: forall (m :: * -> *). MonadIO m => MetaInfo -> m GType
getMetaInfoType MetaInfo
s = IO GType -> m GType
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO GType -> m GType) -> IO GType -> m GType
forall a b. (a -> b) -> a -> b
$ MetaInfo -> (Ptr MetaInfo -> IO GType) -> IO GType
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr MetaInfo
s ((Ptr MetaInfo -> IO GType) -> IO GType)
-> (Ptr MetaInfo -> IO GType) -> IO GType
forall a b. (a -> b) -> a -> b
$ \Ptr MetaInfo
ptr -> do
    CGType
val <- Ptr CGType -> IO CGType
forall a. Storable a => Ptr a -> IO a
peek (Ptr MetaInfo
ptr Ptr MetaInfo -> Int -> Ptr CGType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) :: IO CGType
    let val' :: GType
val' = CGType -> GType
GType CGType
val
    GType -> IO GType
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return GType
val'
setMetaInfoType :: MonadIO m => MetaInfo -> GType -> m ()
setMetaInfoType :: forall (m :: * -> *). MonadIO m => MetaInfo -> GType -> m ()
setMetaInfoType MetaInfo
s GType
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
$ MetaInfo -> (Ptr MetaInfo -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr MetaInfo
s ((Ptr MetaInfo -> IO ()) -> IO ())
-> (Ptr MetaInfo -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr MetaInfo
ptr -> do
    let val' :: CGType
val' = GType -> CGType
gtypeToCGType GType
val
    Ptr CGType -> CGType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr MetaInfo
ptr Ptr MetaInfo -> Int -> Ptr CGType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) (CGType
val' :: CGType)
#if defined(ENABLE_OVERLOADING)
data MetaInfoTypeFieldInfo
instance AttrInfo MetaInfoTypeFieldInfo where
    type AttrBaseTypeConstraint MetaInfoTypeFieldInfo = (~) MetaInfo
    type AttrAllowedOps MetaInfoTypeFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint MetaInfoTypeFieldInfo = (~) GType
    type AttrTransferTypeConstraint MetaInfoTypeFieldInfo = (~)GType
    type AttrTransferType MetaInfoTypeFieldInfo = GType
    type AttrGetType MetaInfoTypeFieldInfo = GType
    type AttrLabel MetaInfoTypeFieldInfo = "type"
    type AttrOrigin MetaInfoTypeFieldInfo = MetaInfo
    attrGet = getMetaInfoType
    attrSet = setMetaInfoType
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gst.Structs.MetaInfo.type"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gst-1.0.28/docs/GI-Gst-Structs-MetaInfo.html#g:attr:type"
        })
metaInfo_type :: AttrLabelProxy "type"
metaInfo_type = AttrLabelProxy
#endif
getMetaInfoSize :: MonadIO m => MetaInfo -> m Word64
getMetaInfoSize :: forall (m :: * -> *). MonadIO m => MetaInfo -> m CGType
getMetaInfoSize MetaInfo
s = IO CGType -> m CGType
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CGType -> m CGType) -> IO CGType -> m CGType
forall a b. (a -> b) -> a -> b
$ MetaInfo -> (Ptr MetaInfo -> IO CGType) -> IO CGType
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr MetaInfo
s ((Ptr MetaInfo -> IO CGType) -> IO CGType)
-> (Ptr MetaInfo -> IO CGType) -> IO CGType
forall a b. (a -> b) -> a -> b
$ \Ptr MetaInfo
ptr -> do
    CGType
val <- Ptr CGType -> IO CGType
forall a. Storable a => Ptr a -> IO a
peek (Ptr MetaInfo
ptr Ptr MetaInfo -> Int -> Ptr CGType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) :: IO Word64
    CGType -> IO CGType
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CGType
val
setMetaInfoSize :: MonadIO m => MetaInfo -> Word64 -> m ()
setMetaInfoSize :: forall (m :: * -> *). MonadIO m => MetaInfo -> CGType -> m ()
setMetaInfoSize MetaInfo
s CGType
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
$ MetaInfo -> (Ptr MetaInfo -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr MetaInfo
s ((Ptr MetaInfo -> IO ()) -> IO ())
-> (Ptr MetaInfo -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr MetaInfo
ptr -> do
    Ptr CGType -> CGType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr MetaInfo
ptr Ptr MetaInfo -> Int -> Ptr CGType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) (CGType
val :: Word64)
#if defined(ENABLE_OVERLOADING)
data MetaInfoSizeFieldInfo
instance AttrInfo MetaInfoSizeFieldInfo where
    type AttrBaseTypeConstraint MetaInfoSizeFieldInfo = (~) MetaInfo
    type AttrAllowedOps MetaInfoSizeFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint MetaInfoSizeFieldInfo = (~) Word64
    type AttrTransferTypeConstraint MetaInfoSizeFieldInfo = (~)Word64
    type AttrTransferType MetaInfoSizeFieldInfo = Word64
    type AttrGetType MetaInfoSizeFieldInfo = Word64
    type AttrLabel MetaInfoSizeFieldInfo = "size"
    type AttrOrigin MetaInfoSizeFieldInfo = MetaInfo
    attrGet = getMetaInfoSize
    attrSet = setMetaInfoSize
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gst.Structs.MetaInfo.size"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gst-1.0.28/docs/GI-Gst-Structs-MetaInfo.html#g:attr:size"
        })
metaInfo_size :: AttrLabelProxy "size"
metaInfo_size = AttrLabelProxy
#endif
getMetaInfoInitFunc :: MonadIO m => MetaInfo -> m (Maybe Gst.Callbacks.MetaInitFunction)
getMetaInfoInitFunc :: forall (m :: * -> *).
MonadIO m =>
MetaInfo -> m (Maybe MetaInitFunction)
getMetaInfoInitFunc MetaInfo
s = IO (Maybe MetaInitFunction) -> m (Maybe MetaInitFunction)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe MetaInitFunction) -> m (Maybe MetaInitFunction))
-> IO (Maybe MetaInitFunction) -> m (Maybe MetaInitFunction)
forall a b. (a -> b) -> a -> b
$ MetaInfo
-> (Ptr MetaInfo -> IO (Maybe MetaInitFunction))
-> IO (Maybe MetaInitFunction)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr MetaInfo
s ((Ptr MetaInfo -> IO (Maybe MetaInitFunction))
 -> IO (Maybe MetaInitFunction))
-> (Ptr MetaInfo -> IO (Maybe MetaInitFunction))
-> IO (Maybe MetaInitFunction)
forall a b. (a -> b) -> a -> b
$ \Ptr MetaInfo
ptr -> do
    FunPtr C_MetaInitFunction
val <- Ptr (FunPtr C_MetaInitFunction) -> IO (FunPtr C_MetaInitFunction)
forall a. Storable a => Ptr a -> IO a
peek (Ptr MetaInfo
ptr Ptr MetaInfo -> Int -> Ptr (FunPtr C_MetaInitFunction)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24) :: IO (FunPtr Gst.Callbacks.C_MetaInitFunction)
    Maybe MetaInitFunction
result <- FunPtr C_MetaInitFunction
-> (FunPtr C_MetaInitFunction -> IO MetaInitFunction)
-> IO (Maybe MetaInitFunction)
forall a b. FunPtr a -> (FunPtr a -> IO b) -> IO (Maybe b)
SP.convertFunPtrIfNonNull FunPtr C_MetaInitFunction
val ((FunPtr C_MetaInitFunction -> IO MetaInitFunction)
 -> IO (Maybe MetaInitFunction))
-> (FunPtr C_MetaInitFunction -> IO MetaInitFunction)
-> IO (Maybe MetaInitFunction)
forall a b. (a -> b) -> a -> b
$ \FunPtr C_MetaInitFunction
val' -> do
        let val'' :: MetaInitFunction
val'' = FunPtr C_MetaInitFunction -> MetaInitFunction
forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
FunPtr C_MetaInitFunction -> Meta -> Ptr () -> Buffer -> m Bool
Gst.Callbacks.dynamic_MetaInitFunction FunPtr C_MetaInitFunction
val'
        MetaInitFunction -> IO MetaInitFunction
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return MetaInitFunction
val''
    Maybe MetaInitFunction -> IO (Maybe MetaInitFunction)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe MetaInitFunction
result
setMetaInfoInitFunc :: MonadIO m => MetaInfo -> FunPtr Gst.Callbacks.C_MetaInitFunction -> m ()
setMetaInfoInitFunc :: forall (m :: * -> *).
MonadIO m =>
MetaInfo -> FunPtr C_MetaInitFunction -> m ()
setMetaInfoInitFunc MetaInfo
s FunPtr C_MetaInitFunction
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
$ MetaInfo -> (Ptr MetaInfo -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr MetaInfo
s ((Ptr MetaInfo -> IO ()) -> IO ())
-> (Ptr MetaInfo -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr MetaInfo
ptr -> do
    Ptr (FunPtr C_MetaInitFunction)
-> FunPtr C_MetaInitFunction -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr MetaInfo
ptr Ptr MetaInfo -> Int -> Ptr (FunPtr C_MetaInitFunction)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24) (FunPtr C_MetaInitFunction
val :: FunPtr Gst.Callbacks.C_MetaInitFunction)
clearMetaInfoInitFunc :: MonadIO m => MetaInfo -> m ()
clearMetaInfoInitFunc :: forall (m :: * -> *). MonadIO m => MetaInfo -> m ()
clearMetaInfoInitFunc MetaInfo
s = 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
$ MetaInfo -> (Ptr MetaInfo -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr MetaInfo
s ((Ptr MetaInfo -> IO ()) -> IO ())
-> (Ptr MetaInfo -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr MetaInfo
ptr -> do
    Ptr (FunPtr C_MetaInitFunction)
-> FunPtr C_MetaInitFunction -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr MetaInfo
ptr Ptr MetaInfo -> Int -> Ptr (FunPtr C_MetaInitFunction)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24) (FunPtr C_MetaInitFunction
forall a. FunPtr a
FP.nullFunPtr :: FunPtr Gst.Callbacks.C_MetaInitFunction)
#if defined(ENABLE_OVERLOADING)
data MetaInfoInitFuncFieldInfo
instance AttrInfo MetaInfoInitFuncFieldInfo where
    type AttrBaseTypeConstraint MetaInfoInitFuncFieldInfo = (~) MetaInfo
    type AttrAllowedOps MetaInfoInitFuncFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint MetaInfoInitFuncFieldInfo = (~) (FunPtr Gst.Callbacks.C_MetaInitFunction)
    type AttrTransferTypeConstraint MetaInfoInitFuncFieldInfo = (~)Gst.Callbacks.MetaInitFunction
    type AttrTransferType MetaInfoInitFuncFieldInfo = (FunPtr Gst.Callbacks.C_MetaInitFunction)
    type AttrGetType MetaInfoInitFuncFieldInfo = Maybe Gst.Callbacks.MetaInitFunction
    type AttrLabel MetaInfoInitFuncFieldInfo = "init_func"
    type AttrOrigin MetaInfoInitFuncFieldInfo = MetaInfo
    attrGet = getMetaInfoInitFunc
    attrSet = setMetaInfoInitFunc
    attrConstruct = undefined
    attrClear = clearMetaInfoInitFunc
    attrTransfer _ v = do
        Gst.Callbacks.mk_MetaInitFunction (Gst.Callbacks.wrap_MetaInitFunction Nothing v)
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gst.Structs.MetaInfo.initFunc"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gst-1.0.28/docs/GI-Gst-Structs-MetaInfo.html#g:attr:initFunc"
        })
metaInfo_initFunc :: AttrLabelProxy "initFunc"
metaInfo_initFunc = AttrLabelProxy
#endif
getMetaInfoFreeFunc :: MonadIO m => MetaInfo -> m (Maybe Gst.Callbacks.MetaFreeFunction)
getMetaInfoFreeFunc :: forall (m :: * -> *).
MonadIO m =>
MetaInfo -> m (Maybe MetaFreeFunction)
getMetaInfoFreeFunc MetaInfo
s = IO (Maybe MetaFreeFunction) -> m (Maybe MetaFreeFunction)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe MetaFreeFunction) -> m (Maybe MetaFreeFunction))
-> IO (Maybe MetaFreeFunction) -> m (Maybe MetaFreeFunction)
forall a b. (a -> b) -> a -> b
$ MetaInfo
-> (Ptr MetaInfo -> IO (Maybe MetaFreeFunction))
-> IO (Maybe MetaFreeFunction)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr MetaInfo
s ((Ptr MetaInfo -> IO (Maybe MetaFreeFunction))
 -> IO (Maybe MetaFreeFunction))
-> (Ptr MetaInfo -> IO (Maybe MetaFreeFunction))
-> IO (Maybe MetaFreeFunction)
forall a b. (a -> b) -> a -> b
$ \Ptr MetaInfo
ptr -> do
    FunPtr C_MetaFreeFunction
val <- Ptr (FunPtr C_MetaFreeFunction) -> IO (FunPtr C_MetaFreeFunction)
forall a. Storable a => Ptr a -> IO a
peek (Ptr MetaInfo
ptr Ptr MetaInfo -> Int -> Ptr (FunPtr C_MetaFreeFunction)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32) :: IO (FunPtr Gst.Callbacks.C_MetaFreeFunction)
    Maybe MetaFreeFunction
result <- FunPtr C_MetaFreeFunction
-> (FunPtr C_MetaFreeFunction -> IO MetaFreeFunction)
-> IO (Maybe MetaFreeFunction)
forall a b. FunPtr a -> (FunPtr a -> IO b) -> IO (Maybe b)
SP.convertFunPtrIfNonNull FunPtr C_MetaFreeFunction
val ((FunPtr C_MetaFreeFunction -> IO MetaFreeFunction)
 -> IO (Maybe MetaFreeFunction))
-> (FunPtr C_MetaFreeFunction -> IO MetaFreeFunction)
-> IO (Maybe MetaFreeFunction)
forall a b. (a -> b) -> a -> b
$ \FunPtr C_MetaFreeFunction
val' -> do
        let val'' :: MetaFreeFunction
val'' = FunPtr C_MetaFreeFunction -> MetaFreeFunction
forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
FunPtr C_MetaFreeFunction -> Meta -> Buffer -> m ()
Gst.Callbacks.dynamic_MetaFreeFunction FunPtr C_MetaFreeFunction
val'
        MetaFreeFunction -> IO MetaFreeFunction
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return MetaFreeFunction
val''
    Maybe MetaFreeFunction -> IO (Maybe MetaFreeFunction)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe MetaFreeFunction
result
setMetaInfoFreeFunc :: MonadIO m => MetaInfo -> FunPtr Gst.Callbacks.C_MetaFreeFunction -> m ()
setMetaInfoFreeFunc :: forall (m :: * -> *).
MonadIO m =>
MetaInfo -> FunPtr C_MetaFreeFunction -> m ()
setMetaInfoFreeFunc MetaInfo
s FunPtr C_MetaFreeFunction
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
$ MetaInfo -> (Ptr MetaInfo -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr MetaInfo
s ((Ptr MetaInfo -> IO ()) -> IO ())
-> (Ptr MetaInfo -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr MetaInfo
ptr -> do
    Ptr (FunPtr C_MetaFreeFunction)
-> FunPtr C_MetaFreeFunction -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr MetaInfo
ptr Ptr MetaInfo -> Int -> Ptr (FunPtr C_MetaFreeFunction)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32) (FunPtr C_MetaFreeFunction
val :: FunPtr Gst.Callbacks.C_MetaFreeFunction)
clearMetaInfoFreeFunc :: MonadIO m => MetaInfo -> m ()
clearMetaInfoFreeFunc :: forall (m :: * -> *). MonadIO m => MetaInfo -> m ()
clearMetaInfoFreeFunc MetaInfo
s = 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
$ MetaInfo -> (Ptr MetaInfo -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr MetaInfo
s ((Ptr MetaInfo -> IO ()) -> IO ())
-> (Ptr MetaInfo -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr MetaInfo
ptr -> do
    Ptr (FunPtr C_MetaFreeFunction)
-> FunPtr C_MetaFreeFunction -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr MetaInfo
ptr Ptr MetaInfo -> Int -> Ptr (FunPtr C_MetaFreeFunction)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32) (FunPtr C_MetaFreeFunction
forall a. FunPtr a
FP.nullFunPtr :: FunPtr Gst.Callbacks.C_MetaFreeFunction)
#if defined(ENABLE_OVERLOADING)
data MetaInfoFreeFuncFieldInfo
instance AttrInfo MetaInfoFreeFuncFieldInfo where
    type AttrBaseTypeConstraint MetaInfoFreeFuncFieldInfo = (~) MetaInfo
    type AttrAllowedOps MetaInfoFreeFuncFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint MetaInfoFreeFuncFieldInfo = (~) (FunPtr Gst.Callbacks.C_MetaFreeFunction)
    type AttrTransferTypeConstraint MetaInfoFreeFuncFieldInfo = (~)Gst.Callbacks.MetaFreeFunction
    type AttrTransferType MetaInfoFreeFuncFieldInfo = (FunPtr Gst.Callbacks.C_MetaFreeFunction)
    type AttrGetType MetaInfoFreeFuncFieldInfo = Maybe Gst.Callbacks.MetaFreeFunction
    type AttrLabel MetaInfoFreeFuncFieldInfo = "free_func"
    type AttrOrigin MetaInfoFreeFuncFieldInfo = MetaInfo
    attrGet = getMetaInfoFreeFunc
    attrSet = setMetaInfoFreeFunc
    attrConstruct = undefined
    attrClear = clearMetaInfoFreeFunc
    attrTransfer _ v = do
        Gst.Callbacks.mk_MetaFreeFunction (Gst.Callbacks.wrap_MetaFreeFunction Nothing v)
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gst.Structs.MetaInfo.freeFunc"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gst-1.0.28/docs/GI-Gst-Structs-MetaInfo.html#g:attr:freeFunc"
        })
metaInfo_freeFunc :: AttrLabelProxy "freeFunc"
metaInfo_freeFunc = AttrLabelProxy
#endif
getMetaInfoTransformFunc :: MonadIO m => MetaInfo -> m (Maybe Gst.Callbacks.MetaTransformFunction)
getMetaInfoTransformFunc :: forall (m :: * -> *).
MonadIO m =>
MetaInfo -> m (Maybe MetaTransformFunction)
getMetaInfoTransformFunc MetaInfo
s = IO (Maybe MetaTransformFunction) -> m (Maybe MetaTransformFunction)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe MetaTransformFunction)
 -> m (Maybe MetaTransformFunction))
-> IO (Maybe MetaTransformFunction)
-> m (Maybe MetaTransformFunction)
forall a b. (a -> b) -> a -> b
$ MetaInfo
-> (Ptr MetaInfo -> IO (Maybe MetaTransformFunction))
-> IO (Maybe MetaTransformFunction)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr MetaInfo
s ((Ptr MetaInfo -> IO (Maybe MetaTransformFunction))
 -> IO (Maybe MetaTransformFunction))
-> (Ptr MetaInfo -> IO (Maybe MetaTransformFunction))
-> IO (Maybe MetaTransformFunction)
forall a b. (a -> b) -> a -> b
$ \Ptr MetaInfo
ptr -> do
    FunPtr C_MetaTransformFunction
val <- Ptr (FunPtr C_MetaTransformFunction)
-> IO (FunPtr C_MetaTransformFunction)
forall a. Storable a => Ptr a -> IO a
peek (Ptr MetaInfo
ptr Ptr MetaInfo -> Int -> Ptr (FunPtr C_MetaTransformFunction)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40) :: IO (FunPtr Gst.Callbacks.C_MetaTransformFunction)
    Maybe MetaTransformFunction
result <- FunPtr C_MetaTransformFunction
-> (FunPtr C_MetaTransformFunction -> IO MetaTransformFunction)
-> IO (Maybe MetaTransformFunction)
forall a b. FunPtr a -> (FunPtr a -> IO b) -> IO (Maybe b)
SP.convertFunPtrIfNonNull FunPtr C_MetaTransformFunction
val ((FunPtr C_MetaTransformFunction -> IO MetaTransformFunction)
 -> IO (Maybe MetaTransformFunction))
-> (FunPtr C_MetaTransformFunction -> IO MetaTransformFunction)
-> IO (Maybe MetaTransformFunction)
forall a b. (a -> b) -> a -> b
$ \FunPtr C_MetaTransformFunction
val' -> do
        let val'' :: MetaTransformFunction
val'' = FunPtr C_MetaTransformFunction -> MetaTransformFunction
forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
FunPtr C_MetaTransformFunction
-> Buffer -> Meta -> Buffer -> Word32 -> Ptr () -> m Bool
Gst.Callbacks.dynamic_MetaTransformFunction FunPtr C_MetaTransformFunction
val'
        MetaTransformFunction -> IO MetaTransformFunction
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return MetaTransformFunction
val''
    Maybe MetaTransformFunction -> IO (Maybe MetaTransformFunction)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe MetaTransformFunction
result
setMetaInfoTransformFunc :: MonadIO m => MetaInfo -> FunPtr Gst.Callbacks.C_MetaTransformFunction -> m ()
setMetaInfoTransformFunc :: forall (m :: * -> *).
MonadIO m =>
MetaInfo -> FunPtr C_MetaTransformFunction -> m ()
setMetaInfoTransformFunc MetaInfo
s FunPtr C_MetaTransformFunction
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
$ MetaInfo -> (Ptr MetaInfo -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr MetaInfo
s ((Ptr MetaInfo -> IO ()) -> IO ())
-> (Ptr MetaInfo -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr MetaInfo
ptr -> do
    Ptr (FunPtr C_MetaTransformFunction)
-> FunPtr C_MetaTransformFunction -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr MetaInfo
ptr Ptr MetaInfo -> Int -> Ptr (FunPtr C_MetaTransformFunction)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40) (FunPtr C_MetaTransformFunction
val :: FunPtr Gst.Callbacks.C_MetaTransformFunction)
clearMetaInfoTransformFunc :: MonadIO m => MetaInfo -> m ()
clearMetaInfoTransformFunc :: forall (m :: * -> *). MonadIO m => MetaInfo -> m ()
clearMetaInfoTransformFunc MetaInfo
s = 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
$ MetaInfo -> (Ptr MetaInfo -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr MetaInfo
s ((Ptr MetaInfo -> IO ()) -> IO ())
-> (Ptr MetaInfo -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr MetaInfo
ptr -> do
    Ptr (FunPtr C_MetaTransformFunction)
-> FunPtr C_MetaTransformFunction -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr MetaInfo
ptr Ptr MetaInfo -> Int -> Ptr (FunPtr C_MetaTransformFunction)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40) (FunPtr C_MetaTransformFunction
forall a. FunPtr a
FP.nullFunPtr :: FunPtr Gst.Callbacks.C_MetaTransformFunction)
#if defined(ENABLE_OVERLOADING)
data MetaInfoTransformFuncFieldInfo
instance AttrInfo MetaInfoTransformFuncFieldInfo where
    type AttrBaseTypeConstraint MetaInfoTransformFuncFieldInfo = (~) MetaInfo
    type AttrAllowedOps MetaInfoTransformFuncFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint MetaInfoTransformFuncFieldInfo = (~) (FunPtr Gst.Callbacks.C_MetaTransformFunction)
    type AttrTransferTypeConstraint MetaInfoTransformFuncFieldInfo = (~)Gst.Callbacks.MetaTransformFunction
    type AttrTransferType MetaInfoTransformFuncFieldInfo = (FunPtr Gst.Callbacks.C_MetaTransformFunction)
    type AttrGetType MetaInfoTransformFuncFieldInfo = Maybe Gst.Callbacks.MetaTransformFunction
    type AttrLabel MetaInfoTransformFuncFieldInfo = "transform_func"
    type AttrOrigin MetaInfoTransformFuncFieldInfo = MetaInfo
    attrGet = getMetaInfoTransformFunc
    attrSet = setMetaInfoTransformFunc
    attrConstruct = undefined
    attrClear = clearMetaInfoTransformFunc
    attrTransfer _ v = do
        Gst.Callbacks.mk_MetaTransformFunction (Gst.Callbacks.wrap_MetaTransformFunction Nothing v)
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gst.Structs.MetaInfo.transformFunc"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gst-1.0.28/docs/GI-Gst-Structs-MetaInfo.html#g:attr:transformFunc"
        })
metaInfo_transformFunc :: AttrLabelProxy "transformFunc"
metaInfo_transformFunc = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList MetaInfo
type instance O.AttributeList MetaInfo = MetaInfoAttributeList
type MetaInfoAttributeList = ('[ '("api", MetaInfoApiFieldInfo), '("type", MetaInfoTypeFieldInfo), '("size", MetaInfoSizeFieldInfo), '("initFunc", MetaInfoInitFuncFieldInfo), '("freeFunc", MetaInfoFreeFuncFieldInfo), '("transformFunc", MetaInfoTransformFuncFieldInfo)] :: [(Symbol, DK.Type)])
#endif
foreign import ccall "gst_meta_info_is_custom" gst_meta_info_is_custom :: 
    Ptr MetaInfo ->                         
    IO CInt
metaInfoIsCustom ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    MetaInfo
    -> m Bool
    
    
metaInfoIsCustom :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
MetaInfo -> m Bool
metaInfoIsCustom MetaInfo
info = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr MetaInfo
info' <- MetaInfo -> IO (Ptr MetaInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr MetaInfo
info
    CInt
result <- Ptr MetaInfo -> IO CInt
gst_meta_info_is_custom Ptr MetaInfo
info'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    MetaInfo -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr MetaInfo
info
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data MetaInfoIsCustomMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.OverloadedMethod MetaInfoIsCustomMethodInfo MetaInfo signature where
    overloadedMethod = metaInfoIsCustom
instance O.OverloadedMethodInfo MetaInfoIsCustomMethodInfo MetaInfo where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gst.Structs.MetaInfo.metaInfoIsCustom",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gst-1.0.28/docs/GI-Gst-Structs-MetaInfo.html#v:metaInfoIsCustom"
        })
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveMetaInfoMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveMetaInfoMethod "isCustom" o = MetaInfoIsCustomMethodInfo
    ResolveMetaInfoMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveMetaInfoMethod t MetaInfo, O.OverloadedMethod info MetaInfo p) => OL.IsLabel t (MetaInfo -> 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 ~ ResolveMetaInfoMethod t MetaInfo, O.OverloadedMethod info MetaInfo p, R.HasField t MetaInfo p) => R.HasField t MetaInfo p where
    getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveMetaInfoMethod t MetaInfo, O.OverloadedMethodInfo info MetaInfo) => OL.IsLabel t (O.MethodProxy info MetaInfo) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif
#endif