Safe Haskell | None |
---|---|
Language | Haskell2010 |
Convert between FFmpeg frames and JuicyPixels images.
Synopsis
- frameToVector :: AVFrame -> IO (Maybe (Vector CUChar))
- frameToVectorT :: AVFrame -> MaybeT IO (Vector CUChar)
- toJuicyT :: AVFrame -> MaybeT IO DynamicImage
- toJuicy :: AVFrame -> IO (Maybe DynamicImage)
- toJuicyImage :: forall p. JuicyPixelFormat p => AVFrame -> IO (Maybe (Image p))
- saveJuicy :: FilePath -> AVFrame -> IO ()
- class Pixel a => JuicyPixelFormat a where
- juicyPixelFormat :: proxy a -> AVPixelFormat
- juicyPixelStride :: forall a proxy. Pixel a => proxy a -> Int
- imageReaderT :: forall m p. (Functor m, MonadIO m, MonadError String m, JuicyPixelFormat p) => InputSource -> m (IO (Maybe (Image p)), IO ())
- imageReader :: JuicyPixelFormat p => InputSource -> IO (IO (Maybe (Image p)), IO ())
- imageReaderTimeT :: forall m p. (Functor m, MonadIO m, MonadError String m, JuicyPixelFormat p) => InputSource -> m (IO (Maybe (Image p, Double)), IO ())
- imageReaderTime :: JuicyPixelFormat p => InputSource -> IO (IO (Maybe (Image p, Double)), IO ())
- imageWriter :: forall p. JuicyPixelFormat p => EncodingParams -> FilePath -> IO (Maybe (Image p) -> IO ())
Documentation
toJuicyImage :: forall p. JuicyPixelFormat p => AVFrame -> IO (Maybe (Image p)) Source #
Convert an AVFrame
to an Image
.
class Pixel a => JuicyPixelFormat a where Source #
Mapping of JuicyPixels
pixel types to FFmpeg pixel formats.
juicyPixelFormat :: proxy a -> AVPixelFormat Source #
Instances
JuicyPixelFormat Pixel8 Source # | |
Defined in Codec.FFmpeg.Juicy juicyPixelFormat :: proxy Pixel8 -> AVPixelFormat Source # | |
JuicyPixelFormat PixelRGB8 Source # | |
Defined in Codec.FFmpeg.Juicy juicyPixelFormat :: proxy PixelRGB8 -> AVPixelFormat Source # | |
JuicyPixelFormat PixelRGBA8 Source # | |
Defined in Codec.FFmpeg.Juicy juicyPixelFormat :: proxy PixelRGBA8 -> AVPixelFormat Source # |
juicyPixelStride :: forall a proxy. Pixel a => proxy a -> Int Source #
Bytes-per-pixel for a JuicyPixels Pixel
type.
imageReaderT :: forall m p. (Functor m, MonadIO m, MonadError String m, JuicyPixelFormat p) => InputSource -> m (IO (Maybe (Image p)), IO ()) Source #
Read frames from a video stream.
imageReader :: JuicyPixelFormat p => InputSource -> IO (IO (Maybe (Image p)), IO ()) Source #
Read frames from a video stream. Errors are thrown as
IOException
s.
imageReaderTimeT :: forall m p. (Functor m, MonadIO m, MonadError String m, JuicyPixelFormat p) => InputSource -> m (IO (Maybe (Image p, Double)), IO ()) Source #
Read time stamped frames from a video stream. Time is given in seconds from the start of the stream.
imageReaderTime :: JuicyPixelFormat p => InputSource -> IO (IO (Maybe (Image p, Double)), IO ()) Source #
Read time stamped frames from a video stream. Time is given in
seconds from the start of the stream. Errors are thrown as
IOException
s.
imageWriter :: forall p. JuicyPixelFormat p => EncodingParams -> FilePath -> IO (Maybe (Image p) -> IO ()) Source #
Open a target file for writing a video stream. When the returned
function is applied to Nothing
, the output stream is closed. Note
that Nothing
must be provided when finishing in order 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 is only supported if the source
images are of the target resolution.