module Mpv.Data.EventPayload where import Data.Aeson (FromJSON (parseJSON), ToJSON (toJSON), withText) import Polysemy.Time.Json (json) import Prelude hiding (Stop) data EndReason = Quit | Stop | Eof | Error | Redirect | Unknown deriving stock (EndReason -> EndReason -> Bool (EndReason -> EndReason -> Bool) -> (EndReason -> EndReason -> Bool) -> Eq EndReason forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: EndReason -> EndReason -> Bool $c/= :: EndReason -> EndReason -> Bool == :: EndReason -> EndReason -> Bool $c== :: EndReason -> EndReason -> Bool Eq, Int -> EndReason -> ShowS [EndReason] -> ShowS EndReason -> String (Int -> EndReason -> ShowS) -> (EndReason -> String) -> ([EndReason] -> ShowS) -> Show EndReason forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [EndReason] -> ShowS $cshowList :: [EndReason] -> ShowS show :: EndReason -> String $cshow :: EndReason -> String showsPrec :: Int -> EndReason -> ShowS $cshowsPrec :: Int -> EndReason -> ShowS Show) endReasonFromText :: Text -> EndReason endReasonFromText :: Text -> EndReason endReasonFromText = \case Text "quit" -> EndReason Quit Text "stop" -> EndReason Stop Text "eof" -> EndReason Eof Text "error" -> EndReason Error Text "redirect" -> EndReason Redirect Text _ -> EndReason Unknown endReasonText :: EndReason -> Text endReasonText :: EndReason -> Text endReasonText = \case EndReason Quit -> Text "quit" EndReason Stop -> Text "stop" EndReason Eof -> Text "eof" EndReason Error -> Text "error" EndReason Redirect -> Text "redirect" EndReason Unknown -> Text "unknown" instance FromJSON EndReason where parseJSON :: Value -> Parser EndReason parseJSON = String -> (Text -> Parser EndReason) -> Value -> Parser EndReason forall a. String -> (Text -> Parser a) -> Value -> Parser a withText String "EndReason" (EndReason -> Parser EndReason forall (f :: * -> *) a. Applicative f => a -> f a pure (EndReason -> Parser EndReason) -> (Text -> EndReason) -> Text -> Parser EndReason forall b c a. (b -> c) -> (a -> b) -> a -> c . Text -> EndReason endReasonFromText) instance ToJSON EndReason where toJSON :: EndReason -> Value toJSON = Text -> Value forall a. ToJSON a => a -> Value toJSON (Text -> Value) -> (EndReason -> Text) -> EndReason -> Value forall b c a. (b -> c) -> (a -> b) -> a -> c . EndReason -> Text endReasonText data EndFile = EndFile { EndFile -> Int playlist_entry_id :: Int, EndFile -> EndReason reason :: EndReason } deriving stock (EndFile -> EndFile -> Bool (EndFile -> EndFile -> Bool) -> (EndFile -> EndFile -> Bool) -> Eq EndFile forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: EndFile -> EndFile -> Bool $c/= :: EndFile -> EndFile -> Bool == :: EndFile -> EndFile -> Bool $c== :: EndFile -> EndFile -> Bool Eq, Int -> EndFile -> ShowS [EndFile] -> ShowS EndFile -> String (Int -> EndFile -> ShowS) -> (EndFile -> String) -> ([EndFile] -> ShowS) -> Show EndFile forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [EndFile] -> ShowS $cshowList :: [EndFile] -> ShowS show :: EndFile -> String $cshow :: EndFile -> String showsPrec :: Int -> EndFile -> ShowS $cshowsPrec :: Int -> EndFile -> ShowS Show) json ''EndFile data FileLoaded = FileLoaded deriving stock (FileLoaded -> FileLoaded -> Bool (FileLoaded -> FileLoaded -> Bool) -> (FileLoaded -> FileLoaded -> Bool) -> Eq FileLoaded forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: FileLoaded -> FileLoaded -> Bool $c/= :: FileLoaded -> FileLoaded -> Bool == :: FileLoaded -> FileLoaded -> Bool $c== :: FileLoaded -> FileLoaded -> Bool Eq, Int -> FileLoaded -> ShowS [FileLoaded] -> ShowS FileLoaded -> String (Int -> FileLoaded -> ShowS) -> (FileLoaded -> String) -> ([FileLoaded] -> ShowS) -> Show FileLoaded forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [FileLoaded] -> ShowS $cshowList :: [FileLoaded] -> ShowS show :: FileLoaded -> String $cshow :: FileLoaded -> String showsPrec :: Int -> FileLoaded -> ShowS $cshowsPrec :: Int -> FileLoaded -> ShowS Show) json ''FileLoaded data Pause = Pause deriving stock (Pause -> Pause -> Bool (Pause -> Pause -> Bool) -> (Pause -> Pause -> Bool) -> Eq Pause forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: Pause -> Pause -> Bool $c/= :: Pause -> Pause -> Bool == :: Pause -> Pause -> Bool $c== :: Pause -> Pause -> Bool Eq, Int -> Pause -> ShowS [Pause] -> ShowS Pause -> String (Int -> Pause -> ShowS) -> (Pause -> String) -> ([Pause] -> ShowS) -> Show Pause forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [Pause] -> ShowS $cshowList :: [Pause] -> ShowS show :: Pause -> String $cshow :: Pause -> String showsPrec :: Int -> Pause -> ShowS $cshowsPrec :: Int -> Pause -> ShowS Show) json ''Pause