Copyright | Will Thompson and Iñaki García Etxebarria |
---|---|
License | LGPL-2.1 |
Maintainer | Iñaki García Etxebarria |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Synopsis
- type C_VideoAffineTransformationGetMatrix = Ptr VideoAffineTransformationMeta -> CFloat -> IO CInt
- type VideoAffineTransformationGetMatrix = VideoAffineTransformationMeta -> Float -> IO Bool
- dynamic_VideoAffineTransformationGetMatrix :: (HasCallStack, MonadIO m) => FunPtr C_VideoAffineTransformationGetMatrix -> VideoAffineTransformationMeta -> Float -> m Bool
- genClosure_VideoAffineTransformationGetMatrix :: MonadIO m => VideoAffineTransformationGetMatrix -> m (GClosure C_VideoAffineTransformationGetMatrix)
- mk_VideoAffineTransformationGetMatrix :: C_VideoAffineTransformationGetMatrix -> IO (FunPtr C_VideoAffineTransformationGetMatrix)
- noVideoAffineTransformationGetMatrix :: Maybe VideoAffineTransformationGetMatrix
- wrap_VideoAffineTransformationGetMatrix :: Maybe (Ptr (FunPtr C_VideoAffineTransformationGetMatrix)) -> VideoAffineTransformationGetMatrix -> C_VideoAffineTransformationGetMatrix
- type C_VideoConvertSampleCallback = Ptr Sample -> Ptr GError -> Ptr () -> IO ()
- type VideoConvertSampleCallback = Sample -> GError -> IO ()
- type VideoConvertSampleCallback_WithClosures = Sample -> GError -> Ptr () -> IO ()
- drop_closures_VideoConvertSampleCallback :: VideoConvertSampleCallback -> VideoConvertSampleCallback_WithClosures
- dynamic_VideoConvertSampleCallback :: (HasCallStack, MonadIO m) => FunPtr C_VideoConvertSampleCallback -> Sample -> GError -> Ptr () -> m ()
- genClosure_VideoConvertSampleCallback :: MonadIO m => VideoConvertSampleCallback -> m (GClosure C_VideoConvertSampleCallback)
- mk_VideoConvertSampleCallback :: C_VideoConvertSampleCallback -> IO (FunPtr C_VideoConvertSampleCallback)
- noVideoConvertSampleCallback :: Maybe VideoConvertSampleCallback
- noVideoConvertSampleCallback_WithClosures :: Maybe VideoConvertSampleCallback_WithClosures
- wrap_VideoConvertSampleCallback :: Maybe (Ptr (FunPtr C_VideoConvertSampleCallback)) -> VideoConvertSampleCallback_WithClosures -> C_VideoConvertSampleCallback
- type C_VideoFormatPack = Ptr VideoFormatInfo -> CUInt -> Ptr () -> Int32 -> Ptr () -> Int32 -> CUInt -> Int32 -> Int32 -> IO ()
- type VideoFormatPack = VideoFormatInfo -> [VideoPackFlags] -> Ptr () -> Int32 -> Ptr () -> Int32 -> [VideoChromaSite] -> Int32 -> Int32 -> IO ()
- dynamic_VideoFormatPack :: (HasCallStack, MonadIO m) => FunPtr C_VideoFormatPack -> VideoFormatInfo -> [VideoPackFlags] -> Ptr () -> Int32 -> Ptr () -> Int32 -> [VideoChromaSite] -> Int32 -> Int32 -> m ()
- genClosure_VideoFormatPack :: MonadIO m => VideoFormatPack -> m (GClosure C_VideoFormatPack)
- mk_VideoFormatPack :: C_VideoFormatPack -> IO (FunPtr C_VideoFormatPack)
- noVideoFormatPack :: Maybe VideoFormatPack
- wrap_VideoFormatPack :: Maybe (Ptr (FunPtr C_VideoFormatPack)) -> VideoFormatPack -> C_VideoFormatPack
- type C_VideoFormatUnpack = Ptr VideoFormatInfo -> CUInt -> Ptr () -> Ptr () -> Int32 -> Int32 -> Int32 -> Int32 -> IO ()
- type VideoFormatUnpack = VideoFormatInfo -> [VideoPackFlags] -> Ptr () -> Ptr () -> Int32 -> Int32 -> Int32 -> Int32 -> IO ()
- dynamic_VideoFormatUnpack :: (HasCallStack, MonadIO m) => FunPtr C_VideoFormatUnpack -> VideoFormatInfo -> [VideoPackFlags] -> Ptr () -> Ptr () -> Int32 -> Int32 -> Int32 -> Int32 -> m ()
- genClosure_VideoFormatUnpack :: MonadIO m => VideoFormatUnpack -> m (GClosure C_VideoFormatUnpack)
- mk_VideoFormatUnpack :: C_VideoFormatUnpack -> IO (FunPtr C_VideoFormatUnpack)
- noVideoFormatUnpack :: Maybe VideoFormatUnpack
- wrap_VideoFormatUnpack :: Maybe (Ptr (FunPtr C_VideoFormatUnpack)) -> VideoFormatUnpack -> C_VideoFormatUnpack
- type C_VideoGLTextureUpload = Ptr VideoGLTextureUploadMeta -> Word32 -> IO CInt
- type VideoGLTextureUpload = VideoGLTextureUploadMeta -> Word32 -> IO Bool
- dynamic_VideoGLTextureUpload :: (HasCallStack, MonadIO m) => FunPtr C_VideoGLTextureUpload -> VideoGLTextureUploadMeta -> Word32 -> m Bool
- genClosure_VideoGLTextureUpload :: MonadIO m => VideoGLTextureUpload -> m (GClosure C_VideoGLTextureUpload)
- mk_VideoGLTextureUpload :: C_VideoGLTextureUpload -> IO (FunPtr C_VideoGLTextureUpload)
- noVideoGLTextureUpload :: Maybe VideoGLTextureUpload
- wrap_VideoGLTextureUpload :: Maybe (Ptr (FunPtr C_VideoGLTextureUpload)) -> VideoGLTextureUpload -> C_VideoGLTextureUpload
- type C_VideoMetaMapFieldCallback = Ptr VideoMeta -> Word32 -> Ptr MapInfo -> Ptr () -> Int32 -> CUInt -> IO CInt
- type VideoMetaMapFieldCallback = VideoMeta -> Word32 -> MapInfo -> Ptr () -> Int32 -> [MapFlags] -> IO Bool
- dynamic_VideoMetaMapFieldCallback :: (HasCallStack, MonadIO m) => FunPtr C_VideoMetaMapFieldCallback -> VideoMeta -> Word32 -> MapInfo -> Ptr () -> Int32 -> [MapFlags] -> m Bool
- genClosure_VideoMetaMapFieldCallback :: MonadIO m => VideoMetaMapFieldCallback -> m (GClosure C_VideoMetaMapFieldCallback)
- mk_VideoMetaMapFieldCallback :: C_VideoMetaMapFieldCallback -> IO (FunPtr C_VideoMetaMapFieldCallback)
- noVideoMetaMapFieldCallback :: Maybe VideoMetaMapFieldCallback
- wrap_VideoMetaMapFieldCallback :: Maybe (Ptr (FunPtr C_VideoMetaMapFieldCallback)) -> VideoMetaMapFieldCallback -> C_VideoMetaMapFieldCallback
- type C_VideoMetaUnmapFieldCallback = Ptr VideoMeta -> Word32 -> Ptr MapInfo -> IO CInt
- type VideoMetaUnmapFieldCallback = VideoMeta -> Word32 -> MapInfo -> IO Bool
- dynamic_VideoMetaUnmapFieldCallback :: (HasCallStack, MonadIO m) => FunPtr C_VideoMetaUnmapFieldCallback -> VideoMeta -> Word32 -> MapInfo -> m Bool
- genClosure_VideoMetaUnmapFieldCallback :: MonadIO m => VideoMetaUnmapFieldCallback -> m (GClosure C_VideoMetaUnmapFieldCallback)
- mk_VideoMetaUnmapFieldCallback :: C_VideoMetaUnmapFieldCallback -> IO (FunPtr C_VideoMetaUnmapFieldCallback)
- noVideoMetaUnmapFieldCallback :: Maybe VideoMetaUnmapFieldCallback
- wrap_VideoMetaUnmapFieldCallback :: Maybe (Ptr (FunPtr C_VideoMetaUnmapFieldCallback)) -> VideoMetaUnmapFieldCallback -> C_VideoMetaUnmapFieldCallback
Signals
VideoAffineTransformationGetMatrix
type C_VideoAffineTransformationGetMatrix = Ptr VideoAffineTransformationMeta -> CFloat -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type VideoAffineTransformationGetMatrix = VideoAffineTransformationMeta -> Float -> IO Bool Source #
No description available in the introspection data.
dynamic_VideoAffineTransformationGetMatrix :: (HasCallStack, MonadIO m) => FunPtr C_VideoAffineTransformationGetMatrix -> VideoAffineTransformationMeta -> Float -> m Bool Source #
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_VideoAffineTransformationGetMatrix :: MonadIO m => VideoAffineTransformationGetMatrix -> m (GClosure C_VideoAffineTransformationGetMatrix) Source #
Wrap the callback into a GClosure
.
mk_VideoAffineTransformationGetMatrix :: C_VideoAffineTransformationGetMatrix -> IO (FunPtr C_VideoAffineTransformationGetMatrix) Source #
Generate a function pointer callable from C code, from a C_VideoAffineTransformationGetMatrix
.
noVideoAffineTransformationGetMatrix :: Maybe VideoAffineTransformationGetMatrix Source #
A convenience synonym for
.Nothing
:: Maybe
VideoAffineTransformationGetMatrix
wrap_VideoAffineTransformationGetMatrix :: Maybe (Ptr (FunPtr C_VideoAffineTransformationGetMatrix)) -> VideoAffineTransformationGetMatrix -> C_VideoAffineTransformationGetMatrix Source #
VideoConvertSampleCallback
type C_VideoConvertSampleCallback = Ptr Sample -> Ptr GError -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type VideoConvertSampleCallback = Sample -> GError -> IO () Source #
No description available in the introspection data.
type VideoConvertSampleCallback_WithClosures = Sample -> GError -> Ptr () -> IO () Source #
No description available in the introspection data.
drop_closures_VideoConvertSampleCallback :: VideoConvertSampleCallback -> VideoConvertSampleCallback_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_VideoConvertSampleCallback :: (HasCallStack, MonadIO m) => FunPtr C_VideoConvertSampleCallback -> Sample -> GError -> Ptr () -> m () Source #
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_VideoConvertSampleCallback :: MonadIO m => VideoConvertSampleCallback -> m (GClosure C_VideoConvertSampleCallback) Source #
Wrap the callback into a GClosure
.
mk_VideoConvertSampleCallback :: C_VideoConvertSampleCallback -> IO (FunPtr C_VideoConvertSampleCallback) Source #
Generate a function pointer callable from C code, from a C_VideoConvertSampleCallback
.
noVideoConvertSampleCallback :: Maybe VideoConvertSampleCallback Source #
A convenience synonym for
.Nothing
:: Maybe
VideoConvertSampleCallback
noVideoConvertSampleCallback_WithClosures :: Maybe VideoConvertSampleCallback_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
VideoConvertSampleCallback_WithClosures
wrap_VideoConvertSampleCallback :: Maybe (Ptr (FunPtr C_VideoConvertSampleCallback)) -> VideoConvertSampleCallback_WithClosures -> C_VideoConvertSampleCallback Source #
Wrap a VideoConvertSampleCallback
into a C_VideoConvertSampleCallback
.
VideoFormatPack
type C_VideoFormatPack = Ptr VideoFormatInfo -> CUInt -> Ptr () -> Int32 -> Ptr () -> Int32 -> CUInt -> Int32 -> Int32 -> IO () Source #
Type for the callback on the (unwrapped) C side.
type VideoFormatPack Source #
= VideoFormatInfo |
|
-> [VideoPackFlags] |
|
-> Ptr () |
|
-> Int32 |
|
-> Ptr () |
|
-> Int32 |
|
-> [VideoChromaSite] |
|
-> Int32 |
|
-> Int32 |
|
-> IO () |
Packs width
pixels from src
to the given planes and strides in the
format info
. The pixels from source have each component interleaved
and will be packed into the planes in data
.
This function operates on pack_lines lines, meaning that src
should
contain at least pack_lines lines with a stride of sstride
and y
should be a multiple of pack_lines.
Subsampled formats will use the horizontally and vertically cosited component from the source. Subsampling should be performed before packing.
Because this function does not have a x coordinate, it is not possible to pack pixels starting from an unaligned position. For tiled images this means that packing should start from a tile coordinate. For subsampled formats this means that a complete pixel needs to be packed.
dynamic_VideoFormatPack Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_VideoFormatPack | |
-> VideoFormatInfo |
|
-> [VideoPackFlags] |
|
-> Ptr () |
|
-> Int32 |
|
-> Ptr () |
|
-> Int32 |
|
-> [VideoChromaSite] |
|
-> Int32 |
|
-> Int32 |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_VideoFormatPack :: MonadIO m => VideoFormatPack -> m (GClosure C_VideoFormatPack) Source #
Wrap the callback into a GClosure
.
mk_VideoFormatPack :: C_VideoFormatPack -> IO (FunPtr C_VideoFormatPack) Source #
Generate a function pointer callable from C code, from a C_VideoFormatPack
.
noVideoFormatPack :: Maybe VideoFormatPack Source #
A convenience synonym for
.Nothing
:: Maybe
VideoFormatPack
wrap_VideoFormatPack :: Maybe (Ptr (FunPtr C_VideoFormatPack)) -> VideoFormatPack -> C_VideoFormatPack Source #
Wrap a VideoFormatPack
into a C_VideoFormatPack
.
VideoFormatUnpack
type C_VideoFormatUnpack = Ptr VideoFormatInfo -> CUInt -> Ptr () -> Ptr () -> Int32 -> Int32 -> Int32 -> Int32 -> IO () Source #
Type for the callback on the (unwrapped) C side.
type VideoFormatUnpack Source #
= VideoFormatInfo |
|
-> [VideoPackFlags] |
|
-> Ptr () |
|
-> Ptr () |
|
-> Int32 |
|
-> Int32 |
|
-> Int32 |
|
-> Int32 |
|
-> IO () |
Unpacks width
pixels from the given planes and strides containing data of
format info
. The pixels will be unpacked into dest
with each component
interleaved as per info
's unpack_format, which will usually be one of
GST_VIDEO_FORMAT_ARGB
, GST_VIDEO_FORMAT_AYUV
, GST_VIDEO_FORMAT_ARGB64
or
GST_VIDEO_FORMAT_AYUV64
depending on the format to unpack.
dest
should at least be big enough to hold width
* bytes_per_pixel bytes
where bytes_per_pixel relates to the unpack format and will usually be
either 4 or 8 depending on the unpack format. bytes_per_pixel will be
the same as the pixel stride for plane 0 for the above formats.
For subsampled formats, the components will be duplicated in the destination array. Reconstruction of the missing components can be performed in a separate step after unpacking.
dynamic_VideoFormatUnpack Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_VideoFormatUnpack | |
-> VideoFormatInfo |
|
-> [VideoPackFlags] |
|
-> Ptr () |
|
-> Ptr () |
|
-> Int32 |
|
-> Int32 |
|
-> Int32 |
|
-> Int32 |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_VideoFormatUnpack :: MonadIO m => VideoFormatUnpack -> m (GClosure C_VideoFormatUnpack) Source #
Wrap the callback into a GClosure
.
mk_VideoFormatUnpack :: C_VideoFormatUnpack -> IO (FunPtr C_VideoFormatUnpack) Source #
Generate a function pointer callable from C code, from a C_VideoFormatUnpack
.
noVideoFormatUnpack :: Maybe VideoFormatUnpack Source #
A convenience synonym for
.Nothing
:: Maybe
VideoFormatUnpack
wrap_VideoFormatUnpack :: Maybe (Ptr (FunPtr C_VideoFormatUnpack)) -> VideoFormatUnpack -> C_VideoFormatUnpack Source #
Wrap a VideoFormatUnpack
into a C_VideoFormatUnpack
.
VideoGLTextureUpload
type C_VideoGLTextureUpload = Ptr VideoGLTextureUploadMeta -> Word32 -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type VideoGLTextureUpload = VideoGLTextureUploadMeta -> Word32 -> IO Bool Source #
No description available in the introspection data.
dynamic_VideoGLTextureUpload :: (HasCallStack, MonadIO m) => FunPtr C_VideoGLTextureUpload -> VideoGLTextureUploadMeta -> Word32 -> m Bool Source #
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_VideoGLTextureUpload :: MonadIO m => VideoGLTextureUpload -> m (GClosure C_VideoGLTextureUpload) Source #
Wrap the callback into a GClosure
.
mk_VideoGLTextureUpload :: C_VideoGLTextureUpload -> IO (FunPtr C_VideoGLTextureUpload) Source #
Generate a function pointer callable from C code, from a C_VideoGLTextureUpload
.
noVideoGLTextureUpload :: Maybe VideoGLTextureUpload Source #
A convenience synonym for
.Nothing
:: Maybe
VideoGLTextureUpload
wrap_VideoGLTextureUpload :: Maybe (Ptr (FunPtr C_VideoGLTextureUpload)) -> VideoGLTextureUpload -> C_VideoGLTextureUpload Source #
Wrap a VideoGLTextureUpload
into a C_VideoGLTextureUpload
.
VideoMetaMapFieldCallback
type C_VideoMetaMapFieldCallback = Ptr VideoMeta -> Word32 -> Ptr MapInfo -> Ptr () -> Int32 -> CUInt -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type VideoMetaMapFieldCallback = VideoMeta -> Word32 -> MapInfo -> Ptr () -> Int32 -> [MapFlags] -> IO Bool Source #
No description available in the introspection data.
dynamic_VideoMetaMapFieldCallback :: (HasCallStack, MonadIO m) => FunPtr C_VideoMetaMapFieldCallback -> VideoMeta -> Word32 -> MapInfo -> Ptr () -> Int32 -> [MapFlags] -> m Bool Source #
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_VideoMetaMapFieldCallback :: MonadIO m => VideoMetaMapFieldCallback -> m (GClosure C_VideoMetaMapFieldCallback) Source #
Wrap the callback into a GClosure
.
mk_VideoMetaMapFieldCallback :: C_VideoMetaMapFieldCallback -> IO (FunPtr C_VideoMetaMapFieldCallback) Source #
Generate a function pointer callable from C code, from a C_VideoMetaMapFieldCallback
.
noVideoMetaMapFieldCallback :: Maybe VideoMetaMapFieldCallback Source #
A convenience synonym for
.Nothing
:: Maybe
VideoMetaMapFieldCallback
wrap_VideoMetaMapFieldCallback :: Maybe (Ptr (FunPtr C_VideoMetaMapFieldCallback)) -> VideoMetaMapFieldCallback -> C_VideoMetaMapFieldCallback Source #
Wrap a VideoMetaMapFieldCallback
into a C_VideoMetaMapFieldCallback
.
VideoMetaUnmapFieldCallback
type C_VideoMetaUnmapFieldCallback = Ptr VideoMeta -> Word32 -> Ptr MapInfo -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type VideoMetaUnmapFieldCallback = VideoMeta -> Word32 -> MapInfo -> IO Bool Source #
No description available in the introspection data.
dynamic_VideoMetaUnmapFieldCallback :: (HasCallStack, MonadIO m) => FunPtr C_VideoMetaUnmapFieldCallback -> VideoMeta -> Word32 -> MapInfo -> m Bool Source #
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_VideoMetaUnmapFieldCallback :: MonadIO m => VideoMetaUnmapFieldCallback -> m (GClosure C_VideoMetaUnmapFieldCallback) Source #
Wrap the callback into a GClosure
.
mk_VideoMetaUnmapFieldCallback :: C_VideoMetaUnmapFieldCallback -> IO (FunPtr C_VideoMetaUnmapFieldCallback) Source #
Generate a function pointer callable from C code, from a C_VideoMetaUnmapFieldCallback
.
noVideoMetaUnmapFieldCallback :: Maybe VideoMetaUnmapFieldCallback Source #
A convenience synonym for
.Nothing
:: Maybe
VideoMetaUnmapFieldCallback