{-# LINE 1 "src/Codec/FFmpeg/Types.hsc" #-}
{-# LANGUAGE ForeignFunctionInterface, FlexibleInstances,
GeneralizedNewtypeDeriving #-}
module Codec.FFmpeg.Types where
import Codec.FFmpeg.Enums
import Control.Monad (zipWithM_,when)
import Data.Maybe (fromMaybe)
import Foreign.C.String (CString)
import Foreign.C.Types
import Foreign.Ptr
import Foreign.Storable
class HasPtr a where
getPtr :: a -> Ptr ()
instance HasPtr (Ptr ()) where getPtr :: Ptr () -> Ptr ()
getPtr = Ptr () -> Ptr ()
forall a. a -> a
id
newtype AVFormatContext = AVFormatContext (Ptr ()) deriving (Ptr b -> Int -> IO AVFormatContext
Ptr b -> Int -> AVFormatContext -> IO ()
Ptr AVFormatContext -> IO AVFormatContext
Ptr AVFormatContext -> Int -> IO AVFormatContext
Ptr AVFormatContext -> Int -> AVFormatContext -> IO ()
Ptr AVFormatContext -> AVFormatContext -> IO ()
AVFormatContext -> Int
(AVFormatContext -> Int)
-> (AVFormatContext -> Int)
-> (Ptr AVFormatContext -> Int -> IO AVFormatContext)
-> (Ptr AVFormatContext -> Int -> AVFormatContext -> IO ())
-> (forall b. Ptr b -> Int -> IO AVFormatContext)
-> (forall b. Ptr b -> Int -> AVFormatContext -> IO ())
-> (Ptr AVFormatContext -> IO AVFormatContext)
-> (Ptr AVFormatContext -> AVFormatContext -> IO ())
-> Storable AVFormatContext
forall b. Ptr b -> Int -> IO AVFormatContext
forall b. Ptr b -> Int -> AVFormatContext -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr AVFormatContext -> AVFormatContext -> IO ()
$cpoke :: Ptr AVFormatContext -> AVFormatContext -> IO ()
peek :: Ptr AVFormatContext -> IO AVFormatContext
$cpeek :: Ptr AVFormatContext -> IO AVFormatContext
pokeByteOff :: Ptr b -> Int -> AVFormatContext -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> AVFormatContext -> IO ()
peekByteOff :: Ptr b -> Int -> IO AVFormatContext
$cpeekByteOff :: forall b. Ptr b -> Int -> IO AVFormatContext
pokeElemOff :: Ptr AVFormatContext -> Int -> AVFormatContext -> IO ()
$cpokeElemOff :: Ptr AVFormatContext -> Int -> AVFormatContext -> IO ()
peekElemOff :: Ptr AVFormatContext -> Int -> IO AVFormatContext
$cpeekElemOff :: Ptr AVFormatContext -> Int -> IO AVFormatContext
alignment :: AVFormatContext -> Int
$calignment :: AVFormatContext -> Int
sizeOf :: AVFormatContext -> Int
$csizeOf :: AVFormatContext -> Int
Storable, AVFormatContext -> Ptr ()
(AVFormatContext -> Ptr ()) -> HasPtr AVFormatContext
forall a. (a -> Ptr ()) -> HasPtr a
getPtr :: AVFormatContext -> Ptr ()
$cgetPtr :: AVFormatContext -> Ptr ()
HasPtr)
class HasNumStreams t where
getNumStreams :: t -> IO CInt
setNumStreams :: t -> CInt -> IO ()
hasNumStreams :: t -> Ptr CInt
{-# LINE 26 "src/Codec/FFmpeg/Types.hsc" #-}
class HasStreams t where
getStreams :: t -> IO (Ptr AVStream)
setStreams :: t -> (Ptr AVStream) -> IO ()
hasStreams :: t -> Ptr (Ptr AVStream)
{-# LINE 27 "src/Codec/FFmpeg/Types.hsc" #-}
class HasOutputFormat t where
getOutputFormat :: t -> IO AVOutputFormat
setOutputFormat :: t -> AVOutputFormat -> IO ()
hasOutputFormat :: t -> Ptr AVOutputFormat
{-# LINE 28 "src/Codec/FFmpeg/Types.hsc" #-}
class HasIOContext t where
getIOContext :: t -> IO AVIOContext
setIOContext :: t -> AVIOContext -> IO ()
hasIOContext :: t -> Ptr AVIOContext
{-# LINE 29 "src/Codec/FFmpeg/Types.hsc" #-}
class HasInputFormat t where
getInputFormat :: t -> IO AVInputFormat
setInputFormat :: t -> AVInputFormat -> IO ()
hasInputFormat :: t -> Ptr AVInputFormat
{-# LINE 30 "src/Codec/FFmpeg/Types.hsc" #-}
instance HasNumStreams AVFormatContext where
getNumStreams = (\hsc_ptr -> peekByteOff hsc_ptr 44) . getPtr
setNumStreams = (\hsc_ptr -> pokeByteOff hsc_ptr 44) . getPtr
hasNumStreams = (\hsc_ptr -> hsc_ptr `plusPtr` 44) . getPtr
{-# LINE 32 "src/Codec/FFmpeg/Types.hsc" #-}
instance HasStreams AVFormatContext where
getStreams = (\hsc_ptr -> peekByteOff hsc_ptr 48) . getPtr
setStreams = (\hsc_ptr -> pokeByteOff hsc_ptr 48) . getPtr
hasStreams = (\hsc_ptr -> hsc_ptr `plusPtr` 48) . getPtr
{-# LINE 33 "src/Codec/FFmpeg/Types.hsc" #-}
instance HasOutputFormat AVFormatContext where
getOutputFormat = (\hsc_ptr -> peekByteOff hsc_ptr 16) . getPtr
setOutputFormat = (\hsc_ptr -> pokeByteOff hsc_ptr 16) . getPtr
hasOutputFormat = (\hsc_ptr -> hsc_ptr `plusPtr` 16) . getPtr
{-# LINE 34 "src/Codec/FFmpeg/Types.hsc" #-}
instance HasInputFormat AVFormatContext where
getInputFormat = (\hsc_ptr -> peekByteOff hsc_ptr 8) . getPtr
setInputFormat = (\hsc_ptr -> pokeByteOff hsc_ptr 8) . getPtr
hasInputFormat = (\hsc_ptr -> hsc_ptr `plusPtr` 8) . getPtr
{-# LINE 35 "src/Codec/FFmpeg/Types.hsc" #-}
instance HasIOContext AVFormatContext where
getIOContext = (\hsc_ptr -> peekByteOff hsc_ptr 32) . getPtr
setIOContext = (\hsc_ptr -> pokeByteOff hsc_ptr 32) . getPtr
hasIOContext = (\hsc_ptr -> hsc_ptr `plusPtr` 32) . getPtr
{-# LINE 36 "src/Codec/FFmpeg/Types.hsc" #-}
instance HasVideoCodecID AVFormatContext where
getVideoCodecID = (\hsc_ptr -> peekByteOff hsc_ptr 1160) . getPtr
setVideoCodecID = (\hsc_ptr -> pokeByteOff hsc_ptr 1160) . getPtr
hasVideoCodecID = (\hsc_ptr -> hsc_ptr `plusPtr` 1160) . getPtr
{-# LINE 37 "src/Codec/FFmpeg/Types.hsc" #-}
setFilename :: AVFormatContext -> String -> IO ()
setFilename ctx fn =
do let ptr = getPtr ctx
dst = ((\hsc_ptr -> hsc_ptr `plusPtr` 56)) ptr
{-# LINE 42 "src/Codec/FFmpeg/Types.hsc" #-}
bytes = map (fromIntegral . fromEnum) fn
zipWithM_ (pokeElemOff dst) bytes [(0 :: CInt) ..]
foreign import ccall "av_input_video_device_next"
av_input_video_device_next :: AVInputFormat -> IO AVInputFormat
setCamera :: AVFormatContext -> IO ()
setCamera :: AVFormatContext -> IO ()
setCamera ctx :: AVFormatContext
ctx = do
AVInputFormat
ipt <- AVInputFormat -> IO AVInputFormat
getCameraAVInputFormat (Ptr () -> AVInputFormat
AVInputFormat Ptr ()
forall b. Ptr b
nullPtr)
AVFormatContext -> AVInputFormat -> IO ()
forall t. HasInputFormat t => t -> AVInputFormat -> IO ()
setInputFormat AVFormatContext
ctx AVInputFormat
ipt
where
getCameraAVInputFormat :: AVInputFormat -> IO AVInputFormat
getCameraAVInputFormat :: AVInputFormat -> IO AVInputFormat
getCameraAVInputFormat p :: AVInputFormat
p = do
AVInputFormat
nxt <- AVInputFormat -> IO AVInputFormat
av_input_video_device_next AVInputFormat
p
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Ptr ()
forall b. Ptr b
nullPtr Ptr () -> Ptr () -> Bool
forall a. Eq a => a -> a -> Bool
== AVInputFormat -> Ptr ()
forall a. HasPtr a => a -> Ptr ()
getPtr AVInputFormat
nxt) (String -> IO ()
forall a. HasCallStack => String -> a
error "No video input device found.")
AVInputFormat -> IO AVInputFormat
forall (m :: * -> *) a. Monad m => a -> m a
return AVInputFormat
nxt
foreign import ccall "avformat_alloc_context"
avformat_alloc_context :: IO (Ptr ())
mallocAVFormatContext :: IO AVFormatContext
mallocAVFormatContext :: IO AVFormatContext
mallocAVFormatContext = Ptr () -> AVFormatContext
AVFormatContext (Ptr () -> AVFormatContext) -> IO (Ptr ()) -> IO AVFormatContext
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO (Ptr ())
avformat_alloc_context
newtype AVCodecContext = AVCodecContext (Ptr ()) deriving (Ptr b -> Int -> IO AVCodecContext
Ptr b -> Int -> AVCodecContext -> IO ()
Ptr AVCodecContext -> IO AVCodecContext
Ptr AVCodecContext -> Int -> IO AVCodecContext
Ptr AVCodecContext -> Int -> AVCodecContext -> IO ()
Ptr AVCodecContext -> AVCodecContext -> IO ()
AVCodecContext -> Int
(AVCodecContext -> Int)
-> (AVCodecContext -> Int)
-> (Ptr AVCodecContext -> Int -> IO AVCodecContext)
-> (Ptr AVCodecContext -> Int -> AVCodecContext -> IO ())
-> (forall b. Ptr b -> Int -> IO AVCodecContext)
-> (forall b. Ptr b -> Int -> AVCodecContext -> IO ())
-> (Ptr AVCodecContext -> IO AVCodecContext)
-> (Ptr AVCodecContext -> AVCodecContext -> IO ())
-> Storable AVCodecContext
forall b. Ptr b -> Int -> IO AVCodecContext
forall b. Ptr b -> Int -> AVCodecContext -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr AVCodecContext -> AVCodecContext -> IO ()
$cpoke :: Ptr AVCodecContext -> AVCodecContext -> IO ()
peek :: Ptr AVCodecContext -> IO AVCodecContext
$cpeek :: Ptr AVCodecContext -> IO AVCodecContext
pokeByteOff :: Ptr b -> Int -> AVCodecContext -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> AVCodecContext -> IO ()
peekByteOff :: Ptr b -> Int -> IO AVCodecContext
$cpeekByteOff :: forall b. Ptr b -> Int -> IO AVCodecContext
pokeElemOff :: Ptr AVCodecContext -> Int -> AVCodecContext -> IO ()
$cpokeElemOff :: Ptr AVCodecContext -> Int -> AVCodecContext -> IO ()
peekElemOff :: Ptr AVCodecContext -> Int -> IO AVCodecContext
$cpeekElemOff :: Ptr AVCodecContext -> Int -> IO AVCodecContext
alignment :: AVCodecContext -> Int
$calignment :: AVCodecContext -> Int
sizeOf :: AVCodecContext -> Int
$csizeOf :: AVCodecContext -> Int
Storable, AVCodecContext -> Ptr ()
(AVCodecContext -> Ptr ()) -> HasPtr AVCodecContext
forall a. (a -> Ptr ()) -> HasPtr a
getPtr :: AVCodecContext -> Ptr ()
$cgetPtr :: AVCodecContext -> Ptr ()
HasPtr)
class HasBitRate t where
getBitRate :: t -> IO CInt
getBitRate :: AVCodecContext -> IO CInt
setBitRate :: t -> CInt -> IO ()
hasBitRate :: t -> Ptr CInt
{-# LINE 72 "src/Codec/FFmpeg/Types.hsc" #-}
instance HasBitRate AVCodecContext where
getBitRate = (\hsc_ptr -> peekByteOff hsc_ptr 96) . getPtr
setBitRate = (\hsc_ptr -> pokeByteOff hsc_ptr 96) . getPtr
hasBitRate = (\hsc_ptr -> hsc_ptr `plusPtr` 96) . getPtr
{-# LINE 73 "src/Codec/FFmpeg/Types.hsc" #-}
class HasWidth t where
getWidth :: t -> IO CInt
setWidth :: t -> CInt -> IO ()
hasWidth :: t -> Ptr CInt
{-# LINE 75 "src/Codec/FFmpeg/Types.hsc" #-}
class HasHeight t where
getHeight :: t -> IO CInt
setHeight :: t -> CInt -> IO ()
hasHeight :: t -> Ptr CInt
{-# LINE 76 "src/Codec/FFmpeg/Types.hsc" #-}
class HasTimeBase t where
getTimeBase :: t -> IO AVRational
setTimeBase :: t -> AVRational -> IO ()
hasTimeBase :: t -> Ptr AVRational
{-# LINE 77 "src/Codec/FFmpeg/Types.hsc" #-}
class HasGopSize t where
getGopSize :: t -> IO CInt
setGopSize :: t -> CInt -> IO ()
hasGopSize :: t -> Ptr CInt
{-# LINE 78 "src/Codec/FFmpeg/Types.hsc" #-}
class HasPixelFormat t where
getPixelFormat :: t -> IO AVPixelFormat
setPixelFormat :: t -> AVPixelFormat -> IO ()
hasPixelFormat :: t -> Ptr AVPixelFormat
{-# LINE 79 "src/Codec/FFmpeg/Types.hsc" #-}
class HasCodecFlags t where
getCodecFlags :: t -> IO CodecFlag
setCodecFlags :: t -> CodecFlag -> IO ()
hasCodecFlags :: t -> Ptr CodecFlag
{-# LINE 80 "src/Codec/FFmpeg/Types.hsc" #-}
class HasCodecID t where
getCodecID :: t -> IO AVCodecID
setCodecID :: t -> AVCodecID -> IO ()
hasCodecID :: t -> Ptr AVCodecID
{-# LINE 81 "src/Codec/FFmpeg/Types.hsc" #-}
class HasPrivData t where
getPrivData :: t -> IO (Ptr ())
setPrivData :: t -> (Ptr ()) -> IO ()
hasPrivData :: t -> Ptr (Ptr ())
{-# LINE 82 "src/Codec/FFmpeg/Types.hsc" #-}
class HasTicksPerFrame t where
getTicksPerFrame :: t -> IO CInt
setTicksPerFrame :: t -> CInt -> IO ()
hasTicksPerFrame :: t -> Ptr CInt
{-# LINE 83 "src/Codec/FFmpeg/Types.hsc" #-}
class HasRawAspectRatio t where
getRawAspectRatio :: t -> IO AVRational
setRawAspectRatio :: t -> AVRational -> IO ()
hasRawAspectRatio :: t -> Ptr AVRational
{-# LINE 84 "src/Codec/FFmpeg/Types.hsc" #-}
instance HasWidth AVCodecContext where
getWidth = (\hsc_ptr -> peekByteOff hsc_ptr 156) . getPtr
setWidth = (\hsc_ptr -> pokeByteOff hsc_ptr 156) . getPtr
hasWidth = (\hsc_ptr -> hsc_ptr `plusPtr` 156) . getPtr
{-# LINE 86 "src/Codec/FFmpeg/Types.hsc" #-}
instance HasHeight AVCodecContext where
getHeight = (\hsc_ptr -> peekByteOff hsc_ptr 160) . getPtr
setHeight = (\hsc_ptr -> pokeByteOff hsc_ptr 160) . getPtr
hasHeight = (\hsc_ptr -> hsc_ptr `plusPtr` 160) . getPtr
{-# LINE 87 "src/Codec/FFmpeg/Types.hsc" #-}
instance HasTimeBase AVCodecContext where
getTimeBase = (\hsc_ptr -> peekByteOff hsc_ptr 140) . getPtr
setTimeBase = (\hsc_ptr -> pokeByteOff hsc_ptr 140) . getPtr
hasTimeBase = (\hsc_ptr -> hsc_ptr `plusPtr` 140) . getPtr
{-# LINE 88 "src/Codec/FFmpeg/Types.hsc" #-}
instance HasGopSize AVCodecContext where
getGopSize = (\hsc_ptr -> peekByteOff hsc_ptr 172) . getPtr
setGopSize = (\hsc_ptr -> pokeByteOff hsc_ptr 172) . getPtr
hasGopSize = (\hsc_ptr -> hsc_ptr `plusPtr` 172) . getPtr
{-# LINE 89 "src/Codec/FFmpeg/Types.hsc" #-}
instance HasPixelFormat AVCodecContext where
getPixelFormat = (\hsc_ptr -> peekByteOff hsc_ptr 176) . getPtr
setPixelFormat = (\hsc_ptr -> pokeByteOff hsc_ptr 176) . getPtr
hasPixelFormat = (\hsc_ptr -> hsc_ptr `plusPtr` 176) . getPtr
{-# LINE 90 "src/Codec/FFmpeg/Types.hsc" #-}
instance HasCodecFlags AVCodecContext where
getCodecFlags = (\hsc_ptr -> peekByteOff hsc_ptr 116) . getPtr
setCodecFlags = (\hsc_ptr -> pokeByteOff hsc_ptr 116) . getPtr
hasCodecFlags = (\hsc_ptr -> hsc_ptr `plusPtr` 116) . getPtr
{-# LINE 91 "src/Codec/FFmpeg/Types.hsc" #-}
instance HasCodecID AVCodecContext where
getCodecID = (\hsc_ptr -> peekByteOff hsc_ptr 56) . getPtr
setCodecID = (\hsc_ptr -> pokeByteOff hsc_ptr 56) . getPtr
hasCodecID = (\hsc_ptr -> hsc_ptr `plusPtr` 56) . getPtr
{-# LINE 92 "src/Codec/FFmpeg/Types.hsc" #-}
instance HasPrivData AVCodecContext where
getPrivData = (\hsc_ptr -> peekByteOff hsc_ptr 72) . getPtr
setPrivData = (\hsc_ptr -> pokeByteOff hsc_ptr 72) . getPtr
hasPrivData = (\hsc_ptr -> hsc_ptr `plusPtr` 72) . getPtr
{-# LINE 93 "src/Codec/FFmpeg/Types.hsc" #-}
instance HasTicksPerFrame AVCodecContext where
getTicksPerFrame = (\hsc_ptr -> peekByteOff hsc_ptr 148) . getPtr
setTicksPerFrame = (\hsc_ptr -> pokeByteOff hsc_ptr 148) . getPtr
hasTicksPerFrame = (\hsc_ptr -> hsc_ptr `plusPtr` 148) . getPtr
{-# LINE 94 "src/Codec/FFmpeg/Types.hsc" #-}
instance HasRawAspectRatio AVCodecContext where
getRawAspectRatio = (\hsc_ptr -> peekByteOff hsc_ptr 272) . getPtr
setRawAspectRatio = (\hsc_ptr -> pokeByteOff hsc_ptr 272) . getPtr
hasRawAspectRatio = (\hsc_ptr -> hsc_ptr `plusPtr` 272) . getPtr
{-# LINE 95 "src/Codec/FFmpeg/Types.hsc" #-}
getFps :: (HasTimeBase a, HasTicksPerFrame a) => a -> IO CDouble
getFps x = do
timeBase <- getTimeBase x
ticksPerFrame <- getTicksPerFrame x
pure (1.0 / av_q2d timeBase / fromIntegral ticksPerFrame)
getAspectRatio :: HasRawAspectRatio a => a -> IO (Maybe AVRational)
getAspectRatio :: a -> IO (Maybe AVRational)
getAspectRatio = (AVRational -> Maybe AVRational)
-> IO AVRational -> IO (Maybe AVRational)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap AVRational -> Maybe AVRational
nonZeroAVRational (IO AVRational -> IO (Maybe AVRational))
-> (a -> IO AVRational) -> a -> IO (Maybe AVRational)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> IO AVRational
forall t. HasRawAspectRatio t => t -> IO AVRational
getRawAspectRatio
guessAspectRatio :: HasRawAspectRatio a => a -> IO AVRational
guessAspectRatio :: a -> IO AVRational
guessAspectRatio = (Maybe AVRational -> AVRational)
-> IO (Maybe AVRational) -> IO AVRational
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (AVRational -> Maybe AVRational -> AVRational
forall a. a -> Maybe a -> a
fromMaybe (CInt -> CInt -> AVRational
AVRational 1 1)) (IO (Maybe AVRational) -> IO AVRational)
-> (a -> IO (Maybe AVRational)) -> a -> IO AVRational
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> IO (Maybe AVRational)
forall a. HasRawAspectRatio a => a -> IO (Maybe AVRational)
getAspectRatio
setAspectRatio :: HasRawAspectRatio a => a -> Maybe AVRational -> IO ()
setAspectRatio :: a -> Maybe AVRational -> IO ()
setAspectRatio x :: a
x Nothing = a -> AVRational -> IO ()
forall t. HasRawAspectRatio t => t -> AVRational -> IO ()
setRawAspectRatio a
x (CInt -> CInt -> AVRational
AVRational 0 1)
setAspectRatio x :: a
x (Just ratio :: AVRational
ratio) = a -> AVRational -> IO ()
forall t. HasRawAspectRatio t => t -> AVRational -> IO ()
setRawAspectRatio a
x AVRational
ratio
newtype AVStream = AVStream (Ptr ()) deriving (Ptr b -> Int -> IO AVStream
Ptr b -> Int -> AVStream -> IO ()
Ptr AVStream -> IO AVStream
Ptr AVStream -> Int -> IO AVStream
Ptr AVStream -> Int -> AVStream -> IO ()
Ptr AVStream -> AVStream -> IO ()
AVStream -> Int
(AVStream -> Int)
-> (AVStream -> Int)
-> (Ptr AVStream -> Int -> IO AVStream)
-> (Ptr AVStream -> Int -> AVStream -> IO ())
-> (forall b. Ptr b -> Int -> IO AVStream)
-> (forall b. Ptr b -> Int -> AVStream -> IO ())
-> (Ptr AVStream -> IO AVStream)
-> (Ptr AVStream -> AVStream -> IO ())
-> Storable AVStream
forall b. Ptr b -> Int -> IO AVStream
forall b. Ptr b -> Int -> AVStream -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr AVStream -> AVStream -> IO ()
$cpoke :: Ptr AVStream -> AVStream -> IO ()
peek :: Ptr AVStream -> IO AVStream
$cpeek :: Ptr AVStream -> IO AVStream
pokeByteOff :: Ptr b -> Int -> AVStream -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> AVStream -> IO ()
peekByteOff :: Ptr b -> Int -> IO AVStream
$cpeekByteOff :: forall b. Ptr b -> Int -> IO AVStream
pokeElemOff :: Ptr AVStream -> Int -> AVStream -> IO ()
$cpokeElemOff :: Ptr AVStream -> Int -> AVStream -> IO ()
peekElemOff :: Ptr AVStream -> Int -> IO AVStream
$cpeekElemOff :: Ptr AVStream -> Int -> IO AVStream
alignment :: AVStream -> Int
$calignment :: AVStream -> Int
sizeOf :: AVStream -> Int
$csizeOf :: AVStream -> Int
Storable, AVStream -> Ptr ()
(AVStream -> Ptr ()) -> HasPtr AVStream
forall a. (a -> Ptr ()) -> HasPtr a
getPtr :: AVStream -> Ptr ()
$cgetPtr :: AVStream -> Ptr ()
HasPtr)
class HasId t where
getId :: t -> IO CInt
setId :: t -> CInt -> IO ()
hasId :: t -> Ptr CInt
{-# LINE 116 "src/Codec/FFmpeg/Types.hsc" #-}
class HasCodecContext t where
getCodecContext :: t -> IO AVCodecContext
setCodecContext :: t -> AVCodecContext -> IO ()
hasCodecContext :: t -> Ptr AVCodecContext
{-# LINE 117 "src/Codec/FFmpeg/Types.hsc" #-}
class HasStreamIndex t where
getStreamIndex :: t -> IO CInt
setStreamIndex :: t -> CInt -> IO ()
hasStreamIndex :: t -> Ptr CInt
{-# LINE 118 "src/Codec/FFmpeg/Types.hsc" #-}
instance HasId AVStream where
getId = (\hsc_ptr -> peekByteOff hsc_ptr 4) . getPtr
setId = (\hsc_ptr -> pokeByteOff hsc_ptr 4) . getPtr
hasId = (\hsc_ptr -> hsc_ptr `plusPtr` 4) . getPtr
{-# LINE 120 "src/Codec/FFmpeg/Types.hsc" #-}
instance HasTimeBase AVStream where
getTimeBase = (\hsc_ptr -> peekByteOff hsc_ptr 48) . getPtr
setTimeBase = (\hsc_ptr -> pokeByteOff hsc_ptr 48) . getPtr
hasTimeBase = (\hsc_ptr -> hsc_ptr `plusPtr` 48) . getPtr
{-# LINE 121 "src/Codec/FFmpeg/Types.hsc" #-}
instance HasCodecContext AVStream where
getCodecContext = (\hsc_ptr -> peekByteOff hsc_ptr 8) . getPtr
setCodecContext = (\hsc_ptr -> pokeByteOff hsc_ptr 8) . getPtr
hasCodecContext = (\hsc_ptr -> hsc_ptr `plusPtr` 8) . getPtr
{-# LINE 122 "src/Codec/FFmpeg/Types.hsc" #-}
instance HasStreamIndex AVStream where
getStreamIndex = (\hsc_ptr -> peekByteOff hsc_ptr 0) . getPtr
setStreamIndex = (\hsc_ptr -> pokeByteOff hsc_ptr 0) . getPtr
hasStreamIndex = (\hsc_ptr -> hsc_ptr `plusPtr` 0) . getPtr
{-# LINE 123 "src/Codec/FFmpeg/Types.hsc" #-}
newtype AVCodec = AVCodec (Ptr ()) deriving (Storable, HasPtr)
class HasLongName t where
getLongName :: t -> IO CString
setLongName :: t -> CString -> IO ()
hasLongName :: t -> Ptr CString
{-# LINE 126 "src/Codec/FFmpeg/Types.hsc" #-}
class HasName t where
getName :: t -> IO CString
setName :: t -> CString -> IO ()
hasName :: t -> Ptr CString
{-# LINE 127 "src/Codec/FFmpeg/Types.hsc" #-}
class HasPixelFormats t where
getPixelFormats :: t -> IO (Ptr AVPixelFormat)
setPixelFormats :: t -> (Ptr AVPixelFormat) -> IO ()
hasPixelFormats :: t -> Ptr (Ptr AVPixelFormat)
{-# LINE 128 "src/Codec/FFmpeg/Types.hsc" #-}
instance HasLongName AVCodec where
getLongName = (\hsc_ptr -> peekByteOff hsc_ptr 8) . getPtr
setLongName = (\hsc_ptr -> pokeByteOff hsc_ptr 8) . getPtr
hasLongName = (\hsc_ptr -> hsc_ptr `plusPtr` 8) . getPtr
{-# LINE 130 "src/Codec/FFmpeg/Types.hsc" #-}
instance HasName AVCodec where
getName = (\hsc_ptr -> peekByteOff hsc_ptr 0) . getPtr
setName = (\hsc_ptr -> pokeByteOff hsc_ptr 0) . getPtr
hasName = (\hsc_ptr -> hsc_ptr `plusPtr` 0) . getPtr
{-# LINE 131 "src/Codec/FFmpeg/Types.hsc" #-}
instance HasCodecID AVCodec where
getCodecID = (\hsc_ptr -> peekByteOff hsc_ptr 20) . getPtr
setCodecID = (\hsc_ptr -> pokeByteOff hsc_ptr 20) . getPtr
hasCodecID = (\hsc_ptr -> hsc_ptr `plusPtr` 20) . getPtr
{-# LINE 132 "src/Codec/FFmpeg/Types.hsc" #-}
instance HasPixelFormats AVCodec where
getPixelFormats = (\hsc_ptr -> peekByteOff hsc_ptr 40) . getPtr
setPixelFormats = (\hsc_ptr -> pokeByteOff hsc_ptr 40) . getPtr
hasPixelFormats = (\hsc_ptr -> hsc_ptr `plusPtr` 40) . getPtr
{-# LINE 133 "src/Codec/FFmpeg/Types.hsc" #-}
newtype AVDictionary = AVDictionary (Ptr ()) deriving (Storable, HasPtr)
newtype AVFrame = AVFrame (Ptr ()) deriving (Storable, HasPtr)
class HasPts t where
getPts :: t -> IO CLong
setPts :: t -> CLong -> IO ()
hasPts :: t -> Ptr CLong
{-# LINE 137 "src/Codec/FFmpeg/Types.hsc" #-}
class HasPktPts t where
getPktPts :: t -> IO CLong
setPktPts :: t -> CLong -> IO ()
hasPktPts :: t -> Ptr CLong
{-# LINE 138 "src/Codec/FFmpeg/Types.hsc" #-}
class HasLineSize t where
getLineSize :: t -> IO CInt
setLineSize :: t -> CInt -> IO ()
hasLineSize :: t -> Ptr CInt
{-# LINE 139 "src/Codec/FFmpeg/Types.hsc" #-}
instance HasPixelFormat AVFrame where
getPixelFormat = (\hsc_ptr -> peekByteOff hsc_ptr 116) . getPtr
setPixelFormat = (\hsc_ptr -> pokeByteOff hsc_ptr 116) . getPtr
hasPixelFormat = (\hsc_ptr -> hsc_ptr `plusPtr` 116) . getPtr
{-# LINE 141 "src/Codec/FFmpeg/Types.hsc" #-}
instance HasWidth AVFrame where
getWidth = (\hsc_ptr -> peekByteOff hsc_ptr 104) . getPtr
setWidth = (\hsc_ptr -> pokeByteOff hsc_ptr 104) . getPtr
hasWidth = (\hsc_ptr -> hsc_ptr `plusPtr` 104) . getPtr
{-# LINE 142 "src/Codec/FFmpeg/Types.hsc" #-}
instance HasHeight AVFrame where
getHeight = (\hsc_ptr -> peekByteOff hsc_ptr 108) . getPtr
setHeight = (\hsc_ptr -> pokeByteOff hsc_ptr 108) . getPtr
hasHeight = (\hsc_ptr -> hsc_ptr `plusPtr` 108) . getPtr
{-# LINE 143 "src/Codec/FFmpeg/Types.hsc" #-}
instance HasLineSize AVFrame where
getLineSize = (\hsc_ptr -> peekByteOff hsc_ptr 64) . getPtr
setLineSize = (\hsc_ptr -> pokeByteOff hsc_ptr 64) . getPtr
hasLineSize = (\hsc_ptr -> hsc_ptr `plusPtr` 64) . getPtr
{-# LINE 144 "src/Codec/FFmpeg/Types.hsc" #-}
instance HasPts AVFrame where
getPts = (\hsc_ptr -> peekByteOff hsc_ptr 136) . getPtr
setPts = (\hsc_ptr -> pokeByteOff hsc_ptr 136) . getPtr
hasPts = (\hsc_ptr -> hsc_ptr `plusPtr` 136) . getPtr
{-# LINE 145 "src/Codec/FFmpeg/Types.hsc" #-}
instance HasPktPts AVFrame where
getPktPts = (\hsc_ptr -> peekByteOff hsc_ptr 144) . getPtr
setPktPts = (\hsc_ptr -> pokeByteOff hsc_ptr 144) . getPtr
hasPktPts = (\hsc_ptr -> hsc_ptr `plusPtr` 144) . getPtr
{-# LINE 146 "src/Codec/FFmpeg/Types.hsc" #-}
instance HasData AVFrame where
getData = (\hsc_ptr -> peekByteOff hsc_ptr 0) . getPtr
setData = (\hsc_ptr -> pokeByteOff hsc_ptr 0) . getPtr
hasData = (\hsc_ptr -> hsc_ptr `plusPtr` 0) . getPtr
{-# LINE 147 "src/Codec/FFmpeg/Types.hsc" #-}
newtype AVPicture = AVPicture (Ptr ()) deriving (Storable, HasPtr)
instance HasData AVPicture where
getData = (\hsc_ptr -> peekByteOff hsc_ptr 0) . getPtr
setData = (\hsc_ptr -> pokeByteOff hsc_ptr 0) . getPtr
hasData = (\hsc_ptr -> hsc_ptr `plusPtr` 0) . getPtr
{-# LINE 150 "src/Codec/FFmpeg/Types.hsc" #-}
newtype SwsContext = SwsContext (Ptr ()) deriving (Storable, HasPtr)
newtype AVOutputFormat = AVOutputFormat (Ptr ()) deriving (Storable, HasPtr)
class HasFormatFlags t where
getFormatFlags :: t -> IO FormatFlag
setFormatFlags :: t -> FormatFlag -> IO ()
getFormatFlags :: AVOutputFormat -> IO FormatFlag
hasFormatFlags :: t -> Ptr FormatFlag
{-# LINE 154 "src/Codec/FFmpeg/Types.hsc" #-}
class HasVideoCodecID t where
getVideoCodecID :: t -> IO AVCodecID
setVideoCodecID :: t -> AVCodecID -> IO ()
hasVideoCodecID :: t -> Ptr AVCodecID
{-# LINE 155 "src/Codec/FFmpeg/Types.hsc" #-}
instance HasFormatFlags AVOutputFormat where
getFormatFlags = (\hsc_ptr -> peekByteOff hsc_ptr 44) . getPtr
setFormatFlags = (\hsc_ptr -> pokeByteOff hsc_ptr 44) . getPtr
hasFormatFlags = (\hsc_ptr -> hsc_ptr `plusPtr` 44) . getPtr
{-# LINE 156 "src/Codec/FFmpeg/Types.hsc" #-}
instance HasVideoCodecID AVOutputFormat where
getVideoCodecID = (\hsc_ptr -> peekByteOff hsc_ptr 36) . getPtr
setVideoCodecID = (\hsc_ptr -> pokeByteOff hsc_ptr 36) . getPtr
hasVideoCodecID = (\hsc_ptr -> hsc_ptr `plusPtr` 36) . getPtr
{-# LINE 157 "src/Codec/FFmpeg/Types.hsc" #-}
newtype AVInputFormat = AVInputFormat (Ptr ()) deriving (Storable, HasPtr)
newtype AVClass = AVClass (Ptr ()) deriving (Storable, HasPtr)
class HasAVClass t where
getAVClass :: t -> IO AVClass
setAVClass :: t -> AVClass -> IO ()
setAVClass :: AVInputFormat -> AVClass -> IO ()
hasAVClass :: t -> Ptr AVClass
{-# LINE 161 "src/Codec/FFmpeg/Types.hsc" #-}
instance HasAVClass AVInputFormat where
getAVClass = (\hsc_ptr -> peekByteOff hsc_ptr 40) . getPtr
setAVClass = (\hsc_ptr -> pokeByteOff hsc_ptr 40) . getPtr
hasAVClass = (\hsc_ptr -> hsc_ptr `plusPtr` 40) . getPtr
{-# LINE 162 "src/Codec/FFmpeg/Types.hsc" #-}
{-# LINE 164 "src/Codec/FFmpeg/Types.hsc" #-}
getAVCategory :: AVInputFormat -> IO Category
getAVCategory aif =
do c <- getAVClass aif
if nullPtr == getPtr c
then return (Category (-1))
else Category <$> peek (((\hsc_ptr -> hsc_ptr `plusPtr` 56)) $ castPtr $ getPtr c)
{-# LINE 170 "src/Codec/FFmpeg/Types.hsc" #-}
newtype Category = Category CInt deriving (Category -> Category -> Bool
(Category -> Category -> Bool)
-> (Category -> Category -> Bool) -> Eq Category
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Category -> Category -> Bool
$c/= :: Category -> Category -> Bool
== :: Category -> Category -> Bool
$c== :: Category -> Category -> Bool
Eq,Eq Category
Eq Category =>
(Category -> Category -> Ordering)
-> (Category -> Category -> Bool)
-> (Category -> Category -> Bool)
-> (Category -> Category -> Bool)
-> (Category -> Category -> Bool)
-> (Category -> Category -> Category)
-> (Category -> Category -> Category)
-> Ord Category
Category -> Category -> Bool
Category -> Category -> Ordering
Category -> Category -> Category
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Category -> Category -> Category
$cmin :: Category -> Category -> Category
max :: Category -> Category -> Category
$cmax :: Category -> Category -> Category
>= :: Category -> Category -> Bool
$c>= :: Category -> Category -> Bool
> :: Category -> Category -> Bool
$c> :: Category -> Category -> Bool
<= :: Category -> Category -> Bool
$c<= :: Category -> Category -> Bool
< :: Category -> Category -> Bool
$c< :: Category -> Category -> Bool
compare :: Category -> Category -> Ordering
$ccompare :: Category -> Category -> Ordering
$cp1Ord :: Eq Category
Ord,Int -> Category -> ShowS
[Category] -> ShowS
Category -> String
(Int -> Category -> ShowS)
-> (Category -> String) -> ([Category] -> ShowS) -> Show Category
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Category] -> ShowS
$cshowList :: [Category] -> ShowS
show :: Category -> String
$cshow :: Category -> String
showsPrec :: Int -> Category -> ShowS
$cshowsPrec :: Int -> Category -> ShowS
Show,ReadPrec [Category]
ReadPrec Category
Int -> ReadS Category
ReadS [Category]
(Int -> ReadS Category)
-> ReadS [Category]
-> ReadPrec Category
-> ReadPrec [Category]
-> Read Category
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Category]
$creadListPrec :: ReadPrec [Category]
readPrec :: ReadPrec Category
$creadPrec :: ReadPrec Category
readList :: ReadS [Category]
$creadList :: ReadS [Category]
readsPrec :: Int -> ReadS Category
$creadsPrec :: Int -> ReadS Category
Read,Int -> Category
Category -> Int
Category -> [Category]
Category -> Category
Category -> Category -> [Category]
Category -> Category -> Category -> [Category]
(Category -> Category)
-> (Category -> Category)
-> (Int -> Category)
-> (Category -> Int)
-> (Category -> [Category])
-> (Category -> Category -> [Category])
-> (Category -> Category -> [Category])
-> (Category -> Category -> Category -> [Category])
-> Enum Category
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: Category -> Category -> Category -> [Category]
$cenumFromThenTo :: Category -> Category -> Category -> [Category]
enumFromTo :: Category -> Category -> [Category]
$cenumFromTo :: Category -> Category -> [Category]
enumFromThen :: Category -> Category -> [Category]
$cenumFromThen :: Category -> Category -> [Category]
enumFrom :: Category -> [Category]
$cenumFrom :: Category -> [Category]
fromEnum :: Category -> Int
$cfromEnum :: Category -> Int
toEnum :: Int -> Category
$ctoEnum :: Int -> Category
pred :: Category -> Category
$cpred :: Category -> Category
succ :: Category -> Category
$csucc :: Category -> Category
Enum)
avClassCategoryNa :: Category
avClassCategoryNa :: Category
avClassCategoryNa = CInt -> Category
Category 0
avClassCategoryInput :: Category
avClassCategoryInput :: Category
avClassCategoryInput = CInt -> Category
Category 1
avClassCategoryOutput :: Category
avClassCategoryOutput :: Category
avClassCategoryOutput = CInt -> Category
Category 2
avClassCategoryMuxer :: Category
avClassCategoryMuxer :: Category
avClassCategoryMuxer = CInt -> Category
Category 3
avClassCategoryDemuxer :: Category
avClassCategoryDemuxer :: Category
avClassCategoryDemuxer = CInt -> Category
Category 4
avClassCategoryEncoder :: Category
avClassCategoryEncoder :: Category
avClassCategoryEncoder = CInt -> Category
Category 5
avClassCategoryDecoder :: Category
avClassCategoryDecoder :: Category
avClassCategoryDecoder = CInt -> Category
Category 6
avClassCategoryFilter :: Category
avClassCategoryFilter = CInt -> Category
Category 7
avClassCategoryBitstreamFilter :: Category
avClassCategoryBitstreamFilter :: Category
avClassCategoryBitstreamFilter = CInt -> Category
Category 8
avClassCategorySwscaler :: Category
avClassCategorySwscaler :: Category
avClassCategorySwscaler = CInt -> Category
Category 9
avClassCategorySwresampler :: Category
avClassCategorySwresampler :: Category
avClassCategorySwresampler = CInt -> Category
Category 10
avClassCategoryDeviceVideoOutput :: Category
avClassCategoryDeviceVideoOutput :: Category
avClassCategoryDeviceVideoOutput = CInt -> Category
Category 40
avClassCategoryDeviceVideoInput :: Category
avClassCategoryDeviceVideoInput :: Category
avClassCategoryDeviceVideoInput = CInt -> Category
Category 41
avClassCategoryDeviceAudioOutput :: Category
avClassCategoryDeviceAudioOutput :: Category
avClassCategoryDeviceAudioOutput = CInt -> Category
Category 42
avClassCategoryDeviceAudioInput :: Category
avClassCategoryDeviceAudioInput :: Category
avClassCategoryDeviceAudioInput = CInt -> Category
Category 43
avClassCategoryDeviceOutput :: Category
avClassCategoryDeviceOutput :: Category
avClassCategoryDeviceOutput = CInt -> Category
Category 44
avClassCategoryDeviceInput :: Category
avClassCategoryDeviceInput :: Category
avClassCategoryDeviceInput = CInt -> Category
Category 45
avClassCategoryNb :: Category
avClassCategoryNb :: Category
avClassCategoryNb = CInt -> Category
Category 46
{-# LINE 179 "src/Codec/FFmpeg/Types.hsc" #-}
{-# LINE 180 "src/Codec/FFmpeg/Types.hsc" #-}
newtype AVIOContext = AVIOContext (Ptr ()) deriving (Storable, HasPtr)
newtype AVPacket = AVPacket (Ptr ()) deriving (Storable, HasPtr)
class HasData t where
getData :: t -> IO (Ptr ())
setData :: t -> (Ptr ()) -> IO ()
hasData :: t -> Ptr (Ptr ())
{-# LINE 185 "src/Codec/FFmpeg/Types.hsc" #-}
class HasSize t where
getSize :: t -> IO CInt
setSize :: t -> CInt -> IO ()
hasSize :: t -> Ptr CInt
{-# LINE 186 "src/Codec/FFmpeg/Types.hsc" #-}
class HasPacketFlags t where
getPacketFlags :: t -> IO PacketFlag
setPacketFlags :: t -> PacketFlag -> IO ()
hasPacketFlags :: t -> Ptr PacketFlag
{-# LINE 187 "src/Codec/FFmpeg/Types.hsc" #-}
class HasDts t where
getDts :: t -> IO CLong
setDts :: t -> CLong -> IO ()
hasDts :: t -> Ptr CLong
{-# LINE 188 "src/Codec/FFmpeg/Types.hsc" #-}
instance HasData AVPacket where
getData = (\hsc_ptr -> peekByteOff hsc_ptr 24) . getPtr
setData = (\hsc_ptr -> pokeByteOff hsc_ptr 24) . getPtr
hasData = (\hsc_ptr -> hsc_ptr `plusPtr` 24) . getPtr
{-# LINE 190 "src/Codec/FFmpeg/Types.hsc" #-}
instance HasSize AVPacket where
getSize = (\hsc_ptr -> peekByteOff hsc_ptr 32) . getPtr
setSize = (\hsc_ptr -> pokeByteOff hsc_ptr 32) . getPtr
hasSize = (\hsc_ptr -> hsc_ptr `plusPtr` 32) . getPtr
{-# LINE 191 "src/Codec/FFmpeg/Types.hsc" #-}
instance HasPacketFlags AVPacket where
getPacketFlags = (\hsc_ptr -> peekByteOff hsc_ptr 40) . getPtr
setPacketFlags = (\hsc_ptr -> pokeByteOff hsc_ptr 40) . getPtr
hasPacketFlags = (\hsc_ptr -> hsc_ptr `plusPtr` 40) . getPtr
{-# LINE 192 "src/Codec/FFmpeg/Types.hsc" #-}
instance HasStreamIndex AVPacket where
getStreamIndex = (\hsc_ptr -> peekByteOff hsc_ptr 36) . getPtr
setStreamIndex = (\hsc_ptr -> pokeByteOff hsc_ptr 36) . getPtr
hasStreamIndex = (\hsc_ptr -> hsc_ptr `plusPtr` 36) . getPtr
{-# LINE 193 "src/Codec/FFmpeg/Types.hsc" #-}
instance HasPts AVPacket where
getPts = (\hsc_ptr -> peekByteOff hsc_ptr 8) . getPtr
setPts = (\hsc_ptr -> pokeByteOff hsc_ptr 8) . getPtr
hasPts = (\hsc_ptr -> hsc_ptr `plusPtr` 8) . getPtr
{-# LINE 194 "src/Codec/FFmpeg/Types.hsc" #-}
instance HasDts AVPacket where
getDts = (\hsc_ptr -> peekByteOff hsc_ptr 16) . getPtr
setDts = (\hsc_ptr -> pokeByteOff hsc_ptr 16) . getPtr
hasDts = (\hsc_ptr -> hsc_ptr `plusPtr` 16) . getPtr
{-# LINE 195 "src/Codec/FFmpeg/Types.hsc" #-}
packetSize :: Int
packetSize = (88)
{-# LINE 199 "src/Codec/FFmpeg/Types.hsc" #-}
pictureSize :: Int
pictureSize = (96)
{-# LINE 202 "src/Codec/FFmpeg/Types.hsc" #-}
data AVRational = AVRational { numerator :: CInt
, denomenator :: CInt } deriving Show
nonZeroAVRational :: AVRational -> Maybe AVRational
nonZeroAVRational :: AVRational -> Maybe AVRational
nonZeroAVRational (AVRational 0 _) = Maybe AVRational
forall a. Maybe a
Nothing
nonZeroAVRational ratio :: AVRational
ratio = AVRational -> Maybe AVRational
forall a. a -> Maybe a
Just AVRational
ratio
instance Storable AVRational where
sizeOf :: AVRational -> Int
sizeOf _ = (8)
{-# LINE 215 "src/Codec/FFmpeg/Types.hsc" #-}
alignment _ = (8)
{-# LINE 216 "src/Codec/FFmpeg/Types.hsc" #-}
peek ptr = AVRational <$> ((\hsc_ptr -> peekByteOff hsc_ptr 0)) ptr
{-# LINE 217 "src/Codec/FFmpeg/Types.hsc" #-}
<*> ((\hsc_ptr -> peekByteOff hsc_ptr 4)) ptr
{-# LINE 218 "src/Codec/FFmpeg/Types.hsc" #-}
poke ptr (AVRational n d) = do ((\hsc_ptr -> pokeByteOff hsc_ptr 0)) ptr n
{-# LINE 219 "src/Codec/FFmpeg/Types.hsc" #-}
((\hsc_ptr -> pokeByteOff hsc_ptr 4)) ptr d
{-# LINE 220 "src/Codec/FFmpeg/Types.hsc" #-}
foreign import ccall "av_rescale_rnd"
av_rescale_rnd :: CLong -> CLong -> CLong -> AVRoundMode -> CLong
av_q2d :: AVRational -> CDouble
av_q2d :: AVRational -> CDouble
av_q2d r :: AVRational
r = CInt -> CDouble
forall a b. (Integral a, Num b) => a -> b
fromIntegral (AVRational -> CInt
numerator AVRational
r) CDouble -> CDouble -> CDouble
forall a. Fractional a => a -> a -> a
/ CInt -> CDouble
forall a b. (Integral a, Num b) => a -> b
fromIntegral (AVRational -> CInt
denomenator AVRational
r)
av_rescale_q :: CLong -> AVRational -> AVRational -> CLong
av_rescale_q :: CLong -> AVRational -> AVRational -> CLong
av_rescale_q a :: CLong
a bq :: AVRational
bq cq :: AVRational
cq = CLong -> CLong -> CLong -> AVRoundMode -> CLong
av_rescale_rnd CLong
a CLong
b CLong
c AVRoundMode
avRoundNearInf
where b :: CLong
b = CInt -> CLong
forall a b. (Integral a, Num b) => a -> b
fromIntegral (AVRational -> CInt
numerator AVRational
bq) CLong -> CLong -> CLong
forall a. Num a => a -> a -> a
* CInt -> CLong
forall a b. (Integral a, Num b) => a -> b
fromIntegral (AVRational -> CInt
denomenator AVRational
cq)
c :: CLong
c = CInt -> CLong
forall a b. (Integral a, Num b) => a -> b
fromIntegral (AVRational -> CInt
numerator AVRational
cq) CLong -> CLong -> CLong
forall a. Num a => a -> a -> a
* CInt -> CLong
forall a b. (Integral a, Num b) => a -> b
fromIntegral (AVRational -> CInt
denomenator AVRational
bq)
{-# LINE 249 "src/Codec/FFmpeg/Types.hsc" #-}
data InputSource = File FilePath | Camera String CameraConfig
deriving (InputSource -> InputSource -> Bool
(InputSource -> InputSource -> Bool)
-> (InputSource -> InputSource -> Bool) -> Eq InputSource
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InputSource -> InputSource -> Bool
$c/= :: InputSource -> InputSource -> Bool
== :: InputSource -> InputSource -> Bool
$c== :: InputSource -> InputSource -> Bool
Eq, Eq InputSource
Eq InputSource =>
(InputSource -> InputSource -> Ordering)
-> (InputSource -> InputSource -> Bool)
-> (InputSource -> InputSource -> Bool)
-> (InputSource -> InputSource -> Bool)
-> (InputSource -> InputSource -> Bool)
-> (InputSource -> InputSource -> InputSource)
-> (InputSource -> InputSource -> InputSource)
-> Ord InputSource
InputSource -> InputSource -> Bool
InputSource -> InputSource -> Ordering
InputSource -> InputSource -> InputSource
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: InputSource -> InputSource -> InputSource
$cmin :: InputSource -> InputSource -> InputSource
max :: InputSource -> InputSource -> InputSource
$cmax :: InputSource -> InputSource -> InputSource
>= :: InputSource -> InputSource -> Bool
$c>= :: InputSource -> InputSource -> Bool
> :: InputSource -> InputSource -> Bool
$c> :: InputSource -> InputSource -> Bool
<= :: InputSource -> InputSource -> Bool
$c<= :: InputSource -> InputSource -> Bool
< :: InputSource -> InputSource -> Bool
$c< :: InputSource -> InputSource -> Bool
compare :: InputSource -> InputSource -> Ordering
$ccompare :: InputSource -> InputSource -> Ordering
$cp1Ord :: Eq InputSource
Ord, Int -> InputSource -> ShowS
[InputSource] -> ShowS
InputSource -> String
(Int -> InputSource -> ShowS)
-> (InputSource -> String)
-> ([InputSource] -> ShowS)
-> Show InputSource
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InputSource] -> ShowS
$cshowList :: [InputSource] -> ShowS
show :: InputSource -> String
$cshow :: InputSource -> String
showsPrec :: Int -> InputSource -> ShowS
$cshowsPrec :: Int -> InputSource -> ShowS
Show, ReadPrec [InputSource]
ReadPrec InputSource
Int -> ReadS InputSource
ReadS [InputSource]
(Int -> ReadS InputSource)
-> ReadS [InputSource]
-> ReadPrec InputSource
-> ReadPrec [InputSource]
-> Read InputSource
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [InputSource]
$creadListPrec :: ReadPrec [InputSource]
readPrec :: ReadPrec InputSource
$creadPrec :: ReadPrec InputSource
readList :: ReadS [InputSource]
$creadList :: ReadS [InputSource]
readsPrec :: Int -> ReadS InputSource
$creadsPrec :: Int -> ReadS InputSource
Read)
data CameraConfig =
CameraConfig { CameraConfig -> Maybe Int
framerate :: Maybe Int
, CameraConfig -> Maybe (Int, Int)
resolution :: Maybe (Int,Int)
, CameraConfig -> Maybe String
format :: Maybe String
}
deriving (CameraConfig -> CameraConfig -> Bool
(CameraConfig -> CameraConfig -> Bool)
-> (CameraConfig -> CameraConfig -> Bool) -> Eq CameraConfig
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CameraConfig -> CameraConfig -> Bool
$c/= :: CameraConfig -> CameraConfig -> Bool
== :: CameraConfig -> CameraConfig -> Bool
$c== :: CameraConfig -> CameraConfig -> Bool
Eq,Eq CameraConfig
Eq CameraConfig =>
(CameraConfig -> CameraConfig -> Ordering)
-> (CameraConfig -> CameraConfig -> Bool)
-> (CameraConfig -> CameraConfig -> Bool)
-> (CameraConfig -> CameraConfig -> Bool)
-> (CameraConfig -> CameraConfig -> Bool)
-> (CameraConfig -> CameraConfig -> CameraConfig)
-> (CameraConfig -> CameraConfig -> CameraConfig)
-> Ord CameraConfig
CameraConfig -> CameraConfig -> Bool
CameraConfig -> CameraConfig -> Ordering
CameraConfig -> CameraConfig -> CameraConfig
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CameraConfig -> CameraConfig -> CameraConfig
$cmin :: CameraConfig -> CameraConfig -> CameraConfig
max :: CameraConfig -> CameraConfig -> CameraConfig
$cmax :: CameraConfig -> CameraConfig -> CameraConfig
>= :: CameraConfig -> CameraConfig -> Bool
$c>= :: CameraConfig -> CameraConfig -> Bool
> :: CameraConfig -> CameraConfig -> Bool
$c> :: CameraConfig -> CameraConfig -> Bool
<= :: CameraConfig -> CameraConfig -> Bool
$c<= :: CameraConfig -> CameraConfig -> Bool
< :: CameraConfig -> CameraConfig -> Bool
$c< :: CameraConfig -> CameraConfig -> Bool
compare :: CameraConfig -> CameraConfig -> Ordering
$ccompare :: CameraConfig -> CameraConfig -> Ordering
$cp1Ord :: Eq CameraConfig
Ord,Int -> CameraConfig -> ShowS
[CameraConfig] -> ShowS
CameraConfig -> String
(Int -> CameraConfig -> ShowS)
-> (CameraConfig -> String)
-> ([CameraConfig] -> ShowS)
-> Show CameraConfig
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CameraConfig] -> ShowS
$cshowList :: [CameraConfig] -> ShowS
show :: CameraConfig -> String
$cshow :: CameraConfig -> String
showsPrec :: Int -> CameraConfig -> ShowS
$cshowsPrec :: Int -> CameraConfig -> ShowS
Show,ReadPrec [CameraConfig]
ReadPrec CameraConfig
Int -> ReadS CameraConfig
ReadS [CameraConfig]
(Int -> ReadS CameraConfig)
-> ReadS [CameraConfig]
-> ReadPrec CameraConfig
-> ReadPrec [CameraConfig]
-> Read CameraConfig
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CameraConfig]
$creadListPrec :: ReadPrec [CameraConfig]
readPrec :: ReadPrec CameraConfig
$creadPrec :: ReadPrec CameraConfig
readList :: ReadS [CameraConfig]
$creadList :: ReadS [CameraConfig]
readsPrec :: Int -> ReadS CameraConfig
$creadsPrec :: Int -> ReadS CameraConfig
Read)
defaultCameraConfig :: CameraConfig
defaultCameraConfig :: CameraConfig
defaultCameraConfig = Maybe Int -> Maybe (Int, Int) -> Maybe String -> CameraConfig
CameraConfig (Int -> Maybe Int
forall a. a -> Maybe a
Just 30) Maybe (Int, Int)
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing