Safe Haskell | None |
---|---|
Language | Haskell2010 |
Video decoding API. Includes FFI declarations for the underlying FFmpeg functions, wrappers for these functions that wrap error condition checking, and high level Haskellized interfaces.
Synopsis
- avformat_open_input :: Ptr AVFormatContext -> CString -> Ptr AVInputFormat -> Ptr AVDictionary -> IO CInt
- avformat_find_stream_info :: AVFormatContext -> Ptr () -> IO CInt
- av_find_best_stream :: AVFormatContext -> AVMediaType -> CInt -> CInt -> Ptr AVCodec -> CInt -> IO CInt
- avcodec_find_decoder :: AVCodecID -> IO AVCodec
- avcodec_find_decoder_by_name :: CString -> IO AVCodec
- avpicture_get_size :: AVPixelFormat -> CInt -> CInt -> IO CInt
- av_malloc :: CSize -> IO (Ptr ())
- av_read_frame :: AVFormatContext -> AVPacket -> IO CInt
- decode_video :: AVCodecContext -> AVFrame -> Ptr CInt -> AVPacket -> IO CInt
- close_input :: Ptr AVFormatContext -> IO ()
- av_dict_set :: Ptr AVDictionary -> CString -> CString -> CInt -> IO CInt
- av_find_input_format :: CString -> IO (Ptr AVInputFormat)
- av_format_set_video_codec :: AVFormatContext -> AVCodec -> IO ()
- dictSet :: Ptr AVDictionary -> String -> String -> IO ()
- openCamera :: (MonadIO m, MonadError String m) => String -> CameraConfig -> m AVFormatContext
- openInput :: (MonadIO m, MonadError String m) => InputSource -> m AVFormatContext
- openFile :: (MonadIO m, MonadError String m) => String -> m AVFormatContext
- frameAsPicture :: AVFrame -> AVPicture
- findDecoder :: (MonadIO m, MonadError String m) => String -> m AVCodec
- checkStreams :: (MonadIO m, MonadError String m) => AVFormatContext -> m ()
- findVideoStream :: (MonadIO m, MonadError String m) => AVFormatContext -> m (CInt, AVCodecContext, AVCodec, AVStream)
- getDecoder :: (MonadIO m, MonadError String m) => AVCodecContext -> m AVCodec
- openCodec :: (MonadIO m, MonadError String m) => AVCodecContext -> AVCodec -> m AVDictionary
- read_frame_check :: AVFormatContext -> AVPacket -> IO ()
- frameReader :: (MonadIO m, MonadError String m) => AVPixelFormat -> InputSource -> m (IO (Maybe AVFrame), IO ())
- frameReaderT :: (Functor m, MonadIO m, MonadError String m) => InputSource -> m (MaybeT IO AVFrame, IO ())
- frameReaderTime :: (MonadIO m, MonadError String m) => AVPixelFormat -> InputSource -> m (IO (Maybe (AVFrame, Double)), IO ())
- frameReaderTimeT :: (Functor m, MonadIO m, MonadError String m) => InputSource -> m (MaybeT IO (AVFrame, Double), IO ())
- prepareReader :: (MonadIO m, MonadError String m) => AVFormatContext -> CInt -> AVPixelFormat -> AVCodecContext -> m (IO (Maybe AVFrame), IO ())
FFI Declarations
avformat_open_input :: Ptr AVFormatContext -> CString -> Ptr AVInputFormat -> Ptr AVDictionary -> IO CInt Source #
avformat_find_stream_info :: AVFormatContext -> Ptr () -> IO CInt Source #
av_find_best_stream :: AVFormatContext -> AVMediaType -> CInt -> CInt -> Ptr AVCodec -> CInt -> IO CInt Source #
avpicture_get_size :: AVPixelFormat -> CInt -> CInt -> IO CInt Source #
av_read_frame :: AVFormatContext -> AVPacket -> IO CInt Source #
decode_video :: AVCodecContext -> AVFrame -> Ptr CInt -> AVPacket -> IO CInt Source #
close_input :: Ptr AVFormatContext -> IO () Source #
av_dict_set :: Ptr AVDictionary -> CString -> CString -> CInt -> IO CInt Source #
av_find_input_format :: CString -> IO (Ptr AVInputFormat) Source #
av_format_set_video_codec :: AVFormatContext -> AVCodec -> IO () Source #
FFmpeg Decoding Interface
openCamera :: (MonadIO m, MonadError String m) => String -> CameraConfig -> m AVFormatContext Source #
Open the first video input device enumerated by FFMPEG.
openInput :: (MonadIO m, MonadError String m) => InputSource -> m AVFormatContext Source #
openFile :: (MonadIO m, MonadError String m) => String -> m AVFormatContext Source #
Open an input media file.
frameAsPicture :: AVFrame -> AVPicture Source #
findDecoder :: (MonadIO m, MonadError String m) => String -> m AVCodec Source #
Find a codec given by name.
checkStreams :: (MonadIO m, MonadError String m) => AVFormatContext -> m () Source #
Read packets of a media file to get stream information. This is useful for file formats with no headers such as MPEG.
findVideoStream :: (MonadIO m, MonadError String m) => AVFormatContext -> m (CInt, AVCodecContext, AVCodec, AVStream) Source #
Searches for a video stream in an AVFormatContext
. If one is
found, returns the index of the stream in the container, and its
associated AVCodecContext
and AVCodec
.
getDecoder :: (MonadIO m, MonadError String m) => AVCodecContext -> m AVCodec Source #
Find a registered decoder with a codec ID matching that found in
the given AVCodecContext
.
openCodec :: (MonadIO m, MonadError String m) => AVCodecContext -> AVCodec -> m AVDictionary Source #
Initialize the given AVCodecContext
to use the given
AVCodec
. **NOTE**: This function is not thread safe!
read_frame_check :: AVFormatContext -> AVPacket -> IO () Source #
Return the next frame of a stream.
frameReader :: (MonadIO m, MonadError String m) => AVPixelFormat -> InputSource -> m (IO (Maybe AVFrame), IO ()) Source #
Read frames of the given AVPixelFormat
from a video stream.
frameReaderT :: (Functor m, MonadIO m, MonadError String m) => InputSource -> m (MaybeT IO AVFrame, IO ()) Source #
Read RGB frames with the result in the MaybeT
transformer.
frameReaderT = fmap (first MaybeT) . frameReader
frameReaderTime :: (MonadIO m, MonadError String m) => AVPixelFormat -> InputSource -> m (IO (Maybe (AVFrame, Double)), IO ()) Source #
Read time stamped frames of the given AVPixelFormat
from a
video stream. Time is given in seconds from the start of the
stream.
frameReaderTimeT :: (Functor m, MonadIO m, MonadError String m) => InputSource -> m (MaybeT IO (AVFrame, Double), IO ()) Source #
Read time stamped RGB frames with the result in the MaybeT
transformer.
frameReaderT = fmap (first MaybeT) . frameReader
prepareReader :: (MonadIO m, MonadError String m) => AVFormatContext -> CInt -> AVPixelFormat -> AVCodecContext -> m (IO (Maybe AVFrame), IO ()) Source #
Construct an action that gets the next available frame, and an action to release all resources associated with this video stream.