2021-09-20 14:19:48 +02:00
|
|
|
{-# LANGUAGE TemplateHaskell #-}
|
2021-09-05 19:30:29 +02:00
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
|
|
|
|
2021-09-17 17:36:58 +02:00
|
|
|
{-|
|
2021-09-20 14:19:48 +02:00
|
|
|
Module : Kino.Types
|
|
|
|
Description : Contains the types needed for the program
|
2021-09-17 17:36:58 +02:00
|
|
|
|
2021-09-20 14:19:48 +02:00
|
|
|
Includes types for the Brick application as well as the types
|
|
|
|
used to represent the JSON data received from the API.
|
2021-09-17 17:36:58 +02:00
|
|
|
-}
|
2021-09-20 14:19:48 +02:00
|
|
|
|
|
|
|
module Kino.Types where
|
2021-09-05 19:30:29 +02:00
|
|
|
|
|
|
|
import Data.Aeson
|
|
|
|
import Data.Aeson.Types
|
2021-09-20 14:19:48 +02:00
|
|
|
import Brick.Widgets.Edit (Editor(..))
|
|
|
|
import Lens.Micro.TH
|
2021-09-06 21:02:39 +02:00
|
|
|
import qualified Data.Text as T
|
2021-09-05 19:30:29 +02:00
|
|
|
|
2021-09-20 14:19:48 +02:00
|
|
|
-- | The general response structure returned by the API
|
2021-09-05 19:30:29 +02:00
|
|
|
data JSONResponse d = JSONResponse
|
2021-09-17 17:36:58 +02:00
|
|
|
{ respStatus :: T.Text
|
|
|
|
, respMessage :: T.Text
|
|
|
|
, respData :: Maybe d
|
|
|
|
} deriving (Eq, Show)
|
2021-09-05 19:30:29 +02:00
|
|
|
|
|
|
|
instance (FromJSON d) => FromJSON (JSONResponse d) where
|
|
|
|
parseJSON (Object v) = JSONResponse
|
|
|
|
<$> v .: "status"
|
|
|
|
<*> v .: "status_message"
|
2021-09-20 13:21:48 +02:00
|
|
|
<*> v .:? "data"
|
2021-09-05 19:30:29 +02:00
|
|
|
parseJSON invalid =
|
|
|
|
prependFailure "parsing JSONResponse failed, "
|
|
|
|
(typeMismatch "Object" invalid)
|
|
|
|
|
2021-09-20 14:19:48 +02:00
|
|
|
-- | The returned data for the list movies endpoint
|
2021-09-05 19:30:29 +02:00
|
|
|
data JSONListMovies = JSONListMovies
|
2021-09-17 17:36:58 +02:00
|
|
|
{ moviesCount :: Int
|
|
|
|
, moviesLimit :: Int
|
2021-09-20 13:21:48 +02:00
|
|
|
, moviesPage :: Int
|
|
|
|
, moviesMovies :: [JSONMovie]
|
2021-09-17 17:36:58 +02:00
|
|
|
} deriving (Eq, Show)
|
2021-09-05 19:30:29 +02:00
|
|
|
|
|
|
|
instance FromJSON JSONListMovies where
|
|
|
|
parseJSON (Object v) = JSONListMovies
|
|
|
|
<$> v .: "movie_count"
|
|
|
|
<*> v .: "limit"
|
|
|
|
<*> v .: "page_number"
|
2021-09-20 13:21:48 +02:00
|
|
|
<*> v .:? "movies" .!= []
|
2021-09-05 19:30:29 +02:00
|
|
|
parseJSON invalid =
|
|
|
|
prependFailure "parsing JSONListMovies failed, "
|
|
|
|
(typeMismatch "Object" invalid)
|
|
|
|
|
2021-09-20 14:19:48 +02:00
|
|
|
-- | An entry in the list returned by the list movies endpoint
|
2021-09-05 19:30:29 +02:00
|
|
|
data JSONMovie = JSONMovie
|
2021-09-20 14:19:48 +02:00
|
|
|
{ movieTitle :: T.Text
|
2021-09-17 17:36:58 +02:00
|
|
|
, movieTitleLong :: T.Text
|
|
|
|
, movieYear :: Int
|
|
|
|
, movieRating :: Double
|
|
|
|
, movieRuntime :: Int
|
|
|
|
, movieGenres :: [T.Text]
|
|
|
|
, movieSummary :: T.Text
|
|
|
|
, movieLanguage :: T.Text
|
|
|
|
, movieTorrents :: [JSONTorrent]
|
|
|
|
} deriving (Eq, Show)
|
2021-09-05 19:30:29 +02:00
|
|
|
|
|
|
|
instance FromJSON JSONMovie where
|
|
|
|
parseJSON (Object v) = JSONMovie
|
2021-09-20 14:19:48 +02:00
|
|
|
<$> v .: "title"
|
2021-09-06 21:02:39 +02:00
|
|
|
<*> v .: "title_long"
|
2021-09-05 19:30:29 +02:00
|
|
|
<*> v .: "year"
|
|
|
|
<*> v .: "rating"
|
|
|
|
<*> v .: "runtime"
|
|
|
|
<*> v .: "genres"
|
|
|
|
<*> v .: "summary"
|
|
|
|
<*> v .: "language"
|
|
|
|
<*> v .: "torrents"
|
2021-09-20 14:19:48 +02:00
|
|
|
parseJSON invalid =
|
2021-09-05 19:30:29 +02:00
|
|
|
prependFailure "parsing JSONMovie failed, "
|
|
|
|
(typeMismatch "Object" invalid)
|
|
|
|
|
2021-09-20 14:19:48 +02:00
|
|
|
-- | A torrent in the list in the movie object
|
2021-09-05 19:30:29 +02:00
|
|
|
data JSONTorrent = JSONTorrent
|
2021-09-20 14:19:48 +02:00
|
|
|
{ torrentHash :: T.Text
|
2021-09-17 17:36:58 +02:00
|
|
|
, torrentQuality :: T.Text
|
|
|
|
, torrentSeeds :: Int
|
|
|
|
} deriving (Eq, Show)
|
2021-09-05 19:30:29 +02:00
|
|
|
|
|
|
|
instance FromJSON JSONTorrent where
|
|
|
|
parseJSON (Object v) = JSONTorrent
|
2021-09-20 14:19:48 +02:00
|
|
|
<$> v .: "hash"
|
2021-09-05 19:30:29 +02:00
|
|
|
<*> v .: "quality"
|
|
|
|
<*> v .: "seeds"
|
2021-09-20 14:19:48 +02:00
|
|
|
parseJSON invalid =
|
2021-09-05 19:30:29 +02:00
|
|
|
prependFailure "parsing JSONTorrent failed, "
|
|
|
|
(typeMismatch "Object" invalid)
|
2021-09-20 14:19:48 +02:00
|
|
|
|
|
|
|
-- | Contains the different elements which we
|
|
|
|
-- might want brick to be able to identify
|
|
|
|
data Ident = Listing | Input | ListItem Int
|
|
|
|
deriving (Eq, Ord, Show)
|
|
|
|
|
|
|
|
-- | Used to distinguish what set of
|
|
|
|
-- widgets should currently be rendered.
|
|
|
|
data Mode = Search | Browse | Message
|
|
|
|
deriving (Eq, Ord, Show)
|
|
|
|
|
|
|
|
-- | Used for scrolling
|
|
|
|
data ScrollDirection = Up | Down
|
|
|
|
deriving (Eq, Show)
|
|
|
|
|
|
|
|
-- | The state of our app
|
|
|
|
data AppS = AppS
|
|
|
|
{ _appMode :: Mode -- ^ The current mode of the app
|
|
|
|
, _appCursor :: Int -- ^ The selected into the listing
|
|
|
|
, _appExpanded :: Bool -- ^ If the currently selected listing is expanded
|
|
|
|
, _appPage :: Int -- ^ The page currently being viewed
|
|
|
|
, _appListing :: JSONListMovies -- ^ The movies being browsed
|
|
|
|
, _appDetails :: Maybe JSONMovie -- ^ The movie being focused
|
|
|
|
, _appMessage :: Maybe String -- ^ The message to be shown in message mode
|
|
|
|
, _appContinue :: Bool -- ^ If to continue after showing message
|
|
|
|
, _appEditor :: Editor T.Text Ident -- ^ The state for the editor widget
|
|
|
|
} deriving (Show)
|
|
|
|
|
|
|
|
makeLenses ''AppS
|