{-# LINE 1 "src/Codec/FFmpeg/Enums.hsc" #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Codec.FFmpeg.Enums where
import Data.Bits (Bits)
import Foreign.C.Types
import Foreign.Storable (Storable)










newtype AVMediaType = AVMediaType CInt deriving (AVMediaType -> AVMediaType -> Bool
(AVMediaType -> AVMediaType -> Bool)
-> (AVMediaType -> AVMediaType -> Bool) -> Eq AVMediaType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AVMediaType -> AVMediaType -> Bool
$c/= :: AVMediaType -> AVMediaType -> Bool
== :: AVMediaType -> AVMediaType -> Bool
$c== :: AVMediaType -> AVMediaType -> Bool
Eq, Ptr b -> Int -> IO AVMediaType
Ptr b -> Int -> AVMediaType -> IO ()
Ptr AVMediaType -> IO AVMediaType
Ptr AVMediaType -> Int -> IO AVMediaType
Ptr AVMediaType -> Int -> AVMediaType -> IO ()
Ptr AVMediaType -> AVMediaType -> IO ()
AVMediaType -> Int
(AVMediaType -> Int)
-> (AVMediaType -> Int)
-> (Ptr AVMediaType -> Int -> IO AVMediaType)
-> (Ptr AVMediaType -> Int -> AVMediaType -> IO ())
-> (forall b. Ptr b -> Int -> IO AVMediaType)
-> (forall b. Ptr b -> Int -> AVMediaType -> IO ())
-> (Ptr AVMediaType -> IO AVMediaType)
-> (Ptr AVMediaType -> AVMediaType -> IO ())
-> Storable AVMediaType
forall b. Ptr b -> Int -> IO AVMediaType
forall b. Ptr b -> Int -> AVMediaType -> 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 AVMediaType -> AVMediaType -> IO ()
$cpoke :: Ptr AVMediaType -> AVMediaType -> IO ()
peek :: Ptr AVMediaType -> IO AVMediaType
$cpeek :: Ptr AVMediaType -> IO AVMediaType
pokeByteOff :: Ptr b -> Int -> AVMediaType -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> AVMediaType -> IO ()
peekByteOff :: Ptr b -> Int -> IO AVMediaType
$cpeekByteOff :: forall b. Ptr b -> Int -> IO AVMediaType
pokeElemOff :: Ptr AVMediaType -> Int -> AVMediaType -> IO ()
$cpokeElemOff :: Ptr AVMediaType -> Int -> AVMediaType -> IO ()
peekElemOff :: Ptr AVMediaType -> Int -> IO AVMediaType
$cpeekElemOff :: Ptr AVMediaType -> Int -> IO AVMediaType
alignment :: AVMediaType -> Int
$calignment :: AVMediaType -> Int
sizeOf :: AVMediaType -> Int
$csizeOf :: AVMediaType -> Int
Storable)
avmediaTypeVideo  :: AVMediaType
avmediaTypeVideo :: AVMediaType
avmediaTypeVideo  = CInt -> AVMediaType
AVMediaType 0
avmediaTypeAudio  :: AVMediaType
avmediaTypeAudio :: AVMediaType
avmediaTypeAudio  = CInt -> AVMediaType
AVMediaType 1
avmediaTypeData  :: AVMediaType
avmediaTypeData :: AVMediaType
avmediaTypeData  = CInt -> AVMediaType
AVMediaType 2
avmediaTypeSubtitle  :: AVMediaType
avmediaTypeSubtitle :: AVMediaType
avmediaTypeSubtitle  = CInt -> AVMediaType
AVMediaType 3
avmediaTypeAttachment  :: AVMediaType
avmediaTypeAttachment :: AVMediaType
avmediaTypeAttachment  = CInt -> AVMediaType
AVMediaType 4
avmediaTypeNb :: AVMediaType
avmediaTypeNb :: AVMediaType
avmediaTypeNb = CInt -> AVMediaType
AVMediaType 5

{-# LINE 24 "src/Codec/FFmpeg/Enums.hsc" #-}

newtype AVPixelFormat = AVPixelFormat CInt deriving (Eq, Storable)
avPixFmtNone  :: AVPixelFormat
avPixFmtNone  = AVPixelFormat (-1)
avPixFmtRgb24  :: AVPixelFormat
avPixFmtRgb24  = AVPixelFormat 2
avPixFmtRgba  :: AVPixelFormat
avPixFmtRgba :: AVPixelFormat
avPixFmtRgba  = CInt -> AVPixelFormat
AVPixelFormat 28
avPixFmtBgra  :: AVPixelFormat
avPixFmtBgra :: AVPixelFormat
avPixFmtBgra  = CInt -> AVPixelFormat
AVPixelFormat 30
avPixFmtY400a  :: AVPixelFormat
avPixFmtY400a :: AVPixelFormat
avPixFmtY400a  = CInt -> AVPixelFormat
AVPixelFormat 66
avPixFmtRgb32  :: AVPixelFormat
avPixFmtRgb32 :: AVPixelFormat
avPixFmtRgb32  = CInt -> AVPixelFormat
AVPixelFormat 30
avPixFmtRgb321  :: AVPixelFormat
avPixFmtRgb321 :: AVPixelFormat
avPixFmtRgb321  = CInt -> AVPixelFormat
AVPixelFormat 29
avPixFmtBgr32  :: AVPixelFormat
avPixFmtBgr32 :: AVPixelFormat
avPixFmtBgr32  = CInt -> AVPixelFormat
AVPixelFormat 28
avPixFmtBgr321  :: AVPixelFormat
avPixFmtBgr321 :: AVPixelFormat
avPixFmtBgr321  = CInt -> AVPixelFormat
AVPixelFormat 27
avPixFmtRgb8  :: AVPixelFormat
avPixFmtRgb8 :: AVPixelFormat
avPixFmtRgb8  = CInt -> AVPixelFormat
AVPixelFormat 22
avPixFmtBgr8  :: AVPixelFormat
avPixFmtBgr8 :: AVPixelFormat
avPixFmtBgr8  = CInt -> AVPixelFormat
AVPixelFormat 19
avPixFmtRgb4Byte  :: AVPixelFormat
avPixFmtRgb4Byte :: AVPixelFormat
avPixFmtRgb4Byte  = CInt -> AVPixelFormat
AVPixelFormat 24
avPixFmtBgr4Byte  :: AVPixelFormat
avPixFmtBgr4Byte :: AVPixelFormat
avPixFmtBgr4Byte  = CInt -> AVPixelFormat
AVPixelFormat 21
avPixFmtGray8  :: AVPixelFormat
avPixFmtGray8 :: AVPixelFormat
avPixFmtGray8  = CInt -> AVPixelFormat
AVPixelFormat 8
avPixFmtGray16  :: AVPixelFormat
avPixFmtGray16 :: AVPixelFormat
avPixFmtGray16  = CInt -> AVPixelFormat
AVPixelFormat 32
avPixFmtGray8a  :: AVPixelFormat
avPixFmtGray8a :: AVPixelFormat
avPixFmtGray8a  = CInt -> AVPixelFormat
AVPixelFormat 66
avPixFmtPal8  :: AVPixelFormat
avPixFmtPal8 :: AVPixelFormat
avPixFmtPal8  = CInt -> AVPixelFormat
AVPixelFormat 11
avPixFmtRgb565  :: AVPixelFormat
avPixFmtRgb565 :: AVPixelFormat
avPixFmtRgb565  = CInt -> AVPixelFormat
AVPixelFormat 44
avPixFmtRgb555  :: AVPixelFormat
avPixFmtRgb555 :: AVPixelFormat
avPixFmtRgb555  = CInt -> AVPixelFormat
AVPixelFormat 46
avPixFmtYuv420p  :: AVPixelFormat
avPixFmtYuv420p :: AVPixelFormat
avPixFmtYuv420p  = CInt -> AVPixelFormat
AVPixelFormat 0
avPixFmtYuv420p9  :: AVPixelFormat
avPixFmtYuv420p9 :: AVPixelFormat
avPixFmtYuv420p9  = CInt -> AVPixelFormat
AVPixelFormat 70
avPixFmtYuv420p10  :: AVPixelFormat
avPixFmtYuv420p10 :: AVPixelFormat
avPixFmtYuv420p10  = CInt -> AVPixelFormat
AVPixelFormat 72
avPixFmtYuv420p12  :: AVPixelFormat
avPixFmtYuv420p12 :: AVPixelFormat
avPixFmtYuv420p12  = CInt -> AVPixelFormat
AVPixelFormat 300
avPixFmtYuv422p12  :: AVPixelFormat
avPixFmtYuv422p12 :: AVPixelFormat
avPixFmtYuv422p12  = CInt -> AVPixelFormat
AVPixelFormat 304
avPixFmtYuv444p12  :: AVPixelFormat
avPixFmtYuv444p12 :: AVPixelFormat
avPixFmtYuv444p12  = CInt -> AVPixelFormat
AVPixelFormat 308
avPixFmtYuv420p14  :: AVPixelFormat
avPixFmtYuv420p14 :: AVPixelFormat
avPixFmtYuv420p14  = CInt -> AVPixelFormat
AVPixelFormat 302
avPixFmtYuv422p14  :: AVPixelFormat
avPixFmtYuv422p14 :: AVPixelFormat
avPixFmtYuv422p14  = CInt -> AVPixelFormat
AVPixelFormat 306
avPixFmtYuv444p14  :: AVPixelFormat
avPixFmtYuv444p14 :: AVPixelFormat
avPixFmtYuv444p14  = CInt -> AVPixelFormat
AVPixelFormat 310
avPixFmtYuv420p16  :: AVPixelFormat
avPixFmtYuv420p16 :: AVPixelFormat
avPixFmtYuv420p16  = CInt -> AVPixelFormat
AVPixelFormat 54
avPixFmtYuv422p16  :: AVPixelFormat
avPixFmtYuv422p16 :: AVPixelFormat
avPixFmtYuv422p16  = CInt -> AVPixelFormat
AVPixelFormat 56
avPixFmtYuv444p16  :: AVPixelFormat
avPixFmtYuv444p16 :: AVPixelFormat
avPixFmtYuv444p16  = CInt -> AVPixelFormat
AVPixelFormat 58
avPixFmtRgba64  :: AVPixelFormat
avPixFmtRgba64 :: AVPixelFormat
avPixFmtRgba64  = CInt -> AVPixelFormat
AVPixelFormat 116
avCodecIdLjpeg :: AVCodecID
avPixFmtBgra64 :: AVPixelFormat
avPixFmtBgra64 :: AVPixelFormat
avPixFmtBgra64 = CInt -> AVPixelFormat
AVPixelFormat 118

{-# LINE 60 "src/Codec/FFmpeg/Enums.hsc" #-}

instance Show AVPixelFormat where
  show x
    | x == avPixFmtRgb24 = "AV_PIX_FMT_RGB24"
    | x == avPixFmtYuv420p = "AV_PIX_FMT_Y420P"
    | x == avPixFmtYuv422p12 = "AV_PIX_FMTYUV422P12"
    | x == avPixFmtYuv420p14 = "AV_PIX_FMTYUV422P12"
    | otherwise = let AVPixelFormat y = x
                  in "Other pixel format: "++show y

newtype AVCodecID = AVCodecID CInt deriving (Eq, Show, Storable)
avCodecIdNone  :: AVCodecID
avCodecIdNone  = AVCodecID 0
avCodecIdMpeg1video  :: AVCodecID
avCodecIdMpeg1video  = AVCodecID 1
avCodecIdMpeg2video  :: AVCodecID
avCodecIdMpeg2video  = AVCodecID 2
avCodecIdH261  :: AVCodecID
avCodecIdH261  = AVCodecID 4
avCodecIdH263  :: AVCodecID
avCodecIdH263  = AVCodecID 5
avCodecIdRv10  :: AVCodecID
avCodecIdRv10  = AVCodecID 6
avCodecIdRv20  :: AVCodecID
avCodecIdRv20  = AVCodecID 7
avCodecIdMjpeg  :: AVCodecID
avCodecIdMjpeg  = AVCodecID 8
avCodecIdMjpegb  :: AVCodecID
avCodecIdMjpegb  = AVCodecID 9
avCodecIdLjpeg  :: AVCodecID
avCodecIdLjpeg  = AVCodecID 10
avCodecIdSp5x  :: AVCodecID
avCodecIdSp5x  = AVCodecID 11
avCodecIdJpegls  :: AVCodecID
avCodecIdJpegls :: AVCodecID
avCodecIdJpegls  = CInt -> AVCodecID
AVCodecID 12
avCodecIdMpeg4  :: AVCodecID
avCodecIdMpeg4 :: AVCodecID
avCodecIdMpeg4  = CInt -> AVCodecID
AVCodecID 13
avCodecIdRawvideo  :: AVCodecID
avCodecIdRawvideo :: AVCodecID
avCodecIdRawvideo  = CInt -> AVCodecID
AVCodecID 14
avCodecIdMsmpeg4v1  :: AVCodecID
avCodecIdMsmpeg4v1 :: AVCodecID
avCodecIdMsmpeg4v1  = CInt -> AVCodecID
AVCodecID 15
avCodecIdMsmpeg4v2  :: AVCodecID
avCodecIdMsmpeg4v2 :: AVCodecID
avCodecIdMsmpeg4v2  = CInt -> AVCodecID
AVCodecID 16
avCodecIdMsmpeg4v3  :: AVCodecID
avCodecIdMsmpeg4v3 :: AVCodecID
avCodecIdMsmpeg4v3  = CInt -> AVCodecID
AVCodecID 17
avCodecIdWmv1  :: AVCodecID
avCodecIdWmv1 :: AVCodecID
avCodecIdWmv1  = CInt -> AVCodecID
AVCodecID 18
avCodecIdWmv2  :: AVCodecID
avCodecIdWmv2 :: AVCodecID
avCodecIdWmv2  = CInt -> AVCodecID
AVCodecID 19
avCodecIdH263p  :: AVCodecID
avCodecIdH263p :: AVCodecID
avCodecIdH263p  = CInt -> AVCodecID
AVCodecID 20
avCodecIdH263i  :: AVCodecID
avCodecIdH263i :: AVCodecID
avCodecIdH263i  = CInt -> AVCodecID
AVCodecID 21
avCodecIdFlv1  :: AVCodecID
avCodecIdFlv1 :: AVCodecID
avCodecIdFlv1  = CInt -> AVCodecID
AVCodecID 22
avCodecIdSvq1  :: AVCodecID
avCodecIdSvq1 :: AVCodecID
avCodecIdSvq1  = CInt -> AVCodecID
AVCodecID 23
avCodecIdSvq3  :: AVCodecID
avCodecIdSvq3 :: AVCodecID
avCodecIdSvq3  = CInt -> AVCodecID
AVCodecID 24
avCodecIdDvvideo  :: AVCodecID
avCodecIdDvvideo :: AVCodecID
avCodecIdDvvideo  = CInt -> AVCodecID
AVCodecID 25
avCodecIdHuffyuv  :: AVCodecID
avCodecIdHuffyuv :: AVCodecID
avCodecIdHuffyuv  = CInt -> AVCodecID
AVCodecID 26
avCodecIdCyuv  :: AVCodecID
avCodecIdCyuv :: AVCodecID
avCodecIdCyuv  = CInt -> AVCodecID
AVCodecID 27
avCodecIdH264  :: AVCodecID
avCodecIdH264 :: AVCodecID
avCodecIdH264  = CInt -> AVCodecID
AVCodecID 28
avCodecIdIndeo3  :: AVCodecID
avCodecIdIndeo3 :: AVCodecID
avCodecIdIndeo3  = CInt -> AVCodecID
AVCodecID 29
avCodecIdVp3  :: AVCodecID
avCodecIdVp3 :: AVCodecID
avCodecIdVp3  = CInt -> AVCodecID
AVCodecID 30
avCodecIdTheora  :: AVCodecID
avCodecIdTheora :: AVCodecID
avCodecIdTheora  = CInt -> AVCodecID
AVCodecID 31
avCodecIdAsv1  :: AVCodecID
avCodecIdAsv1 :: AVCodecID
avCodecIdAsv1  = CInt -> AVCodecID
AVCodecID 32
avCodecIdAsv2  :: AVCodecID
avCodecIdAsv2 :: AVCodecID
avCodecIdAsv2  = CInt -> AVCodecID
AVCodecID 33
avCodecIdFfv1  :: AVCodecID
avCodecIdFfv1 :: AVCodecID
avCodecIdFfv1  = CInt -> AVCodecID
AVCodecID 34
avCodecId4xm  :: AVCodecID
avCodecId4xm :: AVCodecID
avCodecId4xm  = CInt -> AVCodecID
AVCodecID 35
avCodecIdVcr1  :: AVCodecID
avCodecIdVcr1 :: AVCodecID
avCodecIdVcr1  = CInt -> AVCodecID
AVCodecID 36
avCodecIdCljr  :: AVCodecID
avCodecIdCljr :: AVCodecID
avCodecIdCljr  = CInt -> AVCodecID
AVCodecID 37
avCodecIdMdec  :: AVCodecID
avCodecIdMdec :: AVCodecID
avCodecIdMdec  = CInt -> AVCodecID
AVCodecID 38
avCodecIdRoq  :: AVCodecID
avCodecIdRoq :: AVCodecID
avCodecIdRoq  = CInt -> AVCodecID
AVCodecID 39
avCodecIdInterplayVideo  :: AVCodecID
avCodecIdInterplayVideo :: AVCodecID
avCodecIdInterplayVideo  = CInt -> AVCodecID
AVCodecID 40
avCodecIdXanWc3  :: AVCodecID
avCodecIdXanWc3 :: AVCodecID
avCodecIdXanWc3  = CInt -> AVCodecID
AVCodecID 41
avCodecIdXanWc4  :: AVCodecID
avCodecIdXanWc4 :: AVCodecID
avCodecIdXanWc4  = CInt -> AVCodecID
AVCodecID 42
avCodecIdRpza  :: AVCodecID
avCodecIdRpza :: AVCodecID
avCodecIdRpza  = CInt -> AVCodecID
AVCodecID 43
avCodecIdCinepak  :: AVCodecID
avCodecIdCinepak :: AVCodecID
avCodecIdCinepak  = CInt -> AVCodecID
AVCodecID 44
avCodecIdWsVqa  :: AVCodecID
avCodecIdWsVqa :: AVCodecID
avCodecIdWsVqa  = CInt -> AVCodecID
AVCodecID 45
avCodecIdMsrle  :: AVCodecID
avCodecIdMsrle :: AVCodecID
avCodecIdMsrle  = CInt -> AVCodecID
AVCodecID 46
avCodecIdMsvideo1  :: AVCodecID
avCodecIdMsvideo1 :: AVCodecID
avCodecIdMsvideo1  = CInt -> AVCodecID
AVCodecID 47
avCodecIdIdcin  :: AVCodecID
avCodecIdIdcin :: AVCodecID
avCodecIdIdcin  = CInt -> AVCodecID
AVCodecID 48
avCodecId8bps  :: AVCodecID
avCodecId8bps :: AVCodecID
avCodecId8bps  = CInt -> AVCodecID
AVCodecID 49
avCodecIdSmc  :: AVCodecID
avCodecIdSmc :: AVCodecID
avCodecIdSmc  = CInt -> AVCodecID
AVCodecID 50
avCodecIdFlic  :: AVCodecID
avCodecIdFlic :: AVCodecID
avCodecIdFlic  = CInt -> AVCodecID
AVCodecID 51
avCodecIdTruemotion1  :: AVCodecID
avCodecIdTruemotion1 :: AVCodecID
avCodecIdTruemotion1  = CInt -> AVCodecID
AVCodecID 52
avCodecIdVmdvideo  :: AVCodecID
avCodecIdVmdvideo :: AVCodecID
avCodecIdVmdvideo  = CInt -> AVCodecID
AVCodecID 53
avCodecIdMszh  :: AVCodecID
avCodecIdMszh :: AVCodecID
avCodecIdMszh  = CInt -> AVCodecID
AVCodecID 54
avCodecIdZlib  :: AVCodecID
avCodecIdZlib :: AVCodecID
avCodecIdZlib  = CInt -> AVCodecID
AVCodecID 55
avCodecIdQtrle  :: AVCodecID
avCodecIdQtrle :: AVCodecID
avCodecIdQtrle  = CInt -> AVCodecID
AVCodecID 56
avCodecIdTscc  :: AVCodecID
avCodecIdTscc :: AVCodecID
avCodecIdTscc  = CInt -> AVCodecID
AVCodecID 57
avCodecIdUlti  :: AVCodecID
avCodecIdUlti :: AVCodecID
avCodecIdUlti  = CInt -> AVCodecID
AVCodecID 58
avCodecIdQdraw  :: AVCodecID
avCodecIdQdraw :: AVCodecID
avCodecIdQdraw  = CInt -> AVCodecID
AVCodecID 59
avCodecIdVixl  :: AVCodecID
avCodecIdVixl :: AVCodecID
avCodecIdVixl  = CInt -> AVCodecID
AVCodecID 60
avCodecIdQpeg  :: AVCodecID
avCodecIdQpeg :: AVCodecID
avCodecIdQpeg  = CInt -> AVCodecID
AVCodecID 61
avCodecIdPng  :: AVCodecID
avCodecIdPng :: AVCodecID
avCodecIdPng  = CInt -> AVCodecID
AVCodecID 62
avCodecIdPpm  :: AVCodecID
avCodecIdPpm :: AVCodecID
avCodecIdPpm  = CInt -> AVCodecID
AVCodecID 63
avCodecIdPbm  :: AVCodecID
avCodecIdPbm :: AVCodecID
avCodecIdPbm  = CInt -> AVCodecID
AVCodecID 64
avCodecIdPgm  :: AVCodecID
avCodecIdPgm :: AVCodecID
avCodecIdPgm  = CInt -> AVCodecID
AVCodecID 65
avCodecIdPgmyuv  :: AVCodecID
avCodecIdPgmyuv :: AVCodecID
avCodecIdPgmyuv  = CInt -> AVCodecID
AVCodecID 66
avCodecIdPam  :: AVCodecID
avCodecIdPam :: AVCodecID
avCodecIdPam  = CInt -> AVCodecID
AVCodecID 67
avCodecIdFfvhuff  :: AVCodecID
avCodecIdFfvhuff :: AVCodecID
avCodecIdFfvhuff  = CInt -> AVCodecID
AVCodecID 68
avCodecIdRv30  :: AVCodecID
avCodecIdRv30 :: AVCodecID
avCodecIdRv30  = CInt -> AVCodecID
AVCodecID 69
avCodecIdRv40  :: AVCodecID
avCodecIdRv40 :: AVCodecID
avCodecIdRv40  = CInt -> AVCodecID
AVCodecID 70
avCodecIdVc1  :: AVCodecID
avCodecIdVc1 :: AVCodecID
avCodecIdVc1  = CInt -> AVCodecID
AVCodecID 71
avCodecIdWmv3  :: AVCodecID
avCodecIdWmv3 :: AVCodecID
avCodecIdWmv3  = CInt -> AVCodecID
AVCodecID 72
avCodecIdLoco  :: AVCodecID
avCodecIdLoco :: AVCodecID
avCodecIdLoco  = CInt -> AVCodecID
AVCodecID 73
avCodecIdWnv1  :: AVCodecID
avCodecIdWnv1 :: AVCodecID
avCodecIdWnv1  = CInt -> AVCodecID
AVCodecID 74
avCodecIdAasc  :: AVCodecID
avCodecIdAasc :: AVCodecID
avCodecIdAasc  = CInt -> AVCodecID
AVCodecID 75
avCodecIdIndeo2  :: AVCodecID
avCodecIdIndeo2 :: AVCodecID
avCodecIdIndeo2  = CInt -> AVCodecID
AVCodecID 76
avCodecIdFraps  :: AVCodecID
avCodecIdFraps :: AVCodecID
avCodecIdFraps  = CInt -> AVCodecID
AVCodecID 77
avCodecIdTruemotion2  :: AVCodecID
avCodecIdTruemotion2 :: AVCodecID
avCodecIdTruemotion2  = CInt -> AVCodecID
AVCodecID 78
avCodecIdBmp  :: AVCodecID
avCodecIdBmp :: AVCodecID
avCodecIdBmp  = CInt -> AVCodecID
AVCodecID 79
avCodecIdCscd  :: AVCodecID
avCodecIdCscd :: AVCodecID
avCodecIdCscd  = CInt -> AVCodecID
AVCodecID 80
avCodecIdMmvideo  :: AVCodecID
avCodecIdMmvideo :: AVCodecID
avCodecIdMmvideo  = CInt -> AVCodecID
AVCodecID 81
avCodecIdZmbv  :: AVCodecID
avCodecIdZmbv :: AVCodecID
avCodecIdZmbv  = CInt -> AVCodecID
AVCodecID 82
avCodecIdAvs  :: AVCodecID
avCodecIdAvs :: AVCodecID
avCodecIdAvs  = CInt -> AVCodecID
AVCodecID 83
avCodecIdSmackvideo  :: AVCodecID
avCodecIdSmackvideo :: AVCodecID
avCodecIdSmackvideo  = CInt -> AVCodecID
AVCodecID 84
avCodecIdNuv  :: AVCodecID
avCodecIdNuv :: AVCodecID
avCodecIdNuv  = CInt -> AVCodecID
AVCodecID 85
avCodecIdKmvc  :: AVCodecID
avCodecIdKmvc :: AVCodecID
avCodecIdKmvc  = CInt -> AVCodecID
AVCodecID 86
avCodecIdFlashsv  :: AVCodecID
avCodecIdFlashsv :: AVCodecID
avCodecIdFlashsv  = CInt -> AVCodecID
AVCodecID 87
avCodecIdCavs  :: AVCodecID
avCodecIdCavs :: AVCodecID
avCodecIdCavs  = CInt -> AVCodecID
AVCodecID 88
avCodecIdJpeg2000  :: AVCodecID
avCodecIdJpeg2000 :: AVCodecID
avCodecIdJpeg2000  = CInt -> AVCodecID
AVCodecID 89
avCodecIdVmnc  :: AVCodecID
avCodecIdVmnc :: AVCodecID
avCodecIdVmnc  = CInt -> AVCodecID
AVCodecID 90
avCodecIdVp5  :: AVCodecID
avCodecIdVp5 :: AVCodecID
avCodecIdVp5  = CInt -> AVCodecID
AVCodecID 91
avCodecIdVp6  :: AVCodecID
avCodecIdVp6 :: AVCodecID
avCodecIdVp6  = CInt -> AVCodecID
AVCodecID 92
avCodecIdVp6f  :: AVCodecID
avCodecIdVp6f :: AVCodecID
avCodecIdVp6f  = CInt -> AVCodecID
AVCodecID 93
avCodecIdTarga  :: AVCodecID
avCodecIdTarga :: AVCodecID
avCodecIdTarga  = CInt -> AVCodecID
AVCodecID 94
avCodecIdDsicinvideo  :: AVCodecID
avCodecIdDsicinvideo :: AVCodecID
avCodecIdDsicinvideo  = CInt -> AVCodecID
AVCodecID 95
avCodecIdTiertexseqvideo  :: AVCodecID
avCodecIdTiertexseqvideo :: AVCodecID
avCodecIdTiertexseqvideo  = CInt -> AVCodecID
AVCodecID 96
avCodecIdTiff  :: AVCodecID
avCodecIdTiff :: AVCodecID
avCodecIdTiff  = CInt -> AVCodecID
AVCodecID 97
avCodecIdGif  :: AVCodecID
avCodecIdGif :: AVCodecID
avCodecIdGif  = CInt -> AVCodecID
AVCodecID 98
avCodecIdDxa  :: AVCodecID
avCodecIdDxa :: AVCodecID
avCodecIdDxa  = CInt -> AVCodecID
AVCodecID 99
avCodecIdDnxhd  :: AVCodecID
avCodecIdDnxhd :: AVCodecID
avCodecIdDnxhd  = CInt -> AVCodecID
AVCodecID 100
avCodecIdThp  :: AVCodecID
avCodecIdThp :: AVCodecID
avCodecIdThp  = CInt -> AVCodecID
AVCodecID 101
avCodecIdSgi  :: AVCodecID
avCodecIdSgi :: AVCodecID
avCodecIdSgi  = CInt -> AVCodecID
AVCodecID 102
avCodecIdC93  :: AVCodecID
avCodecIdC93 :: AVCodecID
avCodecIdC93  = CInt -> AVCodecID
AVCodecID 103
avCodecIdBethsoftvid  :: AVCodecID
avCodecIdBethsoftvid :: AVCodecID
avCodecIdBethsoftvid  = CInt -> AVCodecID
AVCodecID 104
avCodecIdPtx  :: AVCodecID
avCodecIdPtx :: AVCodecID
avCodecIdPtx  = CInt -> AVCodecID
AVCodecID 105
avCodecIdTxd  :: AVCodecID
avCodecIdTxd :: AVCodecID
avCodecIdTxd  = CInt -> AVCodecID
AVCodecID 106
avCodecIdVp6a  :: AVCodecID
avCodecIdVp6a :: AVCodecID
avCodecIdVp6a  = CInt -> AVCodecID
AVCodecID 107
avCodecIdAmv  :: AVCodecID
avCodecIdAmv :: AVCodecID
avCodecIdAmv  = CInt -> AVCodecID
AVCodecID 108
avCodecIdVb  :: AVCodecID
avCodecIdVb :: AVCodecID
avCodecIdVb  = CInt -> AVCodecID
AVCodecID 109
avCodecIdPcx  :: AVCodecID
avCodecIdPcx :: AVCodecID
avCodecIdPcx  = CInt -> AVCodecID
AVCodecID 110
avCodecIdSunrast  :: AVCodecID
avCodecIdSunrast :: AVCodecID
avCodecIdSunrast  = CInt -> AVCodecID
AVCodecID 111
avCodecIdIndeo4  :: AVCodecID
avCodecIdIndeo4 :: AVCodecID
avCodecIdIndeo4  = CInt -> AVCodecID
AVCodecID 112
avCodecIdIndeo5  :: AVCodecID
avCodecIdIndeo5 :: AVCodecID
avCodecIdIndeo5  = CInt -> AVCodecID
AVCodecID 113
avCodecIdMimic  :: AVCodecID
avCodecIdMimic :: AVCodecID
avCodecIdMimic  = CInt -> AVCodecID
AVCodecID 114
avCodecIdRl2  :: AVCodecID
avCodecIdRl2 :: AVCodecID
avCodecIdRl2  = CInt -> AVCodecID
AVCodecID 115
avCodecIdEscape124  :: AVCodecID
avCodecIdEscape124 :: AVCodecID
avCodecIdEscape124  = CInt -> AVCodecID
AVCodecID 116
avCodecIdDirac  :: AVCodecID
avCodecIdDirac :: AVCodecID
avCodecIdDirac  = CInt -> AVCodecID
AVCodecID 117
avCodecIdBfi  :: AVCodecID
avCodecIdBfi :: AVCodecID
avCodecIdBfi  = CInt -> AVCodecID
AVCodecID 118
avCodecIdCmv  :: AVCodecID
avCodecIdCmv :: AVCodecID
avCodecIdCmv  = CInt -> AVCodecID
AVCodecID 119
avCodecIdMotionpixels  :: AVCodecID
avCodecIdMotionpixels :: AVCodecID
avCodecIdMotionpixels  = CInt -> AVCodecID
AVCodecID 120
avCodecIdTgv  :: AVCodecID
avCodecIdTgv :: AVCodecID
avCodecIdTgv  = CInt -> AVCodecID
AVCodecID 121
avCodecIdTgq  :: AVCodecID
avCodecIdTgq :: AVCodecID
avCodecIdTgq  = CInt -> AVCodecID
AVCodecID 122
avCodecIdTqi  :: AVCodecID
avCodecIdTqi :: AVCodecID
avCodecIdTqi  = CInt -> AVCodecID
AVCodecID 123
avCodecIdAura  :: AVCodecID
avCodecIdAura :: AVCodecID
avCodecIdAura  = CInt -> AVCodecID
AVCodecID 124
avCodecIdAura2  :: AVCodecID
avCodecIdAura2 :: AVCodecID
avCodecIdAura2  = CInt -> AVCodecID
AVCodecID 125
avCodecIdV210x  :: AVCodecID
avCodecIdV210x :: AVCodecID
avCodecIdV210x  = CInt -> AVCodecID
AVCodecID 126
avCodecIdTmv  :: AVCodecID
avCodecIdTmv :: AVCodecID
avCodecIdTmv  = CInt -> AVCodecID
AVCodecID 127
avCodecIdV210  :: AVCodecID
avCodecIdV210 :: AVCodecID
avCodecIdV210  = CInt -> AVCodecID
AVCodecID 128
avCodecIdDpx  :: AVCodecID
avCodecIdDpx :: AVCodecID
avCodecIdDpx  = CInt -> AVCodecID
AVCodecID 129
avCodecIdMad  :: AVCodecID
avCodecIdMad :: AVCodecID
avCodecIdMad  = CInt -> AVCodecID
AVCodecID 130
avCodecIdFrwu  :: AVCodecID
avCodecIdFrwu :: AVCodecID
avCodecIdFrwu  = CInt -> AVCodecID
AVCodecID 131
avCodecIdFlashsv2  :: AVCodecID
avCodecIdFlashsv2 :: AVCodecID
avCodecIdFlashsv2  = AVCodecID 132
avCodecIdCdgraphics  :: AVCodecID
avCodecIdCdgraphics :: AVCodecID
avCodecIdCdgraphics  = CInt -> AVCodecID
AVCodecID 133
avCodecIdR210  :: AVCodecID
avCodecIdR210 :: AVCodecID
avCodecIdR210  = AVCodecID 134
avCodecIdAnm  :: AVCodecID
avCodecIdAnm :: AVCodecID
avCodecIdAnm  = CInt -> AVCodecID
AVCodecID 135
avCodecIdBinkvideo  :: AVCodecID
avCodecIdBinkvideo :: AVCodecID
avCodecIdBinkvideo  = CInt -> AVCodecID
AVCodecID 136
avCodecIdIffIlbm  :: AVCodecID
avCodecIdIffIlbm :: AVCodecID
avCodecIdIffIlbm  = CInt -> AVCodecID
AVCodecID 137
avCodecIdKgv1  :: AVCodecID
avCodecIdKgv1 :: AVCodecID
avCodecIdKgv1  = AVCodecID 138
avCodecIdYop  :: AVCodecID
avCodecIdYop :: AVCodecID
avCodecIdYop  = AVCodecID 139
avCodecIdVp8  :: AVCodecID
avCodecIdVp8 :: AVCodecID
avCodecIdVp8  = AVCodecID 140
avCodecIdPictor  :: AVCodecID
ffProfileAacSsr :: FFProfile
avCodecIdPictor :: AVCodecID
avCodecIdPictor  = CInt -> FFProfile
AVCodecID 141
avCodecIdAnsi  :: AVCodecID
avCodecIdAnsi :: AVCodecID
avCodecIdAnsi  = AVCodecID 142
avCodecIdA64Multi  :: AVCodecID
avCodecIdA64Multi :: AVCodecID
avCodecIdA64Multi  = CInt -> AVCodecID
AVCodecID 143
avCodecIdA64Multi5  :: AVCodecID
avCodecIdA64Multi5 :: AVCodecID
avCodecIdA64Multi5  = AVCodecID 144
avCodecIdR10k  :: AVCodecID
avCodecIdR10k :: AVCodecID
avCodecIdR10k  = CInt -> AVCodecID
AVCodecID 145
avCodecIdMxpeg  :: AVCodecID
avCodecIdMxpeg :: AVCodecID
avCodecIdMxpeg  = CInt -> AVCodecID
AVCodecID 146
avCodecIdLagarith  :: AVCodecID
avCodecIdLagarith :: AVCodecID
avCodecIdLagarith  = CInt -> AVCodecID
AVCodecID 147
avCodecIdProres  :: AVCodecID
avCodecIdProres :: AVCodecID
avCodecIdProres  = CInt -> AVCodecID
AVCodecID 148
avCodecIdJv  :: AVCodecID
avCodecIdJv :: AVCodecID
avCodecIdJv  = CInt -> AVCodecID
AVCodecID 149
avCodecIdDfa  :: AVCodecID
avCodecIdDfa :: AVCodecID
avCodecIdDfa  = CInt -> AVCodecID
AVCodecID 150
avCodecIdWmv3image  :: AVCodecID
avCodecIdWmv3image :: AVCodecID
avCodecIdWmv3image  = AVCodecID 151
avCodecIdVc1image  :: AVCodecID
ffProfileDtsHdHra :: FFProfile
avCodecIdVc1image :: AVCodecID
avCodecIdVc1image  = CInt -> FFProfile
AVCodecID 152
avCodecIdUtvideo  :: AVCodecID
ffProfileDtsHdMa :: FFProfile
avCodecIdUtvideo :: AVCodecID
avCodecIdUtvideo  = CInt -> FFProfile
AVCodecID 153
avCodecIdBmvVideo  :: AVCodecID
ffProfileMpeg2422 :: FFProfile
avCodecIdBmvVideo :: AVCodecID
avCodecIdBmvVideo  = CInt -> FFProfile
AVCodecID 154
avCodecIdVble  :: AVCodecID
avCodecIdVble :: AVCodecID
avCodecIdVble  = CInt -> AVCodecID
AVCodecID 155
avCodecIdDxtory  :: AVCodecID
avCodecIdDxtory :: AVCodecID
avCodecIdDxtory  = AVCodecID 156
avCodecIdV410  :: AVCodecID
avCodecIdV410 :: AVCodecID
avCodecIdV410  = CInt -> AVCodecID
AVCodecID 157
avCodecIdXwd  :: AVCodecID
avCodecIdXwd :: AVCodecID
avCodecIdXwd  = CInt -> AVCodecID
AVCodecID 158
avCodecIdCdxl  :: AVCodecID
avCodecIdCdxl :: AVCodecID
avCodecIdCdxl  = CInt -> AVCodecID
AVCodecID 159
avCodecIdXbm  :: AVCodecID
avCodecIdXbm :: AVCodecID
avCodecIdXbm  = CInt -> AVCodecID
AVCodecID 160
avCodecIdZerocodec  :: AVCodecID
ffProfileH264Intra :: FFProfile
avCodecIdZerocodec :: AVCodecID
avCodecIdZerocodec  = CInt -> AVCodecID
AVCodecID 161
avCodecIdMss1  :: AVCodecID
avCodecIdMss1 :: AVCodecID
avCodecIdMss1  = CInt -> AVCodecID
AVCodecID 162
avCodecIdMsa1  :: AVCodecID
avCodecIdMsa1 :: AVCodecID
avCodecIdMsa1  = CInt -> AVCodecID
AVCodecID 163
avCodecIdTscc2  :: AVCodecID
avCodecIdTscc2 :: AVCodecID
avCodecIdTscc2  = CInt -> AVCodecID
AVCodecID 164
avCodecIdMts2  :: AVCodecID
avCodecIdMts2 :: AVCodecID
avCodecIdMts2  = CInt -> AVCodecID
AVCodecID 165
avCodecIdCllc  :: AVCodecID
avCodecIdCllc :: AVCodecID
avCodecIdCllc  = CInt -> AVCodecID
AVCodecID 166
avCodecIdMss2  :: AVCodecID
avCodecIdMss2 :: AVCodecID
avCodecIdMss2  = CInt -> AVCodecID
AVCodecID 167
avCodecIdVp9  :: AVCodecID
avCodecIdVp9 :: AVCodecID
avCodecIdVp9  = AVCodecID 168
avioFlagRead :: AVIOFlag
avCodecIdAic  :: AVCodecID
avCodecIdAic :: AVCodecID
avCodecIdAic  = AVCodecID 169
avCodecIdEscape130  :: AVCodecID
avCodecIdEscape130 :: AVCodecID
avCodecIdEscape130  = CInt -> AVCodecID
AVCodecID 170
avCodecIdG2m  :: AVCodecID
avCodecIdG2m :: AVCodecID
avCodecIdG2m  = CInt -> AVCodecID
AVCodecID 171
avCodecIdWebp  :: AVCodecID
avCodecIdWebp :: AVCodecID
avCodecIdWebp  = AVCodecID 172
avCodecIdHnm4Video  :: AVCodecID
avCodecIdHnm4Video :: AVCodecID
avCodecIdHnm4Video  = CInt -> AVCodecID
AVCodecID 173
avCodecIdHevc  :: AVCodecID
avCodecIdHevc :: AVCodecID
avCodecIdHevc  = AVCodecID 174
avCodecIdMp2  :: AVCodecID
avCodecIdMp2 :: AVCodecID
avCodecIdMp2  = AVCodecID 86016
avCodecIdMp3  :: AVCodecID
avCodecIdMp3 :: AVCodecID
avCodecIdMp3  = AVCodecID 86017
avCodecIdAac  :: AVCodecID
avCodecIdAac :: AVCodecID
avCodecIdAac  = CInt -> AVCodecID
AVCodecID 86018
avCodecIdAc3  :: AVCodecID
avCodecIdAc3 :: AVCodecID
avCodecIdAc3  = CInt -> AVCodecID
AVCodecID 86019
avCodecIdDts  :: AVCodecID
avCodecIdDts :: AVCodecID
avCodecIdDts  = CInt -> AVCodecID
AVCodecID 86020
avCodecIdVorbis  :: AVCodecID
avCodecIdVorbis :: AVCodecID
avCodecIdVorbis  = AVCodecID 86021
avCodecIdDvaudio  :: AVCodecID
avCodecIdDvaudio :: AVCodecID
avCodecIdDvaudio  = AVCodecID 86022
avCodecIdWmav1  :: AVCodecID
avCodecIdWmav1 :: AVCodecID
avCodecIdWmav1  = AVCodecID 86023
avCodecIdWmav2  :: AVCodecID
avCodecIdWmav2 :: AVCodecID
avCodecIdWmav2  = AVCodecID 86024
avCodecIdMace3  :: AVCodecID
avCodecIdMace3 :: AVCodecID
avCodecIdMace3  = AVCodecID 86025
avCodecIdMace6  :: AVCodecID
avCodecIdMace6 :: AVCodecID
avCodecIdMace6  = CInt -> AVCodecID
AVCodecID 86026
avCodecIdVmdaudio  :: AVCodecID
avCodecIdVmdaudio :: AVCodecID
avCodecIdVmdaudio  = AVCodecID 86027
avCodecIdFlac  :: AVCodecID
avCodecIdFlac :: AVCodecID
avCodecIdFlac  = CInt -> AVCodecID
AVCodecID 86028
avCodecIdMp3adu  :: AVCodecID
avCodecIdMp3adu :: AVCodecID
avCodecIdMp3adu  = AVCodecID 86029
avCodecIdMp3on4  :: AVCodecID
avCodecIdMp3on4 :: AVCodecID
avCodecIdMp3on4  = CInt -> AVCodecID
AVCodecID 86030
avCodecIdShorten  :: AVCodecID
avCodecIdShorten :: AVCodecID
avCodecIdShorten  = AVCodecID 86031
avCodecIdAlac  :: AVCodecID
avCodecIdAlac :: AVCodecID
avCodecIdAlac  = AVCodecID 86032
avCodecIdWestwoodSnd1  :: AVCodecID
avCodecIdWestwoodSnd1 :: AVCodecID
avCodecIdWestwoodSnd1  = AVCodecID 86033
avCodecIdGsm  :: AVCodecID
avCodecIdGsm :: AVCodecID
avCodecIdGsm  = AVCodecID 86034
avCodecIdQdm2  :: AVCodecID
avCodecIdQdm2 :: AVCodecID
avCodecIdQdm2  = AVCodecID 86035
avCodecIdCook  :: AVCodecID
avCodecIdCook :: AVCodecID
avCodecIdCook  = CInt -> AVCodecID
AVCodecID 86036
avCodecIdTruespeech  :: AVCodecID
avCodecIdTruespeech :: AVCodecID
avCodecIdTruespeech  = AVCodecID 86037
avCodecIdTta  :: AVCodecID
avCodecIdTta :: AVCodecID
avCodecIdTta  = CInt -> AVCodecID
AVCodecID 86038
avCodecIdSmackaudio  :: AVCodecID
avCodecIdSmackaudio :: AVCodecID
avCodecIdSmackaudio  = AVCodecID 86039
avCodecIdQcelp  :: AVCodecID
avCodecIdQcelp :: AVCodecID
avCodecIdQcelp  = CInt -> AVCodecID
AVCodecID 86040
avCodecIdWavpack  :: AVCodecID
avCodecIdWavpack :: AVCodecID
avCodecIdWavpack  = CInt -> AVCodecID
AVCodecID 86041
avCodecIdDsicinaudio  :: AVCodecID
avCodecIdDsicinaudio :: AVCodecID
avCodecIdDsicinaudio  = CInt -> AVCodecID
AVCodecID 86042
avCodecIdImc  :: AVCodecID
avCodecIdImc :: AVCodecID
avCodecIdImc  = CInt -> AVCodecID
AVCodecID 86043
avCodecIdMusepack7  :: AVCodecID
avCodecIdMusepack7 :: AVCodecID
avCodecIdMusepack7  = CInt -> AVCodecID
AVCodecID 86044
avCodecIdMlp  :: AVCodecID
avCodecIdMlp :: AVCodecID
avCodecIdMlp  = CInt -> AVCodecID
AVCodecID 86045
avCodecIdGsmMs  :: AVCodecID
avCodecIdGsmMs :: AVCodecID
avCodecIdGsmMs  = CInt -> AVCodecID
AVCodecID 86046
avCodecIdAtrac3  :: AVCodecID
avCodecIdAtrac3 :: AVCodecID
avCodecIdAtrac3  = CInt -> AVCodecID
AVCodecID 86047
avCodecIdApe  :: AVCodecID
avCodecIdApe :: AVCodecID
avCodecIdApe  = AVCodecID 86049
avCodecIdNellymoser  :: AVCodecID
avCodecIdNellymoser :: AVCodecID
avCodecIdNellymoser  = CInt -> AVCodecID
AVCodecID 86050
avCodecIdMusepack8  :: AVCodecID
avCodecIdMusepack8 :: AVCodecID
avCodecIdMusepack8  = AVCodecID 86051
avCodecIdSpeex  :: AVCodecID
avCodecIdSpeex :: AVCodecID
avCodecIdSpeex  = AVCodecID 86052
avfmtNotimestamps :: FormatFlag
avCodecIdWmavoice  :: AVCodecID
avCodecIdWmavoice :: AVCodecID
avCodecIdWmavoice  = AVCodecID 86053
avCodecIdWmapro  :: AVCodecID
avCodecIdWmapro :: AVCodecID
avCodecIdWmapro  = AVCodecID 86054
avCodecIdWmalossless  :: AVCodecID
avCodecIdWmalossless :: AVCodecID
avCodecIdWmalossless  = CInt -> AVCodecID
AVCodecID 86055
avCodecIdAtrac3p  :: AVCodecID
avCodecIdAtrac3p :: AVCodecID
avCodecIdAtrac3p  = AVCodecID 86056
avCodecIdEac3  :: AVCodecID
avCodecIdEac3 :: AVCodecID
avCodecIdEac3  = AVCodecID 86057
avCodecIdSipr  :: AVCodecID
avCodecIdSipr :: AVCodecID
avCodecIdSipr  = AVCodecID 86058
avPktFlagKey :: PacketFlag
avCodecIdMp1  :: AVCodecID
avCodecIdMp1 :: AVCodecID
avCodecIdMp1  = AVCodecID 86059
avfmtAllowFlush :: FormatFlag
avCodecIdTwinvq  :: AVCodecID
avCodecIdTwinvq :: AVCodecID
avCodecIdTwinvq  = AVCodecID 86060
avCodecIdTruehd  :: AVCodecID
avCodecIdTruehd :: AVCodecID
avCodecIdTruehd  = AVCodecID 86061
avfmtTsNegative :: FormatFlag
avCodecIdMp4als  :: AVCodecID
avCodecIdMp4als :: AVCodecID
avCodecIdMp4als  = AVCodecID 86062
avCodecIdAtrac1  :: AVCodecID
avCodecIdAtrac1 :: AVCodecID
avCodecIdAtrac1  = CInt -> AVCodecID
AVCodecID 86063
avCodecIdBinkaudioRdft  :: AVCodecID
avCodecIdBinkaudioRdft :: AVCodecID
avCodecIdBinkaudioRdft  = CInt -> AVCodecID
AVCodecID 86064
avCodecIdBinkaudioDct  :: AVCodecID
avCodecIdBinkaudioDct :: AVCodecID
avCodecIdBinkaudioDct  = CInt -> AVCodecID
AVCodecID 86065
avCodecIdAacLatm  :: AVCodecID
avCodecIdAacLatm :: AVCodecID
avCodecIdAacLatm  = CInt -> AVCodecID
AVCodecID 86066
avCodecIdQdmc  :: AVCodecID
avCodecIdQdmc :: AVCodecID
avCodecIdQdmc  = AVCodecID 86067
avCodecIdCelt  :: AVCodecID
avCodecIdCelt :: AVCodecID
avCodecIdCelt  = CInt -> AVCodecID
AVCodecID 86068
avCodecIdG7231  :: AVCodecID
avCodecIdG7231 :: AVCodecID
avCodecIdG7231  = CInt -> AVCodecID
AVCodecID 86069
avCodecIdG729  :: AVCodecID
avCodecIdG729 :: AVCodecID
avCodecIdG729  = AVCodecID 86070
avCodecId8svxExp  :: AVCodecID
avCodecId8svxExp :: AVCodecID
avCodecId8svxExp  = AVCodecID 86071
avCodecId8svxFib  :: AVCodecID
avCodecId8svxFib :: AVCodecID
avCodecId8svxFib  = AVCodecID 86072
avCodecIdBmvAudio  :: AVCodecID
avCodecIdBmvAudio :: AVCodecID
avCodecIdBmvAudio  = AVCodecID 86073
avCodecIdRalf  :: AVCodecID
avCodecIdRalf :: AVCodecID
avCodecIdRalf  = AVCodecID 86074
avCodecIdIac  :: AVCodecID
avCodecIdIac :: AVCodecID
avCodecIdIac  = AVCodecID 86075
avCodecIdIlbc  :: AVCodecID
avCodecIdIlbc :: AVCodecID
avCodecIdIlbc  = CInt -> AVCodecID
AVCodecID 86076
avCodecIdOpus  :: AVCodecID
avCodecIdOpus :: AVCodecID
avCodecIdOpus  = CInt -> AVCodecID
AVCodecID 86077
avCodecIdComfortNoise  :: AVCodecID
avCodecIdComfortNoise :: AVCodecID
avCodecIdComfortNoise  = CInt -> AVCodecID
AVCodecID 86078
avCodecIdTak  :: AVCodecID
avCodecIdTak :: AVCodecID
avCodecIdTak  = CInt -> AVCodecID
AVCodecID 86079
avCodecIdMetasound  :: AVCodecID
avCodecIdMetasound :: AVCodecID
avCodecIdMetasound  = CInt -> AVCodecID
AVCodecID 86080
avCodecIdPafAudio  :: AVCodecID
avCodecIdPafAudio :: AVCodecID
avCodecIdPafAudio  = CInt -> AVCodecID
AVCodecID 86081
avCodecIdOn2avc  :: AVCodecID
avCodecIdOn2avc :: AVCodecID
avCodecIdOn2avc  = CInt -> AVCodecID
AVCodecID 86082
avCodecIdDssSp  :: AVCodecID
avCodecIdDssSp :: AVCodecID
avCodecIdDssSp  = CInt -> AVCodecID
AVCodecID 86083
avCodecIdFfwavesynth  :: AVCodecID
avCodecIdFfwavesynth :: AVCodecID
avCodecIdFfwavesynth  = CInt -> AVCodecID
AVCodecID 88064
avCodecIdSonic  :: AVCodecID
avCodecIdSonic :: AVCodecID
avCodecIdSonic  = CInt -> AVCodecID
AVCodecID 88065
avCodecIdSonicLs  :: AVCodecID
avCodecIdSonicLs :: AVCodecID
avCodecIdSonicLs  = CInt -> AVCodecID
AVCodecID 88066
avCodecIdEvrc  :: AVCodecID
avCodecIdEvrc :: AVCodecID
avCodecIdEvrc  = CInt -> AVCodecID
AVCodecID 88067
avCodecIdSmv  :: AVCodecID
avCodecIdSmv :: AVCodecID
avCodecIdSmv  = CInt -> AVCodecID
AVCodecID 88068
avCodecIdDsdLsbf  :: AVCodecID
avCodecIdDsdLsbf :: AVCodecID
avCodecIdDsdLsbf  = CInt -> AVCodecID
AVCodecID 88069
avCodecIdDsdMsbf  :: AVCodecID
avCodecIdDsdMsbf :: AVCodecID
avCodecIdDsdMsbf  = CInt -> AVCodecID
AVCodecID 88070
avCodecIdDsdLsbfPlanar  :: AVCodecID
avCodecIdDsdLsbfPlanar :: AVCodecID
avCodecIdDsdLsbfPlanar  = CInt -> AVCodecID
AVCodecID 88071
avCodecIdDsdMsbfPlanar  :: AVCodecID
avCodecIdDsdMsbfPlanar :: AVCodecID
avCodecIdDsdMsbfPlanar  = CInt -> AVCodecID
AVCodecID 88072
avCodecId4gv :: AVCodecID
avCodecId4gv :: AVCodecID
avCodecId4gv = CInt -> AVCodecID
AVCodecID 88073

{-# LINE 323 "src/Codec/FFmpeg/Enums.hsc" #-}


 -- \
 -- , AV_CODEC_ID_INTERPLAY_ACM\
 -- , AV_CODEC_ID_XMA1\
 -- , AV_CODEC_ID_XMA2\
 -- , AV_CODEC_ID_DST


newtype SwsAlgorithm = SwsAlgorithm CUInt deriving (Eq, Show, Storable)
swsFastBilinear  :: SwsAlgorithm
swsFastBilinear  = SwsAlgorithm 1
swsBilinear  :: SwsAlgorithm
swsBilinear  = SwsAlgorithm 2
swsBicubic  :: SwsAlgorithm
swsBicubic  = SwsAlgorithm 4
swsX  :: SwsAlgorithm
swsX  = SwsAlgorithm 8
swsPoint  :: SwsAlgorithm
swsPoint  = SwsAlgorithm 16
swsArea  :: SwsAlgorithm
swsArea  = SwsAlgorithm 32
swsBicublin  :: SwsAlgorithm
swsBicublin  = SwsAlgorithm 64
swsGauss  :: SwsAlgorithm
swsGauss  = SwsAlgorithm 128
swsSinc  :: SwsAlgorithm
swsSinc  = SwsAlgorithm 256
swsLanczos  :: SwsAlgorithm
swsLanczos  = SwsAlgorithm 512
swsSpline :: SwsAlgorithm
swsSpline = SwsAlgorithm 1024

{-# LINE 345 "src/Codec/FFmpeg/Enums.hsc" #-}

newtype FFProfile = FFProfile CInt deriving (Eq, Storable)
ffProfileAacMain  :: FFProfile
ffProfileAacMain  = FFProfile 0
ffProfileAacLow  :: FFProfile
ffProfileAacLow  = FFProfile 1
ffProfileAacSsr  :: FFProfile
ffProfileAacSsr  = FFProfile 2
ffProfileAacLtp  :: FFProfile
ffProfileAacLtp  = FFProfile 3
ffProfileAacHe  :: FFProfile
ffProfileAacHe  = FFProfile 4
ffProfileAacHeV2  :: FFProfile
ffProfileAacHeV2  = FFProfile 28
ffProfileAacLd  :: FFProfile
ffProfileAacLd  = FFProfile 22
ffProfileAacEld  :: FFProfile
ffProfileAacEld  = FFProfile 38
ffProfileMpeg2AacLow  :: FFProfile
ffProfileMpeg2AacLow  = FFProfile 128
ffProfileMpeg2AacHe  :: FFProfile
ffProfileMpeg2AacHe  = FFProfile 131
ffProfileDts  :: FFProfile
ffProfileDts  = FFProfile 20
ffProfileDtsEs  :: FFProfile
ffProfileDtsEs  = FFProfile 30
ffProfileDts9624  :: FFProfile
ffProfileDts9624  = FFProfile 40
ffProfileDtsHdHra  :: FFProfile
ffProfileDtsHdHra  = FFProfile 50
ffProfileDtsHdMa  :: FFProfile
ffProfileDtsHdMa  = FFProfile 60
ffProfileMpeg2422  :: FFProfile
ffProfileMpeg2422  = FFProfile 0
ffProfileMpeg2High  :: FFProfile
ffProfileMpeg2High  = FFProfile 1
ffProfileMpeg2Ss  :: FFProfile
ffProfileMpeg2Ss  = FFProfile 2
ffProfileMpeg2SnrScalable  :: FFProfile
ffProfileMpeg2SnrScalable  = FFProfile 3
ffProfileMpeg2Main  :: FFProfile
ffProfileMpeg2Main  = FFProfile 4
ffProfileMpeg2Simple  :: FFProfile
ffProfileMpeg2Simple  = FFProfile 5
ffProfileH264Constrained  :: FFProfile
ffProfileH264Constrained  = FFProfile 512
ffProfileH264Intra  :: FFProfile
ffProfileH264Intra  = FFProfile 2048
ffProfileH264Baseline  :: FFProfile
ffProfileH264Baseline  = FFProfile 66
ffProfileH264ConstrainedBaseline  :: FFProfile
ffProfileH264ConstrainedBaseline  = FFProfile 578
ffProfileH264Main  :: FFProfile
ffProfileH264Main  = FFProfile 77
ffProfileH264Extended  :: FFProfile
ffProfileH264Extended  = FFProfile 88
ffProfileH264High  :: FFProfile
ffProfileH264High  = FFProfile 100
ffProfileH264High10  :: FFProfile
ffProfileH264High10  = FFProfile 110
ffProfileH264High10Intra  :: FFProfile
ffProfileH264High10Intra  = FFProfile 2158
ffProfileH264High422  :: FFProfile
ffProfileH264High422  = FFProfile 122
ffProfileH264High422Intra  :: FFProfile
ffProfileH264High422Intra  = FFProfile 2170
ffProfileH264High444  :: FFProfile
ffProfileH264High444  = FFProfile 144
ffProfileH264High444Predictive  :: FFProfile
ffProfileH264High444Predictive  = FFProfile 244
ffProfileH264High444Intra  :: FFProfile
ffProfileH264High444Intra  = FFProfile 2292
ffProfileH264Cavlc444  :: FFProfile
ffProfileH264Cavlc444  = FFProfile 44
ffProfileVc1Simple  :: FFProfile
ffProfileVc1Simple  = FFProfile 0
ffProfileVc1Main  :: FFProfile
ffProfileVc1Main  = FFProfile 1
ffProfileVc1Complex  :: FFProfile
ffProfileVc1Complex  = FFProfile 2
ffProfileVc1Advanced  :: FFProfile
ffProfileVc1Advanced  = FFProfile 3
ffProfileMpeg4Simple  :: FFProfile
ffProfileMpeg4Simple  = FFProfile 0
ffProfileMpeg4SimpleScalable  :: FFProfile
ffProfileMpeg4SimpleScalable  = FFProfile 1
ffProfileMpeg4Core  :: FFProfile
ffProfileMpeg4Core  = FFProfile 2
ffProfileMpeg4Main  :: FFProfile
ffProfileMpeg4Main  = FFProfile 3
ffProfileMpeg4NBit  :: FFProfile
ffProfileMpeg4NBit  = FFProfile 4
ffProfileMpeg4ScalableTexture  :: FFProfile
ffProfileMpeg4ScalableTexture  = FFProfile 5
ffProfileMpeg4SimpleFaceAnimation  :: FFProfile
ffProfileMpeg4SimpleFaceAnimation  = FFProfile 6
ffProfileMpeg4BasicAnimatedTexture  :: FFProfile
ffProfileMpeg4BasicAnimatedTexture  = FFProfile 7
ffProfileMpeg4Hybrid  :: FFProfile
ffProfileMpeg4Hybrid  = FFProfile 8
ffProfileMpeg4AdvancedRealTime  :: FFProfile
ffProfileMpeg4AdvancedRealTime  = FFProfile 9
ffProfileMpeg4CoreScalable  :: FFProfile
ffProfileMpeg4CoreScalable  = FFProfile 10
ffProfileMpeg4AdvancedCoding  :: FFProfile
ffProfileMpeg4AdvancedCoding  = FFProfile 11
ffProfileMpeg4AdvancedCore  :: FFProfile
ffProfileMpeg4AdvancedCore  = FFProfile 12
ffProfileMpeg4AdvancedScalableTexture  :: FFProfile
ffProfileMpeg4AdvancedScalableTexture  = FFProfile 13
ffProfileMpeg4SimpleStudio  :: FFProfile
ffProfileMpeg4SimpleStudio  = FFProfile 14
ffProfileMpeg4AdvancedSimple :: FFProfile
ffProfileMpeg4AdvancedSimple = FFProfile 15

{-# LINE 404 "src/Codec/FFmpeg/Enums.hsc" #-}

newtype AVIOFlag = AVIOFlag CInt deriving (Eq, Storable)
avioFlagRead  :: AVIOFlag
avioFlagRead  = AVIOFlag 1
avioFlagWrite  :: AVIOFlag
avioFlagWrite  = AVIOFlag 2
avioFlagReadWrite  :: AVIOFlag
avioFlagReadWrite  = AVIOFlag 3
avioFlagNonblock  :: AVIOFlag
avioFlagNonblock  = AVIOFlag 8
avioFlagDirect :: AVIOFlag
avioFlagDirect = AVIOFlag 32768

{-# LINE 412 "src/Codec/FFmpeg/Enums.hsc" #-}

newtype AVRoundMode = AVRoundMode CInt deriving (Eq, Storable)
avRoundZero  :: AVRoundMode
avRoundZero  = AVRoundMode 0
avRoundInf  :: AVRoundMode
avRoundInf  = AVRoundMode 1
avRoundDown  :: AVRoundMode
avRoundDown  = AVRoundMode 2
avRoundUp  :: AVRoundMode
avRoundUp  = AVRoundMode 3
avRoundNearInf  :: AVRoundMode
avRoundNearInf  = AVRoundMode 5
avRoundPassMinmax :: AVRoundMode
avRoundPassMinmax = AVRoundMode 8192

{-# LINE 421 "src/Codec/FFmpeg/Enums.hsc" #-}

newtype CodecFlag = CodecFlag CInt deriving (Eq, Bits, Storable)

{-# LINE 449 "src/Codec/FFmpeg/Enums.hsc" #-}
avCodecFlagUnaligned  :: CodecFlag
avCodecFlagUnaligned  = CodecFlag 1
avCodecFlagQscale  :: CodecFlag
avCodecFlagQscale  = CodecFlag 2
avCodecFlag4mv  :: CodecFlag
avCodecFlag4mv  = CodecFlag 4
avCodecFlagOutputCorrupt  :: CodecFlag
avCodecFlagOutputCorrupt  = CodecFlag 8
avCodecFlagQpel  :: CodecFlag
avCodecFlagQpel  = CodecFlag 16
avCodecFlagPass1  :: CodecFlag
avCodecFlagPass1  = CodecFlag 512
avCodecFlagPass2  :: CodecFlag
avCodecFlagPass2  = CodecFlag 1024
avCodecFlagLoopFilter  :: CodecFlag
avCodecFlagLoopFilter  = CodecFlag 2048
avCodecFlagGray  :: CodecFlag
avCodecFlagGray  = CodecFlag 8192
avCodecFlagPsnr  :: CodecFlag
avCodecFlagPsnr  = CodecFlag 32768
avCodecFlagTruncated  :: CodecFlag
avCodecFlagTruncated  = CodecFlag 65536
avCodecFlagInterlacedDct  :: CodecFlag
avCodecFlagInterlacedDct  = CodecFlag 262144
avCodecFlagLowDelay  :: CodecFlag
avCodecFlagLowDelay  = CodecFlag 524288
avCodecFlagGlobalHeader  :: CodecFlag
avCodecFlagGlobalHeader  = CodecFlag 4194304
avCodecFlagBitexact  :: CodecFlag
avCodecFlagBitexact  = CodecFlag 8388608
avCodecFlagAcPred  :: CodecFlag
avCodecFlagAcPred  = CodecFlag 16777216
avCodecFlagInterlacedMe  :: CodecFlag
avCodecFlagInterlacedMe  = CodecFlag 536870912
avCodecFlagClosedGop :: CodecFlag
avCodecFlagClosedGop = CodecFlag 2147483648

{-# LINE 468 "src/Codec/FFmpeg/Enums.hsc" #-}

{-# LINE 469 "src/Codec/FFmpeg/Enums.hsc" #-}

newtype FormatFlag = FormatFlag CInt deriving (Eq, Bits, Storable)

{-# LINE 484 "src/Codec/FFmpeg/Enums.hsc" #-}
avfmtNofile  :: FormatFlag
avfmtNofile  = FormatFlag 1
avfmtNeednumber  :: FormatFlag
avfmtNeednumber  = FormatFlag 2
avfmtGlobalheader  :: FormatFlag
avfmtGlobalheader  = FormatFlag 64
avfmtNotimestamps  :: FormatFlag
avfmtNotimestamps  = FormatFlag 128
avfmtVariableFps  :: FormatFlag
avfmtVariableFps  = FormatFlag 1024
avfmtNodimensions  :: FormatFlag
avfmtNodimensions  = FormatFlag 2048
avfmtNostreams  :: FormatFlag
avfmtNostreams  = FormatFlag 4096
avfmtNobinsearch  :: FormatFlag
avfmtNobinsearch  = FormatFlag 8192
avfmtNogensearch  :: FormatFlag
avfmtNogensearch  = FormatFlag 16384
avfmtNoByteSeek  :: FormatFlag
avfmtNoByteSeek  = FormatFlag 32768
avfmtAllowFlush  :: FormatFlag
avfmtAllowFlush  = FormatFlag 65536
avfmtTsNonstrict  :: FormatFlag
avfmtTsNonstrict  = FormatFlag 131072
avfmtTsNegative  :: FormatFlag
avfmtTsNegative  = FormatFlag 262144
avfmtSeekToPts :: FormatFlag
avfmtSeekToPts = FormatFlag 67108864

{-# LINE 499 "src/Codec/FFmpeg/Enums.hsc" #-}

{-# LINE 500 "src/Codec/FFmpeg/Enums.hsc" #-}

newtype PacketFlag = PacketFlag CInt deriving (Eq, Bits, Storable)
avPktFlagKey  :: PacketFlag
avPktFlagKey  = PacketFlag 1
avPktFlagCorrupt :: PacketFlag
avPktFlagCorrupt = PacketFlag 2

{-# LINE 505 "src/Codec/FFmpeg/Enums.hsc" #-}

newtype LogLevel = LogLevel CInt deriving (Eq, Bits, Storable)
avLogQuiet  :: LogLevel
avLogQuiet  = LogLevel (-8)
avLogPanic  :: LogLevel
avLogPanic  = LogLevel 0
avLogFatal  :: LogLevel
avLogFatal  = LogLevel 8
avLogError  :: LogLevel
avLogError  = LogLevel 16
avLogWarning  :: LogLevel
avLogWarning  = LogLevel 24
avLogInfo  :: LogLevel
avLogInfo  = LogLevel 32
avLogVerbose  :: LogLevel
avLogVerbose  = LogLevel 40
avLogDebug  :: LogLevel
avLogDebug  = LogLevel 48
avLogTrace  :: LogLevel
avLogTrace  = LogLevel 56
avLogMaxOffset :: LogLevel
avLogMaxOffset = LogLevel 64

{-# LINE 518 "src/Codec/FFmpeg/Enums.hsc" #-}

newtype AVSampleFormat = AVSampleFormat CInt deriving (Eq, Bits, Storable)
avSampleFmtNone  :: AVSampleFormat
avSampleFmtNone  = AVSampleFormat (-1)
avSampleFmtU8  :: AVSampleFormat
avSampleFmtU8  = AVSampleFormat 0
avSampleFmtS16  :: AVSampleFormat
avSampleFmtS16  = AVSampleFormat 1
avSampleFmtS32  :: AVSampleFormat
avSampleFmtS32  = AVSampleFormat 2
avSampleFmtFlt  :: AVSampleFormat
avSampleFmtFlt  = AVSampleFormat 3
avSampleFmtDbl  :: AVSampleFormat
avSampleFmtDbl  = AVSampleFormat 4
avSampleFmtU8p  :: AVSampleFormat
avSampleFmtU8p  = AVSampleFormat 5
avSampleFmtS16p  :: AVSampleFormat
avSampleFmtS16p  = AVSampleFormat 6
avSampleFmtS32p  :: AVSampleFormat
avSampleFmtS32p  = AVSampleFormat 7
avSampleFmtFltp  :: AVSampleFormat
avSampleFmtFltp  = AVSampleFormat 8
avSampleFmtDblp  :: AVSampleFormat
avSampleFmtDblp  = AVSampleFormat 9
avSampleFmtNb :: AVSampleFormat
avSampleFmtNb = AVSampleFormat 12

{-# LINE 533 "src/Codec/FFmpeg/Enums.hsc" #-}

getSampleFormatInt :: AVSampleFormat -> CInt
getSampleFormatInt (AVSampleFormat i) = i