{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.GstVideo.Structs.VideoAncillary
(
VideoAncillary(..) ,
newZeroVideoAncillary ,
noVideoAncillary ,
#if defined(ENABLE_OVERLOADING)
ResolveVideoAncillaryMethod ,
#endif
getVideoAncillaryDID ,
setVideoAncillaryDID ,
#if defined(ENABLE_OVERLOADING)
videoAncillary_dID ,
#endif
getVideoAncillaryDataCount ,
setVideoAncillaryDataCount ,
#if defined(ENABLE_OVERLOADING)
videoAncillary_dataCount ,
#endif
getVideoAncillarySDIDBlockNumber ,
setVideoAncillarySDIDBlockNumber ,
#if defined(ENABLE_OVERLOADING)
videoAncillary_sDIDBlockNumber ,
#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.GI.Base.Signals as B.Signals
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
newtype VideoAncillary = VideoAncillary (ManagedPtr VideoAncillary)
deriving (VideoAncillary -> VideoAncillary -> Bool
(VideoAncillary -> VideoAncillary -> Bool)
-> (VideoAncillary -> VideoAncillary -> Bool) -> Eq VideoAncillary
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VideoAncillary -> VideoAncillary -> Bool
$c/= :: VideoAncillary -> VideoAncillary -> Bool
== :: VideoAncillary -> VideoAncillary -> Bool
$c== :: VideoAncillary -> VideoAncillary -> Bool
Eq)
instance WrappedPtr VideoAncillary where
wrappedPtrCalloc :: IO (Ptr VideoAncillary)
wrappedPtrCalloc = Int -> IO (Ptr VideoAncillary)
forall a. Int -> IO (Ptr a)
callocBytes 48
wrappedPtrCopy :: VideoAncillary -> IO VideoAncillary
wrappedPtrCopy = \p :: VideoAncillary
p -> VideoAncillary
-> (Ptr VideoAncillary -> IO VideoAncillary) -> IO VideoAncillary
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr VideoAncillary
p (Int -> Ptr VideoAncillary -> IO (Ptr VideoAncillary)
forall a. WrappedPtr a => Int -> Ptr a -> IO (Ptr a)
copyBytes 48 (Ptr VideoAncillary -> IO (Ptr VideoAncillary))
-> (Ptr VideoAncillary -> IO VideoAncillary)
-> Ptr VideoAncillary
-> IO VideoAncillary
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (ManagedPtr VideoAncillary -> VideoAncillary)
-> Ptr VideoAncillary -> IO VideoAncillary
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr VideoAncillary -> VideoAncillary
VideoAncillary)
wrappedPtrFree :: Maybe (GDestroyNotify VideoAncillary)
wrappedPtrFree = GDestroyNotify VideoAncillary
-> Maybe (GDestroyNotify VideoAncillary)
forall a. a -> Maybe a
Just GDestroyNotify VideoAncillary
forall a. FunPtr (Ptr a -> IO ())
ptr_to_g_free
newZeroVideoAncillary :: MonadIO m => m VideoAncillary
newZeroVideoAncillary :: m VideoAncillary
newZeroVideoAncillary = IO VideoAncillary -> m VideoAncillary
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO VideoAncillary -> m VideoAncillary)
-> IO VideoAncillary -> m VideoAncillary
forall a b. (a -> b) -> a -> b
$ IO (Ptr VideoAncillary)
forall a. WrappedPtr a => IO (Ptr a)
wrappedPtrCalloc IO (Ptr VideoAncillary)
-> (Ptr VideoAncillary -> IO VideoAncillary) -> IO VideoAncillary
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr VideoAncillary -> VideoAncillary)
-> Ptr VideoAncillary -> IO VideoAncillary
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr VideoAncillary -> VideoAncillary
VideoAncillary
instance tag ~ 'AttrSet => Constructible VideoAncillary tag where
new :: (ManagedPtr VideoAncillary -> VideoAncillary)
-> [AttrOp VideoAncillary tag] -> m VideoAncillary
new _ attrs :: [AttrOp VideoAncillary tag]
attrs = do
VideoAncillary
o <- m VideoAncillary
forall (m :: * -> *). MonadIO m => m VideoAncillary
newZeroVideoAncillary
VideoAncillary -> [AttrOp VideoAncillary 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set VideoAncillary
o [AttrOp VideoAncillary tag]
[AttrOp VideoAncillary 'AttrSet]
attrs
VideoAncillary -> m VideoAncillary
forall (m :: * -> *) a. Monad m => a -> m a
return VideoAncillary
o
noVideoAncillary :: Maybe VideoAncillary
noVideoAncillary :: Maybe VideoAncillary
noVideoAncillary = Maybe VideoAncillary
forall a. Maybe a
Nothing
getVideoAncillaryDID :: MonadIO m => VideoAncillary -> m Word8
getVideoAncillaryDID :: VideoAncillary -> m Word8
getVideoAncillaryDID s :: VideoAncillary
s = IO Word8 -> m Word8
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word8 -> m Word8) -> IO Word8 -> m Word8
forall a b. (a -> b) -> a -> b
$ VideoAncillary -> (Ptr VideoAncillary -> IO Word8) -> IO Word8
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr VideoAncillary
s ((Ptr VideoAncillary -> IO Word8) -> IO Word8)
-> (Ptr VideoAncillary -> IO Word8) -> IO Word8
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr VideoAncillary
ptr -> do
Word8
val <- Ptr Word8 -> IO Word8
forall a. Storable a => Ptr a -> IO a
peek (Ptr VideoAncillary
ptr Ptr VideoAncillary -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0) :: IO Word8
Word8 -> IO Word8
forall (m :: * -> *) a. Monad m => a -> m a
return Word8
val
setVideoAncillaryDID :: MonadIO m => VideoAncillary -> Word8 -> m ()
setVideoAncillaryDID :: VideoAncillary -> Word8 -> m ()
setVideoAncillaryDID s :: VideoAncillary
s val :: Word8
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ VideoAncillary -> (Ptr VideoAncillary -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr VideoAncillary
s ((Ptr VideoAncillary -> IO ()) -> IO ())
-> (Ptr VideoAncillary -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr VideoAncillary
ptr -> do
Ptr Word8 -> Word8 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr VideoAncillary
ptr Ptr VideoAncillary -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0) (Word8
val :: Word8)
#if defined(ENABLE_OVERLOADING)
data VideoAncillaryDIDFieldInfo
instance AttrInfo VideoAncillaryDIDFieldInfo where
type AttrBaseTypeConstraint VideoAncillaryDIDFieldInfo = (~) VideoAncillary
type AttrAllowedOps VideoAncillaryDIDFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint VideoAncillaryDIDFieldInfo = (~) Word8
type AttrTransferTypeConstraint VideoAncillaryDIDFieldInfo = (~)Word8
type AttrTransferType VideoAncillaryDIDFieldInfo = Word8
type AttrGetType VideoAncillaryDIDFieldInfo = Word8
type AttrLabel VideoAncillaryDIDFieldInfo = "DID"
type AttrOrigin VideoAncillaryDIDFieldInfo = VideoAncillary
attrGet = getVideoAncillaryDID
attrSet = setVideoAncillaryDID
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
videoAncillary_dID :: AttrLabelProxy "dID"
videoAncillary_dID = AttrLabelProxy
#endif
getVideoAncillarySDIDBlockNumber :: MonadIO m => VideoAncillary -> m Word8
getVideoAncillarySDIDBlockNumber :: VideoAncillary -> m Word8
getVideoAncillarySDIDBlockNumber s :: VideoAncillary
s = IO Word8 -> m Word8
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word8 -> m Word8) -> IO Word8 -> m Word8
forall a b. (a -> b) -> a -> b
$ VideoAncillary -> (Ptr VideoAncillary -> IO Word8) -> IO Word8
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr VideoAncillary
s ((Ptr VideoAncillary -> IO Word8) -> IO Word8)
-> (Ptr VideoAncillary -> IO Word8) -> IO Word8
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr VideoAncillary
ptr -> do
Word8
val <- Ptr Word8 -> IO Word8
forall a. Storable a => Ptr a -> IO a
peek (Ptr VideoAncillary
ptr Ptr VideoAncillary -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 1) :: IO Word8
Word8 -> IO Word8
forall (m :: * -> *) a. Monad m => a -> m a
return Word8
val
setVideoAncillarySDIDBlockNumber :: MonadIO m => VideoAncillary -> Word8 -> m ()
setVideoAncillarySDIDBlockNumber :: VideoAncillary -> Word8 -> m ()
setVideoAncillarySDIDBlockNumber s :: VideoAncillary
s val :: Word8
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ VideoAncillary -> (Ptr VideoAncillary -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr VideoAncillary
s ((Ptr VideoAncillary -> IO ()) -> IO ())
-> (Ptr VideoAncillary -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr VideoAncillary
ptr -> do
Ptr Word8 -> Word8 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr VideoAncillary
ptr Ptr VideoAncillary -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 1) (Word8
val :: Word8)
#if defined(ENABLE_OVERLOADING)
data VideoAncillarySDIDBlockNumberFieldInfo
instance AttrInfo VideoAncillarySDIDBlockNumberFieldInfo where
type AttrBaseTypeConstraint VideoAncillarySDIDBlockNumberFieldInfo = (~) VideoAncillary
type AttrAllowedOps VideoAncillarySDIDBlockNumberFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint VideoAncillarySDIDBlockNumberFieldInfo = (~) Word8
type AttrTransferTypeConstraint VideoAncillarySDIDBlockNumberFieldInfo = (~)Word8
type AttrTransferType VideoAncillarySDIDBlockNumberFieldInfo = Word8
type AttrGetType VideoAncillarySDIDBlockNumberFieldInfo = Word8
type AttrLabel VideoAncillarySDIDBlockNumberFieldInfo = "SDID_block_number"
type AttrOrigin VideoAncillarySDIDBlockNumberFieldInfo = VideoAncillary
attrGet = getVideoAncillarySDIDBlockNumber
attrSet = setVideoAncillarySDIDBlockNumber
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
videoAncillary_sDIDBlockNumber :: AttrLabelProxy "sDIDBlockNumber"
videoAncillary_sDIDBlockNumber = AttrLabelProxy
#endif
getVideoAncillaryDataCount :: MonadIO m => VideoAncillary -> m Word8
getVideoAncillaryDataCount :: VideoAncillary -> m Word8
getVideoAncillaryDataCount s :: VideoAncillary
s = IO Word8 -> m Word8
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word8 -> m Word8) -> IO Word8 -> m Word8
forall a b. (a -> b) -> a -> b
$ VideoAncillary -> (Ptr VideoAncillary -> IO Word8) -> IO Word8
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr VideoAncillary
s ((Ptr VideoAncillary -> IO Word8) -> IO Word8)
-> (Ptr VideoAncillary -> IO Word8) -> IO Word8
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr VideoAncillary
ptr -> do
Word8
val <- Ptr Word8 -> IO Word8
forall a. Storable a => Ptr a -> IO a
peek (Ptr VideoAncillary
ptr Ptr VideoAncillary -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 2) :: IO Word8
Word8 -> IO Word8
forall (m :: * -> *) a. Monad m => a -> m a
return Word8
val
setVideoAncillaryDataCount :: MonadIO m => VideoAncillary -> Word8 -> m ()
setVideoAncillaryDataCount :: VideoAncillary -> Word8 -> m ()
setVideoAncillaryDataCount s :: VideoAncillary
s val :: Word8
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ VideoAncillary -> (Ptr VideoAncillary -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr VideoAncillary
s ((Ptr VideoAncillary -> IO ()) -> IO ())
-> (Ptr VideoAncillary -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr VideoAncillary
ptr -> do
Ptr Word8 -> Word8 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr VideoAncillary
ptr Ptr VideoAncillary -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 2) (Word8
val :: Word8)
#if defined(ENABLE_OVERLOADING)
data VideoAncillaryDataCountFieldInfo
instance AttrInfo VideoAncillaryDataCountFieldInfo where
type AttrBaseTypeConstraint VideoAncillaryDataCountFieldInfo = (~) VideoAncillary
type AttrAllowedOps VideoAncillaryDataCountFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint VideoAncillaryDataCountFieldInfo = (~) Word8
type AttrTransferTypeConstraint VideoAncillaryDataCountFieldInfo = (~)Word8
type AttrTransferType VideoAncillaryDataCountFieldInfo = Word8
type AttrGetType VideoAncillaryDataCountFieldInfo = Word8
type AttrLabel VideoAncillaryDataCountFieldInfo = "data_count"
type AttrOrigin VideoAncillaryDataCountFieldInfo = VideoAncillary
attrGet = getVideoAncillaryDataCount
attrSet = setVideoAncillaryDataCount
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
videoAncillary_dataCount :: AttrLabelProxy "dataCount"
videoAncillary_dataCount = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList VideoAncillary
type instance O.AttributeList VideoAncillary = VideoAncillaryAttributeList
type VideoAncillaryAttributeList = ('[ '("dID", VideoAncillaryDIDFieldInfo), '("sDIDBlockNumber", VideoAncillarySDIDBlockNumberFieldInfo), '("dataCount", VideoAncillaryDataCountFieldInfo)] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveVideoAncillaryMethod (t :: Symbol) (o :: *) :: * where
ResolveVideoAncillaryMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveVideoAncillaryMethod t VideoAncillary, O.MethodInfo info VideoAncillary p) => OL.IsLabel t (VideoAncillary -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif