module FFProbe.Data.Stream (
    Stream (..),
    StreamType (..),
    isVideoStream,
    isAudioStream,
    isSubtitleStream,
    isStreamOfType,
    StreamDisposition (..),
) where
import Control.Applicative ((<|>))
import Data.Aeson
import Data.Aeson.Types (Parser)
import Data.Text hiding (index)
import FFProbe.Data.Tags (HasTags (..), TagList)
import FFProbe.Data.Tags.Internal
import FFProbe.Internal
import Prelude hiding (id)
data StreamType
    = VideoStream
    | AudioStream
    | SubtitleStream
    | DataStream
    | Attachment
    | Other String
    deriving (StreamType -> StreamType -> Bool
(StreamType -> StreamType -> Bool)
-> (StreamType -> StreamType -> Bool) -> Eq StreamType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: StreamType -> StreamType -> Bool
== :: StreamType -> StreamType -> Bool
$c/= :: StreamType -> StreamType -> Bool
/= :: StreamType -> StreamType -> Bool
Eq, Int -> StreamType -> ShowS
[StreamType] -> ShowS
StreamType -> String
(Int -> StreamType -> ShowS)
-> (StreamType -> String)
-> ([StreamType] -> ShowS)
-> Show StreamType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> StreamType -> ShowS
showsPrec :: Int -> StreamType -> ShowS
$cshow :: StreamType -> String
show :: StreamType -> String
$cshowList :: [StreamType] -> ShowS
showList :: [StreamType] -> ShowS
Show)
instance FromJSON StreamType where
    parseJSON :: Value -> Parser StreamType
parseJSON (String Text
"video") = StreamType -> Parser StreamType
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return StreamType
VideoStream
    parseJSON (String Text
"audio") = StreamType -> Parser StreamType
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return StreamType
AudioStream
    parseJSON (String Text
"subtitle") = StreamType -> Parser StreamType
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return StreamType
SubtitleStream
    parseJSON (String Text
"data") = StreamType -> Parser StreamType
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return StreamType
DataStream
    parseJSON (String Text
"attachment") = StreamType -> Parser StreamType
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return StreamType
Attachment
    parseJSON (String Text
s) = StreamType -> Parser StreamType
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (StreamType -> Parser StreamType)
-> StreamType -> Parser StreamType
forall a b. (a -> b) -> a -> b
$ String -> StreamType
Other (Text -> String
unpack Text
s)
    parseJSON Value
x = StreamType -> Parser StreamType
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (StreamType -> Parser StreamType)
-> StreamType -> Parser StreamType
forall a b. (a -> b) -> a -> b
$ String -> StreamType
Other (Value -> String
forall a. Show a => a -> String
show Value
x)
data StreamDisposition = StreamDisposition
    { StreamDisposition -> Bool
isDefault :: Bool,
      StreamDisposition -> Bool
isDub :: Bool,
      StreamDisposition -> Bool
isOriginal :: Bool,
       :: Bool,
      StreamDisposition -> Bool
isLyrics :: Bool,
      StreamDisposition -> Bool
isKaraoke :: Bool,
      StreamDisposition -> Bool
isForced :: Bool,
      StreamDisposition -> Bool
isHearingImpaired :: Bool,
      StreamDisposition -> Bool
isVisualImpaired :: Bool,
      StreamDisposition -> Bool
isCleanEffects :: Bool,
      StreamDisposition -> Bool
isAttachedPic :: Bool,
      StreamDisposition -> Bool
isTimedThumbnails :: Bool,
      StreamDisposition -> Bool
isNonDiegetic :: Bool,
      StreamDisposition -> Bool
isCaptions :: Bool,
      StreamDisposition -> Bool
isDescriptions :: Bool,
      StreamDisposition -> Bool
isMetadata :: Bool,
      StreamDisposition -> Bool
isDependent :: Bool,
      StreamDisposition -> Bool
isStillImage :: Bool
    }
isVideoStream :: Stream -> Bool
isVideoStream :: Stream -> Bool
isVideoStream = StreamType -> Stream -> Bool
isStreamOfType StreamType
VideoStream
isAudioStream :: Stream -> Bool
isAudioStream :: Stream -> Bool
isAudioStream = StreamType -> Stream -> Bool
isStreamOfType StreamType
AudioStream
isSubtitleStream :: Stream -> Bool
isSubtitleStream :: Stream -> Bool
isSubtitleStream = StreamType -> Stream -> Bool
isStreamOfType StreamType
SubtitleStream
isStreamOfType :: StreamType -> Stream -> Bool
isStreamOfType :: StreamType -> Stream -> Bool
isStreamOfType StreamType
stype Stream
stream = StreamType
stype StreamType -> StreamType -> Bool
forall a. Eq a => a -> a -> Bool
== Stream -> StreamType
streamType Stream
stream
instance FromJSON StreamDisposition where
    parseJSON :: Value -> Parser StreamDisposition
