Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- class HasPtr a where
- newtype AVFormatContext = AVFormatContext (Ptr ())
- class HasNumStreams t where
- getNumStreams :: t -> IO CInt
- setNumStreams :: t -> CInt -> IO ()
- hasNumStreams :: t -> Ptr CInt
- class HasStreams t where
- getStreams :: t -> IO (Ptr AVStream)
- setStreams :: t -> Ptr AVStream -> IO ()
- hasStreams :: t -> Ptr (Ptr AVStream)
- class HasOutputFormat t where
- getOutputFormat :: t -> IO AVOutputFormat
- setOutputFormat :: t -> AVOutputFormat -> IO ()
- hasOutputFormat :: t -> Ptr AVOutputFormat
- class HasIOContext t where
- getIOContext :: t -> IO AVIOContext
- setIOContext :: t -> AVIOContext -> IO ()
- hasIOContext :: t -> Ptr AVIOContext
- class HasInputFormat t where
- getInputFormat :: t -> IO AVInputFormat
- setInputFormat :: t -> AVInputFormat -> IO ()
- hasInputFormat :: t -> Ptr AVInputFormat
- setFilename :: AVFormatContext -> String -> IO ()
- av_input_video_device_next :: AVInputFormat -> IO AVInputFormat
- setCamera :: AVFormatContext -> IO ()
- avformat_alloc_context :: IO (Ptr ())
- mallocAVFormatContext :: IO AVFormatContext
- newtype AVCodecContext = AVCodecContext (Ptr ())
- class HasBitRate t where
- getBitRate :: t -> IO CInt
- setBitRate :: t -> CInt -> IO ()
- hasBitRate :: t -> Ptr CInt
- class HasWidth t where
- class HasHeight t where
- class HasTimeBase t where
- getTimeBase :: t -> IO AVRational
- setTimeBase :: t -> AVRational -> IO ()
- hasTimeBase :: t -> Ptr AVRational
- class HasGopSize t where
- getGopSize :: t -> IO CInt
- setGopSize :: t -> CInt -> IO ()
- hasGopSize :: t -> Ptr CInt
- class HasPixelFormat t where
- getPixelFormat :: t -> IO AVPixelFormat
- setPixelFormat :: t -> AVPixelFormat -> IO ()
- hasPixelFormat :: t -> Ptr AVPixelFormat
- class HasCodecFlags t where
- getCodecFlags :: t -> IO CodecFlag
- setCodecFlags :: t -> CodecFlag -> IO ()
- hasCodecFlags :: t -> Ptr CodecFlag
- class HasCodecID t where
- getCodecID :: t -> IO AVCodecID
- setCodecID :: t -> AVCodecID -> IO ()
- hasCodecID :: t -> Ptr AVCodecID
- class HasPrivData t where
- getPrivData :: t -> IO (Ptr ())
- setPrivData :: t -> Ptr () -> IO ()
- hasPrivData :: t -> Ptr (Ptr ())
- class HasTicksPerFrame t where
- getTicksPerFrame :: t -> IO CInt
- setTicksPerFrame :: t -> CInt -> IO ()
- hasTicksPerFrame :: t -> Ptr CInt
- class HasRawAspectRatio t where
- getRawAspectRatio :: t -> IO AVRational
- setRawAspectRatio :: t -> AVRational -> IO ()
- hasRawAspectRatio :: t -> Ptr AVRational
- getFps :: (HasTimeBase a, HasTicksPerFrame a) => a -> IO CDouble
- getAspectRatio :: HasRawAspectRatio a => a -> IO (Maybe AVRational)
- guessAspectRatio :: HasRawAspectRatio a => a -> IO AVRational
- setAspectRatio :: HasRawAspectRatio a => a -> Maybe AVRational -> IO ()
- newtype AVStream = AVStream (Ptr ())
- class HasId t where
- class HasCodecContext t where
- getCodecContext :: t -> IO AVCodecContext
- setCodecContext :: t -> AVCodecContext -> IO ()
- hasCodecContext :: t -> Ptr AVCodecContext
- class HasStreamIndex t where
- getStreamIndex :: t -> IO CInt
- setStreamIndex :: t -> CInt -> IO ()
- hasStreamIndex :: t -> Ptr CInt
- newtype AVCodec = AVCodec (Ptr ())
- class HasLongName t where
- getLongName :: t -> IO CString
- setLongName :: t -> CString -> IO ()
- hasLongName :: t -> Ptr CString
- class HasName t where
- class HasPixelFormats t where
- getPixelFormats :: t -> IO (Ptr AVPixelFormat)
- setPixelFormats :: t -> Ptr AVPixelFormat -> IO ()
- hasPixelFormats :: t -> Ptr (Ptr AVPixelFormat)
- newtype AVDictionary = AVDictionary (Ptr ())
- newtype AVFrame = AVFrame (Ptr ())
- class HasPts t where
- class HasPktPts t where
- class HasLineSize t where
- getLineSize :: t -> IO CInt
- setLineSize :: t -> CInt -> IO ()
- hasLineSize :: t -> Ptr CInt
- newtype AVPicture = AVPicture (Ptr ())
- newtype SwsContext = SwsContext (Ptr ())
- newtype AVOutputFormat = AVOutputFormat (Ptr ())
- class HasFormatFlags t where
- getFormatFlags :: t -> IO FormatFlag
- setFormatFlags :: t -> FormatFlag -> IO ()
- hasFormatFlags :: t -> Ptr FormatFlag
- class HasVideoCodecID t where
- getVideoCodecID :: t -> IO AVCodecID
- setVideoCodecID :: t -> AVCodecID -> IO ()
- hasVideoCodecID :: t -> Ptr AVCodecID
- newtype AVInputFormat = AVInputFormat (Ptr ())
- newtype AVClass = AVClass (Ptr ())
- class HasAVClass t where
- getAVClass :: t -> IO AVClass
- setAVClass :: t -> AVClass -> IO ()
- hasAVClass :: t -> Ptr AVClass
- getAVCategory :: AVInputFormat -> IO Category
- newtype Category = Category CInt
- avClassCategoryNa :: Category
- avClassCategoryInput :: Category
- avClassCategoryOutput :: Category
- avClassCategoryMuxer :: Category
- avClassCategoryDemuxer :: Category
- newtype AVIOContext = AVIOContext (Ptr ())
- avClassCategoryEncoder :: Category
- newtype AVPacket = AVPacket (Ptr ())
- avClassCategoryDecoder :: Category
- class HasData t where
- class HasSize t where
- avClassCategoryFilter :: Category
- class HasPacketFlags t where
- getPacketFlags :: t -> IO PacketFlag
- setPacketFlags :: t -> PacketFlag -> IO ()
- hasPacketFlags :: t -> Ptr PacketFlag
- class HasDts t where
- avClassCategoryBitstreamFilter :: Category
- avClassCategorySwscaler :: Category
- avClassCategorySwresampler :: Category
- avClassCategoryDeviceVideoOutput :: Category
- avClassCategoryDeviceVideoInput :: Category
- packetSize :: Int
- avClassCategoryDeviceAudioOutput :: Category
- pictureSize :: Int
- avClassCategoryDeviceAudioInput :: Category
- avClassCategoryDeviceOutput :: Category
- avClassCategoryDeviceInput :: Category
- data AVRational = AVRational {
- numerator :: CInt
- denomenator :: CInt
- avClassCategoryNb :: Category
- nonZeroAVRational :: AVRational -> Maybe AVRational
- av_rescale_rnd :: CLong -> CLong -> CLong -> AVRoundMode -> CLong
- av_q2d :: AVRational -> CDouble
- av_rescale_q :: CLong -> AVRational -> AVRational -> CLong
- data InputSource
- data CameraConfig = CameraConfig {}
- defaultCameraConfig :: CameraConfig
Documentation
Instances
HasPtr AVPacket Source # | |
HasPtr AVIOContext Source # | |
Defined in Codec.FFmpeg.Types getPtr :: AVIOContext -> Ptr () Source # | |
HasPtr AVClass Source # | |
HasPtr AVInputFormat Source # | |
Defined in Codec.FFmpeg.Types getPtr :: AVInputFormat -> Ptr () Source # | |
HasPtr AVOutputFormat Source # | |
Defined in Codec.FFmpeg.Types getPtr :: AVOutputFormat -> Ptr () Source # | |
HasPtr SwsContext Source # | |
Defined in Codec.FFmpeg.Types getPtr :: SwsContext -> Ptr () Source # | |
HasPtr AVPicture Source # | |
HasPtr AVFrame Source # | |
HasPtr AVDictionary Source # | |
Defined in Codec.FFmpeg.Types getPtr :: AVDictionary -> Ptr () Source # | |
HasPtr AVCodec Source # | |
HasPtr AVStream Source # | |
HasPtr AVCodecContext Source # | |
Defined in Codec.FFmpeg.Types getPtr :: AVCodecContext -> Ptr () Source # | |
HasPtr AVFormatContext Source # | |
Defined in Codec.FFmpeg.Types getPtr :: AVFormatContext -> Ptr () Source # | |
HasPtr (Ptr ()) Source # | |
newtype AVFormatContext Source #
AVFormatContext (Ptr ()) |
Instances
class HasNumStreams t where Source #
getNumStreams :: t -> IO CInt Source #
setNumStreams :: t -> CInt -> IO () Source #
hasNumStreams :: t -> Ptr CInt Source #
Instances
HasNumStreams AVFormatContext Source # | |
Defined in Codec.FFmpeg.Types getNumStreams :: AVFormatContext -> IO CInt Source # setNumStreams :: AVFormatContext -> CInt -> IO () Source # hasNumStreams :: AVFormatContext -> Ptr CInt Source # |
class HasStreams t where Source #
Instances
HasStreams AVFormatContext Source # | |
Defined in Codec.FFmpeg.Types getStreams :: AVFormatContext -> IO (Ptr AVStream) Source # setStreams :: AVFormatContext -> Ptr AVStream -> IO () Source # hasStreams :: AVFormatContext -> Ptr (Ptr AVStream) Source # |
class HasOutputFormat t where Source #
getOutputFormat :: t -> IO AVOutputFormat Source #
setOutputFormat :: t -> AVOutputFormat -> IO () Source #
hasOutputFormat :: t -> Ptr AVOutputFormat Source #
Instances
HasOutputFormat AVFormatContext Source # | |
Defined in Codec.FFmpeg.Types |
class HasIOContext t where Source #
getIOContext :: t -> IO AVIOContext Source #
setIOContext :: t -> AVIOContext -> IO () Source #
hasIOContext :: t -> Ptr AVIOContext Source #
Instances
HasIOContext AVFormatContext Source # | |
Defined in Codec.FFmpeg.Types getIOContext :: AVFormatContext -> IO AVIOContext Source # setIOContext :: AVFormatContext -> AVIOContext -> IO () Source # |
class HasInputFormat t where Source #
getInputFormat :: t -> IO AVInputFormat Source #
setInputFormat :: t -> AVInputFormat -> IO () Source #
hasInputFormat :: t -> Ptr AVInputFormat Source #
Instances
HasInputFormat AVFormatContext Source # | |
Defined in Codec.FFmpeg.Types getInputFormat :: AVFormatContext -> IO AVInputFormat Source # setInputFormat :: AVFormatContext -> AVInputFormat -> IO () Source # hasInputFormat :: AVFormatContext -> Ptr AVInputFormat Source # |
setFilename :: AVFormatContext -> String -> IO () Source #
setCamera :: AVFormatContext -> IO () Source #
avformat_alloc_context :: IO (Ptr ()) Source #
newtype AVCodecContext Source #
AVCodecContext (Ptr ()) |
Instances
class HasBitRate t where Source #
getBitRate :: t -> IO CInt Source #
setBitRate :: t -> CInt -> IO () Source #
hasBitRate :: t -> Ptr CInt Source #
Instances
HasBitRate AVCodecContext Source # | |
Defined in Codec.FFmpeg.Types getBitRate :: AVCodecContext -> IO CInt Source # setBitRate :: AVCodecContext -> CInt -> IO () Source # hasBitRate :: AVCodecContext -> Ptr CInt Source # |
class HasWidth t where Source #
Instances
HasWidth AVFrame Source # | |
HasWidth AVCodecContext Source # | |
Defined in Codec.FFmpeg.Types |
class HasHeight t where Source #
Instances
HasHeight AVFrame Source # | |
HasHeight AVCodecContext Source # | |
Defined in Codec.FFmpeg.Types |
class HasTimeBase t where Source #
getTimeBase :: t -> IO AVRational Source #
setTimeBase :: t -> AVRational -> IO () Source #
hasTimeBase :: t -> Ptr AVRational Source #
Instances
HasTimeBase AVStream Source # | |
Defined in Codec.FFmpeg.Types getTimeBase :: AVStream -> IO AVRational Source # setTimeBase :: AVStream -> AVRational -> IO () Source # hasTimeBase :: AVStream -> Ptr AVRational Source # | |
HasTimeBase AVCodecContext Source # | |
Defined in Codec.FFmpeg.Types getTimeBase :: AVCodecContext -> IO AVRational Source # setTimeBase :: AVCodecContext -> AVRational -> IO () Source # |
class HasGopSize t where Source #
getGopSize :: t -> IO CInt Source #
setGopSize :: t -> CInt -> IO () Source #
hasGopSize :: t -> Ptr CInt Source #
Instances
HasGopSize AVCodecContext Source # | |
Defined in Codec.FFmpeg.Types getGopSize :: AVCodecContext -> IO CInt Source # setGopSize :: AVCodecContext -> CInt -> IO () Source # hasGopSize :: AVCodecContext -> Ptr CInt Source # |
class HasPixelFormat t where Source #
getPixelFormat :: t -> IO AVPixelFormat Source #
setPixelFormat :: t -> AVPixelFormat -> IO () Source #
hasPixelFormat :: t -> Ptr AVPixelFormat Source #
Instances
HasPixelFormat AVFrame Source # | |
Defined in Codec.FFmpeg.Types getPixelFormat :: AVFrame -> IO AVPixelFormat Source # setPixelFormat :: AVFrame -> AVPixelFormat -> IO () Source # hasPixelFormat :: AVFrame -> Ptr AVPixelFormat Source # | |
HasPixelFormat AVCodecContext Source # | |
Defined in Codec.FFmpeg.Types getPixelFormat :: AVCodecContext -> IO AVPixelFormat Source # setPixelFormat :: AVCodecContext -> AVPixelFormat -> IO () Source # hasPixelFormat :: AVCodecContext -> Ptr AVPixelFormat Source # |
class HasCodecFlags t where Source #
getCodecFlags :: t -> IO CodecFlag Source #
setCodecFlags :: t -> CodecFlag -> IO () Source #
hasCodecFlags :: t -> Ptr CodecFlag Source #
Instances
HasCodecFlags AVCodecContext Source # | |
Defined in Codec.FFmpeg.Types getCodecFlags :: AVCodecContext -> IO CodecFlag Source # setCodecFlags :: AVCodecContext -> CodecFlag -> IO () Source # |
class HasCodecID t where Source #
getCodecID :: t -> IO AVCodecID Source #
setCodecID :: t -> AVCodecID -> IO () Source #
hasCodecID :: t -> Ptr AVCodecID Source #
Instances
HasCodecID AVCodec Source # | |
Defined in Codec.FFmpeg.Types | |
HasCodecID AVCodecContext Source # | |
Defined in Codec.FFmpeg.Types getCodecID :: AVCodecContext -> IO AVCodecID Source # setCodecID :: AVCodecContext -> AVCodecID -> IO () Source # hasCodecID :: AVCodecContext -> Ptr AVCodecID Source # |
class HasPrivData t where Source #
getPrivData :: t -> IO (Ptr ()) Source #
setPrivData :: t -> Ptr () -> IO () Source #
hasPrivData :: t -> Ptr (Ptr ()) Source #
Instances
HasPrivData AVCodecContext Source # | |
Defined in Codec.FFmpeg.Types getPrivData :: AVCodecContext -> IO (Ptr ()) Source # setPrivData :: AVCodecContext -> Ptr () -> IO () Source # hasPrivData :: AVCodecContext -> Ptr (Ptr ()) Source # |
class HasTicksPerFrame t where Source #
getTicksPerFrame :: t -> IO CInt Source #
setTicksPerFrame :: t -> CInt -> IO () Source #
hasTicksPerFrame :: t -> Ptr CInt Source #
Instances
HasTicksPerFrame AVCodecContext Source # | |
Defined in Codec.FFmpeg.Types getTicksPerFrame :: AVCodecContext -> IO CInt Source # setTicksPerFrame :: AVCodecContext -> CInt -> IO () Source # hasTicksPerFrame :: AVCodecContext -> Ptr CInt Source # |
class HasRawAspectRatio t where Source #
getRawAspectRatio :: t -> IO AVRational Source #
setRawAspectRatio :: t -> AVRational -> IO () Source #
hasRawAspectRatio :: t -> Ptr AVRational Source #
Instances
HasRawAspectRatio AVCodecContext Source # | |
Defined in Codec.FFmpeg.Types getRawAspectRatio :: AVCodecContext -> IO AVRational Source # setRawAspectRatio :: AVCodecContext -> AVRational -> IO () Source # hasRawAspectRatio :: AVCodecContext -> Ptr AVRational Source # |
getFps :: (HasTimeBase a, HasTicksPerFrame a) => a -> IO CDouble Source #
getAspectRatio :: HasRawAspectRatio a => a -> IO (Maybe AVRational) Source #
guessAspectRatio :: HasRawAspectRatio a => a -> IO AVRational Source #
When unspecified, the most likely pixel shape is a square
setAspectRatio :: HasRawAspectRatio a => a -> Maybe AVRational -> IO () Source #
Instances
Storable AVStream Source # | |
HasStreamIndex AVStream Source # | |
Defined in Codec.FFmpeg.Types | |
HasCodecContext AVStream Source # | |
Defined in Codec.FFmpeg.Types getCodecContext :: AVStream -> IO AVCodecContext Source # setCodecContext :: AVStream -> AVCodecContext -> IO () Source # | |
HasId AVStream Source # | |
HasTimeBase AVStream Source # | |
Defined in Codec.FFmpeg.Types getTimeBase :: AVStream -> IO AVRational Source # setTimeBase :: AVStream -> AVRational -> IO () Source # hasTimeBase :: AVStream -> Ptr AVRational Source # | |
HasPtr AVStream Source # | |
Monad m => MonadReader AVStream (AvStreamT m) Source # | |
class HasCodecContext t where Source #
getCodecContext :: t -> IO AVCodecContext Source #
setCodecContext :: t -> AVCodecContext -> IO () Source #
hasCodecContext :: t -> Ptr AVCodecContext Source #
Instances
HasCodecContext AVStream Source # | |
Defined in Codec.FFmpeg.Types getCodecContext :: AVStream -> IO AVCodecContext Source # setCodecContext :: AVStream -> AVCodecContext -> IO () Source # |
class HasStreamIndex t where Source #
getStreamIndex :: t -> IO CInt Source #
setStreamIndex :: t -> CInt -> IO () Source #
hasStreamIndex :: t -> Ptr CInt Source #
Instances
HasStreamIndex AVPacket Source # | |
Defined in Codec.FFmpeg.Types | |
HasStreamIndex AVStream Source # | |
Defined in Codec.FFmpeg.Types |
Instances
Storable AVCodec Source # | |
HasPixelFormats AVCodec Source # | |
Defined in Codec.FFmpeg.Types getPixelFormats :: AVCodec -> IO (Ptr AVPixelFormat) Source # setPixelFormats :: AVCodec -> Ptr AVPixelFormat -> IO () Source # hasPixelFormats :: AVCodec -> Ptr (Ptr AVPixelFormat) Source # | |
HasName AVCodec Source # | |
HasLongName AVCodec Source # | |
Defined in Codec.FFmpeg.Types | |
HasCodecID AVCodec Source # | |
Defined in Codec.FFmpeg.Types | |
HasPtr AVCodec Source # | |
class HasLongName t where Source #
getLongName :: t -> IO CString Source #
setLongName :: t -> CString -> IO () Source #
hasLongName :: t -> Ptr CString Source #
Instances
HasLongName AVCodec Source # | |
Defined in Codec.FFmpeg.Types |
class HasPixelFormats t where Source #
getPixelFormats :: t -> IO (Ptr AVPixelFormat) Source #
setPixelFormats :: t -> Ptr AVPixelFormat -> IO () Source #
hasPixelFormats :: t -> Ptr (Ptr AVPixelFormat) Source #
Instances
HasPixelFormats AVCodec Source # | |
Defined in Codec.FFmpeg.Types getPixelFormats :: AVCodec -> IO (Ptr AVPixelFormat) Source # setPixelFormats :: AVCodec -> Ptr AVPixelFormat -> IO () Source # hasPixelFormats :: AVCodec -> Ptr (Ptr AVPixelFormat) Source # |
newtype AVDictionary Source #
AVDictionary (Ptr ()) |
Instances
Storable AVDictionary Source # | |
Defined in Codec.FFmpeg.Types sizeOf :: AVDictionary -> Int # alignment :: AVDictionary -> Int # peekElemOff :: Ptr AVDictionary -> Int -> IO AVDictionary # pokeElemOff :: Ptr AVDictionary -> Int -> AVDictionary -> IO () # peekByteOff :: Ptr b -> Int -> IO AVDictionary # pokeByteOff :: Ptr b -> Int -> AVDictionary -> IO () # peek :: Ptr AVDictionary -> IO AVDictionary # poke :: Ptr AVDictionary -> AVDictionary -> IO () # | |
HasPtr AVDictionary Source # | |
Defined in Codec.FFmpeg.Types getPtr :: AVDictionary -> Ptr () Source # |
Instances
Storable AVFrame Source # | |
HasData AVFrame Source # | |
HasLineSize AVFrame Source # | |
Defined in Codec.FFmpeg.Types | |
HasPktPts AVFrame Source # | |
HasPts AVFrame Source # | |
HasPixelFormat AVFrame Source # | |
Defined in Codec.FFmpeg.Types getPixelFormat :: AVFrame -> IO AVPixelFormat Source # setPixelFormat :: AVFrame -> AVPixelFormat -> IO () Source # hasPixelFormat :: AVFrame -> Ptr AVPixelFormat Source # | |
HasHeight AVFrame Source # | |
HasWidth AVFrame Source # | |
HasPtr AVFrame Source # | |
SwsCompatible AVFrame Source # | |
class HasLineSize t where Source #
getLineSize :: t -> IO CInt Source #
setLineSize :: t -> CInt -> IO () Source #
hasLineSize :: t -> Ptr CInt Source #
Instances
HasLineSize AVFrame Source # | |
Defined in Codec.FFmpeg.Types |
Instances
Storable AVPicture Source # | |
Defined in Codec.FFmpeg.Types | |
HasData AVPicture Source # | |
HasPtr AVPicture Source # | |
newtype SwsContext Source #
SwsContext (Ptr ()) |
Instances
Storable SwsContext Source # | |
Defined in Codec.FFmpeg.Types sizeOf :: SwsContext -> Int # alignment :: SwsContext -> Int # peekElemOff :: Ptr SwsContext -> Int -> IO SwsContext # pokeElemOff :: Ptr SwsContext -> Int -> SwsContext -> IO () # peekByteOff :: Ptr b -> Int -> IO SwsContext # pokeByteOff :: Ptr b -> Int -> SwsContext -> IO () # peek :: Ptr SwsContext -> IO SwsContext # poke :: Ptr SwsContext -> SwsContext -> IO () # | |
HasPtr SwsContext Source # | |
Defined in Codec.FFmpeg.Types getPtr :: SwsContext -> Ptr () Source # |
newtype AVOutputFormat Source #
AVOutputFormat (Ptr ()) |
Instances
Storable AVOutputFormat Source # | |
Defined in Codec.FFmpeg.Types sizeOf :: AVOutputFormat -> Int # alignment :: AVOutputFormat -> Int # peekElemOff :: Ptr AVOutputFormat -> Int -> IO AVOutputFormat # pokeElemOff :: Ptr AVOutputFormat -> Int -> AVOutputFormat -> IO () # peekByteOff :: Ptr b -> Int -> IO AVOutputFormat # pokeByteOff :: Ptr b -> Int -> AVOutputFormat -> IO () # peek :: Ptr AVOutputFormat -> IO AVOutputFormat # poke :: Ptr AVOutputFormat -> AVOutputFormat -> IO () # | |
HasVideoCodecID AVOutputFormat Source # | |
Defined in Codec.FFmpeg.Types getVideoCodecID :: AVOutputFormat -> IO AVCodecID Source # setVideoCodecID :: AVOutputFormat -> AVCodecID -> IO () Source # | |
HasFormatFlags AVOutputFormat Source # | |
Defined in Codec.FFmpeg.Types getFormatFlags :: AVOutputFormat -> IO FormatFlag Source # setFormatFlags :: AVOutputFormat -> FormatFlag -> IO () Source # | |
HasPtr AVOutputFormat Source # | |
Defined in Codec.FFmpeg.Types getPtr :: AVOutputFormat -> Ptr () Source # |
class HasFormatFlags t where Source #
getFormatFlags :: t -> IO FormatFlag Source #
setFormatFlags :: t -> FormatFlag -> IO () Source #
hasFormatFlags :: t -> Ptr FormatFlag Source #
Instances
HasFormatFlags AVOutputFormat Source # | |
Defined in Codec.FFmpeg.Types getFormatFlags :: AVOutputFormat -> IO FormatFlag Source # setFormatFlags :: AVOutputFormat -> FormatFlag -> IO () Source # |
class HasVideoCodecID t where Source #
getVideoCodecID :: t -> IO AVCodecID Source #
setVideoCodecID :: t -> AVCodecID -> IO () Source #
hasVideoCodecID :: t -> Ptr AVCodecID Source #
Instances
HasVideoCodecID AVOutputFormat Source # | |
Defined in Codec.FFmpeg.Types getVideoCodecID :: AVOutputFormat -> IO AVCodecID Source # setVideoCodecID :: AVOutputFormat -> AVCodecID -> IO () Source # | |
HasVideoCodecID AVFormatContext Source # | |
Defined in Codec.FFmpeg.Types getVideoCodecID :: AVFormatContext -> IO AVCodecID Source # setVideoCodecID :: AVFormatContext -> AVCodecID -> IO () Source # hasVideoCodecID :: AVFormatContext -> Ptr AVCodecID Source # |
newtype AVInputFormat Source #
AVInputFormat (Ptr ()) |
Instances
Storable AVInputFormat Source # | |
Defined in Codec.FFmpeg.Types sizeOf :: AVInputFormat -> Int # alignment :: AVInputFormat -> Int # peekElemOff :: Ptr AVInputFormat -> Int -> IO AVInputFormat # pokeElemOff :: Ptr AVInputFormat -> Int -> AVInputFormat -> IO () # peekByteOff :: Ptr b -> Int -> IO AVInputFormat # pokeByteOff :: Ptr b -> Int -> AVInputFormat -> IO () # peek :: Ptr AVInputFormat -> IO AVInputFormat # poke :: Ptr AVInputFormat -> AVInputFormat -> IO () # | |
HasAVClass AVInputFormat Source # | |
Defined in Codec.FFmpeg.Types getAVClass :: AVInputFormat -> IO AVClass Source # setAVClass :: AVInputFormat -> AVClass -> IO () Source # hasAVClass :: AVInputFormat -> Ptr AVClass Source # | |
HasPtr AVInputFormat Source # | |
Defined in Codec.FFmpeg.Types getPtr :: AVInputFormat -> Ptr () Source # |
Instances
Storable AVClass Source # | |
HasPtr AVClass Source # | |
class HasAVClass t where Source #
getAVClass :: t -> IO AVClass Source #
setAVClass :: t -> AVClass -> IO () Source #
hasAVClass :: t -> Ptr AVClass Source #
Instances
HasAVClass AVInputFormat Source # | |
Defined in Codec.FFmpeg.Types getAVClass :: AVInputFormat -> IO AVClass Source # setAVClass :: AVInputFormat -> AVClass -> IO () Source # hasAVClass :: AVInputFormat -> Ptr AVClass Source # |
getAVCategory :: AVInputFormat -> IO Category Source #
Instances
Enum Category Source # | |
Eq Category Source # | |
Ord Category Source # | |
Defined in Codec.FFmpeg.Types | |
Read Category Source # | |
Show Category Source # | |
newtype AVIOContext Source #
AVIOContext (Ptr ()) |
Instances
Storable AVIOContext Source # | |
Defined in Codec.FFmpeg.Types sizeOf :: AVIOContext -> Int # alignment :: AVIOContext -> Int # peekElemOff :: Ptr AVIOContext -> Int -> IO AVIOContext # pokeElemOff :: Ptr AVIOContext -> Int -> AVIOContext -> IO () # peekByteOff :: Ptr b -> Int -> IO AVIOContext # pokeByteOff :: Ptr b -> Int -> AVIOContext -> IO () # peek :: Ptr AVIOContext -> IO AVIOContext # poke :: Ptr AVIOContext -> AVIOContext -> IO () # | |
HasPtr AVIOContext Source # | |
Defined in Codec.FFmpeg.Types getPtr :: AVIOContext -> Ptr () Source # |
Instances
Storable AVPacket Source # | |
HasDts AVPacket Source # | |
HasPacketFlags AVPacket Source # | |
Defined in Codec.FFmpeg.Types getPacketFlags :: AVPacket -> IO PacketFlag Source # setPacketFlags :: AVPacket -> PacketFlag -> IO () Source # hasPacketFlags :: AVPacket -> Ptr PacketFlag Source # | |
HasSize AVPacket Source # | |
HasData AVPacket Source # | |
HasPts AVPacket Source # | |
HasStreamIndex AVPacket Source # | |
Defined in Codec.FFmpeg.Types | |
HasPtr AVPacket Source # | |
class HasPacketFlags t where Source #
getPacketFlags :: t -> IO PacketFlag Source #
setPacketFlags :: t -> PacketFlag -> IO () Source #
hasPacketFlags :: t -> Ptr PacketFlag Source #
Instances
HasPacketFlags AVPacket Source # | |
Defined in Codec.FFmpeg.Types getPacketFlags :: AVPacket -> IO PacketFlag Source # setPacketFlags :: AVPacket -> PacketFlag -> IO () Source # hasPacketFlags :: AVPacket -> Ptr PacketFlag Source # |
packetSize :: Int Source #
sizeof
the AVPacket
structure in bytes.
pictureSize :: Int Source #
Types with Haskell equivalents
data AVRational Source #
AVRational | |
|
Instances
Show AVRational Source # | |
Defined in Codec.FFmpeg.Types showsPrec :: Int -> AVRational -> ShowS # show :: AVRational -> String # showList :: [AVRational] -> ShowS # | |
Storable AVRational Source # | |
Defined in Codec.FFmpeg.Types sizeOf :: AVRational -> Int # alignment :: AVRational -> Int # peekElemOff :: Ptr AVRational -> Int -> IO AVRational # pokeElemOff :: Ptr AVRational -> Int -> AVRational -> IO () # peekByteOff :: Ptr b -> Int -> IO AVRational # pokeByteOff :: Ptr b -> Int -> AVRational -> IO () # peek :: Ptr AVRational -> IO AVRational # poke :: Ptr AVRational -> AVRational -> IO () # |
nonZeroAVRational :: AVRational -> Maybe AVRational Source #
FFmpeg often uses 0 to mean "unknown"; use Nothing
instead.
av_rescale_rnd :: CLong -> CLong -> CLong -> AVRoundMode -> CLong Source #
av_q2d :: AVRational -> CDouble Source #
Convert an AVRational
to a Double
av_rescale_q :: CLong -> AVRational -> AVRational -> CLong Source #
Rescale an integer from one time base to another.
data InputSource Source #
The input source can be a file or a camera. When using Camera
,
frequently in the form Camera "0:0" defaultCameraConfig
, the first input video device
enumerated by libavdevice is selected.
Instances
Eq InputSource Source # | |
Defined in Codec.FFmpeg.Types (==) :: InputSource -> InputSource -> Bool # (/=) :: InputSource -> InputSource -> Bool # | |
Ord InputSource Source # | |
Defined in Codec.FFmpeg.Types compare :: InputSource -> InputSource -> Ordering # (<) :: InputSource -> InputSource -> Bool # (<=) :: InputSource -> InputSource -> Bool # (>) :: InputSource -> InputSource -> Bool # (>=) :: InputSource -> InputSource -> Bool # max :: InputSource -> InputSource -> InputSource # min :: InputSource -> InputSource -> InputSource # | |
Read InputSource Source # | |
Defined in Codec.FFmpeg.Types readsPrec :: Int -> ReadS InputSource # readList :: ReadS [InputSource] # readPrec :: ReadPrec InputSource # readListPrec :: ReadPrec [InputSource] # | |
Show InputSource Source # | |
Defined in Codec.FFmpeg.Types showsPrec :: Int -> InputSource -> ShowS # show :: InputSource -> String # showList :: [InputSource] -> ShowS # |
data CameraConfig Source #
Instances
Eq CameraConfig Source # | |
Defined in Codec.FFmpeg.Types (==) :: CameraConfig -> CameraConfig -> Bool # (/=) :: CameraConfig -> CameraConfig -> Bool # | |
Ord CameraConfig Source # | |
Defined in Codec.FFmpeg.Types compare :: CameraConfig -> CameraConfig -> Ordering # (<) :: CameraConfig -> CameraConfig -> Bool # (<=) :: CameraConfig -> CameraConfig -> Bool # (>) :: CameraConfig -> CameraConfig -> Bool # (>=) :: CameraConfig -> CameraConfig -> Bool # max :: CameraConfig -> CameraConfig -> CameraConfig # min :: CameraConfig -> CameraConfig -> CameraConfig # | |
Read CameraConfig Source # | |
Defined in Codec.FFmpeg.Types readsPrec :: Int -> ReadS CameraConfig # readList :: ReadS [CameraConfig] # | |
Show CameraConfig Source # | |
Defined in Codec.FFmpeg.Types showsPrec :: Int -> CameraConfig -> ShowS # show :: CameraConfig -> String # showList :: [CameraConfig] -> ShowS # |