module Mpv.Data.Track where import Data.Aeson (FromJSON (parseJSON), ToJSON (toJSON), withText) import Exon (exon) import Polysemy.Time.Json (json) data TrackType = Audio | Sub | Video deriving stock (TrackType -> TrackType -> Bool (TrackType -> TrackType -> Bool) -> (TrackType -> TrackType -> Bool) -> Eq TrackType forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: TrackType -> TrackType -> Bool $c/= :: TrackType -> TrackType -> Bool == :: TrackType -> TrackType -> Bool $c== :: TrackType -> TrackType -> Bool Eq, Int -> TrackType -> ShowS [TrackType] -> ShowS TrackType -> String (Int -> TrackType -> ShowS) -> (TrackType -> String) -> ([TrackType] -> ShowS) -> Show TrackType forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [TrackType] -> ShowS $cshowList :: [TrackType] -> ShowS show :: TrackType -> String $cshow :: TrackType -> String showsPrec :: Int -> TrackType -> ShowS $cshowsPrec :: Int -> TrackType -> ShowS Show, Int -> TrackType TrackType -> Int TrackType -> [TrackType] TrackType -> TrackType TrackType -> TrackType -> [TrackType] TrackType -> TrackType -> TrackType -> [TrackType] (TrackType -> TrackType) -> (TrackType -> TrackType) -> (Int -> TrackType) -> (TrackType -> Int) -> (TrackType -> [TrackType]) -> (TrackType -> TrackType -> [TrackType]) -> (TrackType -> TrackType -> [TrackType]) -> (TrackType -> TrackType -> TrackType -> [TrackType]) -> Enum TrackType 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 :: TrackType -> TrackType -> TrackType -> [TrackType] $cenumFromThenTo :: TrackType -> TrackType -> TrackType -> [TrackType] enumFromTo :: TrackType -> TrackType -> [TrackType] $cenumFromTo :: TrackType -> TrackType -> [TrackType] enumFromThen :: TrackType -> TrackType -> [TrackType] $cenumFromThen :: TrackType -> TrackType -> [TrackType] enumFrom :: TrackType -> [TrackType] $cenumFrom :: TrackType -> [TrackType] fromEnum :: TrackType -> Int $cfromEnum :: TrackType -> Int toEnum :: Int -> TrackType $ctoEnum :: Int -> TrackType pred :: TrackType -> TrackType $cpred :: TrackType -> TrackType succ :: TrackType -> TrackType $csucc :: TrackType -> TrackType Enum, Eq TrackType Eq TrackType -> (TrackType -> TrackType -> Ordering) -> (TrackType -> TrackType -> Bool) -> (TrackType -> TrackType -> Bool) -> (TrackType -> TrackType -> Bool) -> (TrackType -> TrackType -> Bool) -> (TrackType -> TrackType -> TrackType) -> (TrackType -> TrackType -> TrackType) -> Ord TrackType TrackType -> TrackType -> Bool TrackType -> TrackType -> Ordering TrackType -> TrackType -> TrackType 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 :: TrackType -> TrackType -> TrackType $cmin :: TrackType -> TrackType -> TrackType max :: TrackType -> TrackType -> TrackType $cmax :: TrackType -> TrackType -> TrackType >= :: TrackType -> TrackType -> Bool $c>= :: TrackType -> TrackType -> Bool > :: TrackType -> TrackType -> Bool $c> :: TrackType -> TrackType -> Bool <= :: TrackType -> TrackType -> Bool $c<= :: TrackType -> TrackType -> Bool < :: TrackType -> TrackType -> Bool $c< :: TrackType -> TrackType -> Bool compare :: TrackType -> TrackType -> Ordering $ccompare :: TrackType -> TrackType -> Ordering Ord) instance FromJSON TrackType where parseJSON :: Value -> Parser TrackType parseJSON = String -> (Text -> Parser TrackType) -> Value -> Parser TrackType forall a. String -> (Text -> Parser a) -> Value -> Parser a withText String "TrackType" \case Text "audio" -> TrackType -> Parser TrackType forall (f :: * -> *) a. Applicative f => a -> f a pure TrackType Audio Text "sub" -> TrackType -> Parser TrackType forall (f :: * -> *) a. Applicative f => a -> f a pure TrackType Sub Text "video" -> TrackType -> Parser TrackType forall (f :: * -> *) a. Applicative f => a -> f a pure TrackType Video Text other -> String -> Parser TrackType forall (m :: * -> *) a. MonadFail m => String -> m a fail [exon|Unknown track type `#{toString other}`|] trackTypeText :: TrackType -> Text trackTypeText :: TrackType -> Text trackTypeText = \case TrackType Audio -> Text "audio" TrackType Sub -> Text "sub" TrackType Video -> Text "video" instance ToJSON TrackType where toJSON :: TrackType -> Value toJSON = Text -> Value forall a. ToJSON a => a -> Value toJSON (Text -> Value) -> (TrackType -> Text) -> TrackType -> Value forall b c a. (b -> c) -> (a -> b) -> a -> c . TrackType -> Text trackTypeText data Track = Track { Track -> Maybe Int id :: Maybe Int, Track -> Bool selected :: Bool, Track -> Maybe Text lang :: Maybe Text, Track -> TrackType _type :: TrackType } deriving stock (Track -> Track -> Bool (Track -> Track -> Bool) -> (Track -> Track -> Bool) -> Eq Track forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: Track -> Track -> Bool $c/= :: Track -> Track -> Bool == :: Track -> Track -> Bool $c== :: Track -> Track -> Bool Eq, Int -> Track -> ShowS [Track] -> ShowS Track -> String (Int -> Track -> ShowS) -> (Track -> String) -> ([Track] -> ShowS) -> Show Track forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [Track] -> ShowS $cshowList :: [Track] -> ShowS show :: Track -> String $cshow :: Track -> String showsPrec :: Int -> Track -> ShowS $cshowsPrec :: Int -> Track -> ShowS Show, (forall x. Track -> Rep Track x) -> (forall x. Rep Track x -> Track) -> Generic Track forall x. Rep Track x -> Track forall x. Track -> Rep Track x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep Track x -> Track $cfrom :: forall x. Track -> Rep Track x Generic, Eq Track Eq Track -> (Track -> Track -> Ordering) -> (Track -> Track -> Bool) -> (Track -> Track -> Bool) -> (Track -> Track -> Bool) -> (Track -> Track -> Bool) -> (Track -> Track -> Track) -> (Track -> Track -> Track) -> Ord Track Track -> Track -> Bool Track -> Track -> Ordering Track -> Track -> Track 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 :: Track -> Track -> Track $cmin :: Track -> Track -> Track max :: Track -> Track -> Track $cmax :: Track -> Track -> Track >= :: Track -> Track -> Bool $c>= :: Track -> Track -> Bool > :: Track -> Track -> Bool $c> :: Track -> Track -> Bool <= :: Track -> Track -> Bool $c<= :: Track -> Track -> Bool < :: Track -> Track -> Bool $c< :: Track -> Track -> Bool compare :: Track -> Track -> Ordering $ccompare :: Track -> Track -> Ordering Ord) json ''Track newtype TrackList = TrackList { TrackList -> NonEmpty Track unTrackList :: NonEmpty Track } deriving stock (TrackList -> TrackList -> Bool (TrackList -> TrackList -> Bool) -> (TrackList -> TrackList -> Bool) -> Eq TrackList forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: TrackList -> TrackList -> Bool $c/= :: TrackList -> TrackList -> Bool == :: TrackList -> TrackList -> Bool $c== :: TrackList -> TrackList -> Bool Eq, Int -> TrackList -> ShowS [TrackList] -> ShowS TrackList -> String (Int -> TrackList -> ShowS) -> (TrackList -> String) -> ([TrackList] -> ShowS) -> Show TrackList forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [TrackList] -> ShowS $cshowList :: [TrackList] -> ShowS show :: TrackList -> String $cshow :: TrackList -> String showsPrec :: Int -> TrackList -> ShowS $cshowsPrec :: Int -> TrackList -> ShowS Show, (forall x. TrackList -> Rep TrackList x) -> (forall x. Rep TrackList x -> TrackList) -> Generic TrackList forall x. Rep TrackList x -> TrackList forall x. TrackList -> Rep TrackList x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep TrackList x -> TrackList $cfrom :: forall x. TrackList -> Rep TrackList x Generic) json ''TrackList