parseJSON = String
-> (Object -> Parser StreamDisposition)
-> Value
-> Parser StreamDisposition
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Disposition" ((Object -> Parser StreamDisposition)
 -> Value -> Parser StreamDisposition)
-> (Object -> Parser StreamDisposition)
-> Value
-> Parser StreamDisposition
forall a b. (a -> b) -> a -> b
$ \Object
v -> do
        let getValue :: Key -> Parser Bool
getValue Key
key = (Int -> Parser Bool
parseDispositionValue (Int -> Parser Bool) -> Parser Int -> Parser Bool
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Object
v Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
key) Parser Bool -> Parser Bool -> Parser Bool
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Bool -> Parser Bool
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
False
        Bool
isDefault <- Key -> Parser Bool
getValue Key
"default"
        Bool
isDub <- Key -> Parser Bool
getValue Key
"dub"
        Bool
isOriginal <- Key -> Parser Bool
getValue Key
"original"
        Bool
isComment <- Key -> Parser Bool
getValue Key
"comment"
        Bool
isLyrics <- Key -> Parser Bool
getValue Key
"lyrics"
        Bool
isKaraoke <- Key -> Parser Bool
getValue Key
"karaoke"
        Bool
isForced <- Key -> Parser Bool
getValue Key
"forced"
        Bool
isHearingImpaired <- Key -> Parser Bool
getValue Key
"hearing_impaired"
        Bool
isVisualImpaired <- Key -> Parser Bool
getValue Key
"visual_impaired"
        Bool
isCleanEffects <- Key -> Parser Bool
getValue Key
"clean_effects"
        Bool
isAttachedPic <- Key -> Parser Bool
getValue Key
"attached_pic"
        Bool
isTimedThumbnails <- Key -> Parser Bool
getValue Key
"attached_pic"
        Bool
isNonDiegetic <- Key -> Parser Bool
getValue Key
"non_diegetic"
        Bool
isCaptions <- Key -> Parser Bool
getValue Key
"captions"
        Bool
isDescriptions <- Key -> Parser Bool
getValue Key
"descriptions"
        Bool
isMetadata <- Key -> Parser Bool
getValue Key
"metadata"
        Bool
isDependent <- Key -> Parser Bool
getValue Key
"dependent"
        Bool
isStillImage <- Key -> Parser Bool
getValue Key
"still_image"
        StreamDisposition -> Parser StreamDisposition
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return StreamDisposition {Bool
isDefault :: Bool
isDub :: Bool
isOriginal :: Bool
isComment :: Bool
isLyrics :: Bool
isKaraoke :: Bool
isForced :: Bool
isHearingImpaired :: Bool
isVisualImpaired :: Bool
isCleanEffects :: Bool
isAttachedPic :: Bool
isTimedThumbnails :: Bool
isNonDiegetic :: Bool
isCaptions :: Bool
isDescriptions :: Bool
isMetadata :: Bool
isDependent :: Bool
isStillImage :: Bool
isDefault :: Bool
isDub :: Bool
isOriginal :: Bool
isComment :: Bool
isLyrics :: Bool
isKaraoke :: Bool
isForced :: Bool
isHearingImpaired :: Bool
isVisualImpaired :: Bool
isCleanEffects :: Bool
isAttachedPic :: Bool
isTimedThumbnails :: Bool
isNonDiegetic :: Bool
isCaptions :: Bool
isDescriptions :: Bool
isMetadata :: Bool
isDependent :: Bool
isStillImage :: Bool
..}
        where
            parseDispositionValue :: Int -> Parser Bool
            parseDispositionValue :: Int -> Parser Bool
parseDispositionValue Int
0 = Bool -> Parser Bool
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
            parseDispositionValue Int
1 = Bool -> Parser Bool
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
            parseDispositionValue Int
