Safe Haskell | None |
---|---|
Language | Haskell2010 |
Video encoding API. Includes FFI declarations for the underlying FFmpeg functions, wrappers for these functions that wrap error condition checking, and high level Haskellized interfaces.
Note: If you need to import this module, consider qualifying the import.
Synopsis
- avcodec_find_encoder :: AVCodecID -> IO AVCodec
- avcodec_find_encoder_by_name :: CString -> IO AVCodec
- av_opt_set :: Ptr () -> CString -> CString -> CInt -> IO CInt
- avcodec_encode_video2 :: AVCodecContext -> AVPacket -> AVFrame -> Ptr CInt -> IO CInt
- av_image_alloc :: Ptr (Ptr CUChar) -> Ptr CInt -> CInt -> CInt -> AVPixelFormat -> CInt -> IO CInt
- av_freep :: Ptr (Ptr a) -> IO ()
- av_guess_format :: CString -> CString -> CString -> IO AVOutputFormat
- avformat_alloc_output_context2 :: Ptr AVFormatContext -> AVOutputFormat -> CString -> CString -> IO CInt
- avformat_new_stream :: AVFormatContext -> AVCodec -> IO AVStream
- av_write_frame :: AVFormatContext -> AVPacket -> IO CInt
- av_interleaved_write_frame :: AVFormatContext -> AVPacket -> IO CInt
- avformat_write_header :: AVFormatContext -> Ptr AVDictionary -> IO CInt
- av_write_trailer :: AVFormatContext -> IO CInt
- avio_open :: Ptr AVIOContext -> CString -> AVIOFlag -> IO CInt
- avio_close :: AVIOContext -> IO CInt
- avformat_free_context :: AVFormatContext -> IO ()
- av_image_fill_arrays :: Ptr (Ptr CUChar) -> Ptr CInt -> Ptr CUChar -> AVPixelFormat -> CInt -> CInt -> CInt -> IO CInt
- av_image_fill_linesizes :: Ptr CInt -> AVPixelFormat -> CInt -> IO CInt
- data EncodingParams = EncodingParams {}
- defaultH264 :: CInt -> CInt -> EncodingParams
- defaultParams :: CInt -> CInt -> EncodingParams
- checkFlag :: Bits a => a -> a -> Bool
- initStream :: EncodingParams -> AVFormatContext -> IO (AVStream, AVCodecContext)
- initTempFrame :: EncodingParams -> AVPixelFormat -> IO AVFrame
- allocOutputContext :: Maybe String -> FilePath -> IO AVFormatContext
- avio_open_check :: AVFormatContext -> String -> IO ()
- avio_close_check :: AVFormatContext -> IO ()
- encode_video_check :: AVCodecContext -> AVPacket -> Maybe AVFrame -> IO Bool
- write_header_check :: AVFormatContext -> IO ()
- write_frame_check :: AVFormatContext -> AVPacket -> IO ()
- write_trailer_check :: AVFormatContext -> IO ()
- palettizeRGB8 :: EncodingParams -> Vector CUChar -> Vector CUChar
- palettizeJuicy :: EncodingParams -> Vector CUChar -> Vector CUChar
- frameWriter :: EncodingParams -> FilePath -> IO (Maybe (AVPixelFormat, V2 CInt, Vector CUChar) -> IO ())
- frameWriterRgb :: EncodingParams -> FilePath -> IO (Maybe (Vector CUChar) -> IO ())
FFI Declarations
avcodec_encode_video2 :: AVCodecContext -> AVPacket -> AVFrame -> Ptr CInt -> IO CInt Source #
av_image_alloc :: Ptr (Ptr CUChar) -> Ptr CInt -> CInt -> CInt -> AVPixelFormat -> CInt -> IO CInt Source #
av_guess_format :: CString -> CString -> CString -> IO AVOutputFormat Source #
avformat_alloc_output_context2 :: Ptr AVFormatContext -> AVOutputFormat -> CString -> CString -> IO CInt Source #
avformat_new_stream :: AVFormatContext -> AVCodec -> IO AVStream Source #
av_write_frame :: AVFormatContext -> AVPacket -> IO CInt Source #
avformat_write_header :: AVFormatContext -> Ptr AVDictionary -> IO CInt Source #
av_write_trailer :: AVFormatContext -> IO CInt Source #
avio_close :: AVIOContext -> IO CInt Source #
avformat_free_context :: AVFormatContext -> IO () Source #
av_image_fill_arrays :: Ptr (Ptr CUChar) -> Ptr CInt -> Ptr CUChar -> AVPixelFormat -> CInt -> CInt -> CInt -> IO CInt Source #
av_image_fill_linesizes :: Ptr CInt -> AVPixelFormat -> CInt -> IO CInt Source #
FFmpeg Encoding Interface
data EncodingParams Source #
Minimal parameters describing the desired video output.
EncodingParams | |
|
defaultH264 :: CInt -> CInt -> EncodingParams Source #
Use default parameters for a video of the given width and height, forcing the choice of the h264 encoder.
defaultParams :: CInt -> CInt -> EncodingParams Source #
Use default parameters for a video of the given width and height. The output format is determined by the output file name.
checkFlag :: Bits a => a -> a -> Bool Source #
Determine if the bitwise intersection of two values is non-zero.
initStream :: EncodingParams -> AVFormatContext -> IO (AVStream, AVCodecContext) Source #
Find and initialize the requested encoder, and add a video stream to the output container.
initTempFrame :: EncodingParams -> AVPixelFormat -> IO AVFrame Source #
Initialize a temporary YUV frame of the same resolution as the output video stream. We well convert RGB frames using this frame as a destination before encoding the video frame.
allocOutputContext :: Maybe String -> FilePath -> IO AVFormatContext Source #
Allocate an output context inferring the codec from the given file name.
avio_open_check :: AVFormatContext -> String -> IO () Source #
Open the given file for writing.
avio_close_check :: AVFormatContext -> IO () Source #
Close an open IO context.
encode_video_check :: AVCodecContext -> AVPacket -> Maybe AVFrame -> IO Bool Source #
write_header_check :: AVFormatContext -> IO () Source #
Allocate the stream private data and write the stream header to an output media file.
write_frame_check :: AVFormatContext -> AVPacket -> IO () Source #
Write a packet to an output media file.
write_trailer_check :: AVFormatContext -> IO () Source #
Write the stream trailer to an output media file and free the
private data. May only be called after a successful call to
write_header_check
.
palettizeRGB8 :: EncodingParams -> Vector CUChar -> Vector CUChar Source #
Quantize RGB24 pixels to the systematic RGB8 color palette. The
image data has space for a palette appended to be compliant with
av_image_fill_arrays'
s expectations. This is slow.
palettizeJuicy :: EncodingParams -> Vector CUChar -> Vector CUChar Source #
High quality dithered, median cut palette using palettize
. The
result is packed such that the BGRA palette is laid out
contiguously following the palettized image data.
frameWriter :: EncodingParams -> FilePath -> IO (Maybe (AVPixelFormat, V2 CInt, Vector CUChar) -> IO ()) Source #
Open a target file for writing a video stream. The function
returned may be used to write image frames (specified by a pixel
format, resolution, and pixel data). If this function is applied to
Nothing
, then the output stream is closed. Note that Nothing
must be provided to properly terminate video encoding.
Support for source images that are of a different size to the
output resolution is limited to non-palettized destination formats
(i.e. those that are handled by libswscaler
). Practically, this
means that animated gif output only works if the source images are
of the target resolution.
frameWriterRgb :: EncodingParams -> FilePath -> IO (Maybe (Vector CUChar) -> IO ()) Source #
Open a target file for writing a video stream. The function
returned may be used to write RGB images of the resolution given by
the provided EncodingParams
(i.e. the same resolution as the
output video). If this function is applied to Nothing
, then the
output stream is closed. Note that Nothing
must be provided to
properly terminate video encoding.