n = String -> Parser Bool
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser Bool) -> String -> Parser Bool
forall a b. (a -> b) -> a -> b
$ String
"Expected 0 or 1. Got " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
n
data Stream = Stream
    { Stream -> Integer
index :: Integer,
      Stream -> String
codecName :: String,
      Stream -> String
codecLongName :: String,
      Stream -> String
codecType :: String,
      Stream -> StreamType
streamType :: StreamType,
      Stream -> String
codecTagString :: String,
      
      Stream -> String
codecTag :: String,
      Stream -> String
rFrameRate :: String,
      Stream -> String
averageFrameRate :: String,
      Stream -> String
timeBase :: String,
      Stream -> Integer
startPts :: Integer,
      Stream -> Float
startTime :: Float,
      
      Stream -> Maybe Float
duration :: Maybe Float,
      Stream -> Maybe Integer
bitRate :: Maybe Integer,
      Stream -> Maybe Integer
bitsPerRawSample :: Maybe Integer,
      Stream -> Maybe Integer
bitsPerSample :: Maybe Integer,
      Stream -> Maybe Integer
framesCount :: Maybe Integer,
      Stream -> TagList
tags :: TagList,
      Stream -> StreamDisposition
disposition :: StreamDisposition,
      Stream -> Maybe String
fieldOrder :: Maybe String,
      Stream -> Maybe String
profile :: Maybe String,
      Stream -> Maybe Integer
width :: Maybe Integer,
      Stream -> Maybe Integer
height :: Maybe Integer,
      Stream -> Maybe Integer
hasBFrames :: Maybe Integer,
      
      Stream -> Maybe String
sampleAspectRatio :: Maybe String,
      Stream -> Maybe String
displayAspectRatio :: Maybe String,
      Stream -> Maybe String
pixFmt :: Maybe String,
      Stream -> Maybe Integer
level :: Maybe Integer,
      Stream -> Maybe String
colorRange :: Maybe String,
      Stream -> Maybe String
colorSpace :: Maybe String,
      Stream -> Maybe String
sampleFmt :: Maybe String,
      Stream -> Maybe Integer
sampleRate :: Maybe Integer,
      Stream -> Maybe Integer
channels :: Maybe Integer,
      Stream -> Maybe String
channelLayout :: Maybe String,
      
      Stream -> Object
raw :: Object
    }
instance HasTags Stream where
    getTags :: Stream -> TagList
getTags = Stream -> TagList
tags
instance FromJSON Stream where
    parseJSON :: Value -> Parser Stream
parseJSON = String -> (Object -> Parser Stream) -> Value -> Parser Stream
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Stream" ((Object -> Parser Stream) -> Value -> Parser Stream)
-> (Object -> Parser Stream) -> Value -> Parser Stream
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
        let raw :: Object
raw = Object
o
        Integer
index <- Object
o Object -> Key -> Parser Integer
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"index"
        String
codecName <- Object
o Object -> Key -> Parser String
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"codec_name"
        String
codecLongName <- Object
o Object -> Key -> Parser String
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"codec_long_name"
        String
codecType <- Object
o Object -> Key -> Parser String
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"codec_type"
        StreamType
streamType <- Value -> Parser StreamType
forall a. FromJSON a => Value -> Parser a
parseJSON (Text -> Value
String (Text -> Value) -> Text -> Value
forall a b. (a -> b) -> a -> b
$ String -> Text
pack String
codecType)
        String
codecTagString <- Object
o Object -> Key -> Parser String
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"codec_tag_string"
        String
codecTag <- Object
o Object -> Key -> Parser String
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"codec_tag"
        String
rFrameRate <- Object
o Object -> Key -> Parser String
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"r_frame_rate"
        String
averageFrameRate <- Object
o Object -> Key -> Parser String
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"avg_frame_rate"
        String
timeBase <- Object
o Object -> Key -> Parser String
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"time_base"
        Integer
startPts <- Object
o Object -> Key -> Parser Integer
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"start_pts"
        Float
startTime <- String -> Parser Float
forall a. Read a => String -> Parser a
parseReadable (String -> Parser Float) -> Parser String -> Parser Float
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Object
o Object -> Key -> Parser String
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"start_time"
        Maybe Float
duration <- Maybe String -> Parser (Maybe Float)
forall a. Read a => Maybe String -> Parser (Maybe a)
parseOptionalValue (Maybe String -> Parser (Maybe Float))
-> Parser (Maybe String) -> Parser (Maybe Float)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Object
o Object -> Key -> Parser (Maybe String)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"duration"
        Maybe Integer
bitRate <- Maybe String -> Parser (Maybe Integer)
forall a. Read a => Maybe String -> Parser (Maybe a)
parseOptionalValue (Maybe String -> Parser (Maybe Integer))
-> Parser (Maybe String) -> Parser (Maybe Integer)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Object
o Object -> Key -> Parser (Maybe String)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"bit_rate"
        Maybe Integer
bitsPerRawSample <- Maybe String -> Parser (Maybe Integer)
forall a. Read a => Maybe String -> Parser (Maybe a)
parseOptionalValue (Maybe String -> Parser (Maybe Integer))
-> Parser (Maybe String) -> Parser (Maybe Integer)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Object
o Object -> Key -> Parser (Maybe String)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"bits_per_raw_sample"
        Maybe Integer
bitsPerSample <- Object
o Object -> Key -> Parser (Maybe Integer)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"bits_per_sample"
        Maybe Integer
framesCount <- Maybe String -> Parser (Maybe Integer)
forall a. Read a => Maybe String -> Parser (Maybe a)
parseOptionalValue (Maybe String -> Parser (Maybe Integer))
-> Parser (Maybe String) -> Parser (Maybe Integer)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Object
o Object -> Key -> Parser (Maybe String)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"nb_frames"
        TagList
tags <- Value -> Parser TagList
parseTags (Value -> Parser TagList) -> Parser Value -> Parser TagList
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Object
o Object -> Key -> Parser Value
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"tags"
        StreamDisposition
disposition <- Object
o Object -> Key -> Parser StreamDisposition
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"disposition"
        Maybe String
fieldOrder <- Object
o Object -> Key -> Parser (Maybe String)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"field_order"
        Maybe String
profile <- Object
o Object -> Key -> Parser (Maybe String)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"profile"
        Maybe Integer
width <- Object
o Object -> Key -> Parser (Maybe Integer)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"width"
        Maybe Integer
height <- Object
o Object -> Key -> Parser (Maybe Integer)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"height"
        Maybe Integer
hasBFrames <- Object
o Object -> Key -> Parser (Maybe Integer)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"has_b_frames"
        Maybe String
sampleAspectRatio <- Object
o Object -> Key -> Parser (Maybe String)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"sample_aspect_ratio"
        Maybe String
displayAspectRatio <- Object
o Object -> Key -> Parser (Maybe String)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"display_aspect_ratio"
        Maybe String
pixFmt <- Object
o Object -> Key -> Parser (Maybe String)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"pix_fmt"
        Maybe Integer
level <- Object
o Object -> Key -> Parser (Maybe Integer)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"level"
        Maybe String
colorRange <- Object
o Object -> Key -> Parser (Maybe String)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"color_range"
        Maybe String
colorSpace <- Object
o Object -> Key -> Parser (Maybe String)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"color_space"
        Maybe String
sampleFmt <- Object
o Object -> Key -> Parser (Maybe String)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"sample_fmt"
        Maybe Integer
sampleRate <- Maybe String -> Parser (Maybe Integer)
forall a. Read a => Maybe String -> Parser (Maybe a)
parseOptionalValue (Maybe String -> Parser (Maybe Integer))
-> Parser (Maybe String) -> Parser (Maybe Integer)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Object
o Object -> Key -> Parser (Maybe String)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"sample_rate"
        Maybe Integer
channels <- Object
o Object -> Key -> Parser (Maybe Integer)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"channels"
        Maybe String
channelLayout <- Object
o Object -> Key -> Parser (Maybe String)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"channel_layout"
        Stream -> Parser Stream
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return Stream {Float
Integer
String
TagList
Maybe Float
Maybe Integer
Maybe String
Object
StreamDisposition
StreamType
streamType :: StreamType
index :: Integer
codecName :: String
codecLongName :: String
codecType :: String
codecTagString :: String
codecTag :: String
rFrameRate :: String
averageFrameRate :: String
timeBase :: String
startPts :: Integer
startTime :: Float
duration :: Maybe Float
bitRate :: Maybe Integer
bitsPerRawSample :: Maybe Integer
bitsPerSample :: Maybe Integer
framesCount :: Maybe Integer
tags :: TagList
disposition :: StreamDisposition
fieldOrder :: Maybe String
profile :: Maybe String
width :: Maybe Integer
height :: Maybe Integer
hasBFrames :: Maybe Integer
sampleAspectRatio :: Maybe String
displayAspectRatio :: Maybe String
pixFmt :: Maybe String
level :: Maybe Integer
colorRange :: Maybe String
colorSpace :: Maybe String
sampleFmt :: Maybe String
sampleRate :: Maybe Integer
channels :: Maybe Integer
channelLayout :: Maybe String
raw :: Object
raw :: Object
index :: Integer
codecName :: String
codecLongName :: String
codecType :: String
streamType :: StreamType
codecTagString :: String
codecTag :: String
rFrameRate :: String
averageFrameRate :: String
timeBase :: String
startPts :: Integer
startTime :: Float
duration :: Maybe Float
bitRate :: Maybe Integer
bitsPerRawSample :: Maybe Integer
bitsPerSample :: Maybe Integer
framesCount :: Maybe Integer
tags :: TagList
disposition :: StreamDisposition
fieldOrder :: Maybe String
profile :: Maybe String
width :: Maybe Integer
height :: Maybe Integer
hasBFrames :: Maybe Integer
sampleAspectRatio :: Maybe String
displayAspectRatio :: Maybe String
pixFmt :: Maybe String
level :: Maybe Integer
colorRange :: Maybe String
colorSpace :: Maybe String
sampleFmt :: Maybe String
sampleRate :: Maybe Integer
channels :: Maybe Integer
channelLayout :: Maybe String
..}