kino/src/Kino/Types.hs

128 lines
3.8 KiB
Haskell

{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE OverloadedStrings #-}
{-|
Module : Kino.Types
Description : Contains the types needed for the program
Includes types for the Brick application as well as the types
used to represent the JSON data received from the API.
-}
module Kino.Types where
import Data.Aeson
import Data.Aeson.Types
import Brick.Widgets.Edit (Editor(..))
import Lens.Micro.TH
import qualified Data.Text as T
import qualified Network.Wreq as WR (Options)
-- | The general response structure returned by the API
data JSONResponse d = JSONResponse
{ respStatus :: T.Text
, respMessage :: T.Text
, respData :: Maybe d
} deriving (Eq, Show)
instance (FromJSON d) => FromJSON (JSONResponse d) where
parseJSON (Object v) = JSONResponse
<$> v .: "status"
<*> v .: "status_message"
<*> v .:? "data"
parseJSON invalid =
prependFailure "parsing JSONResponse failed, "
(typeMismatch "Object" invalid)
-- | The returned data for the list movies endpoint
data JSONListMovies = JSONListMovies
{ moviesCount :: Int
, moviesLimit :: Int
, moviesPage :: Int
, moviesMovies :: [JSONMovie]
} deriving (Eq, Show)
instance FromJSON JSONListMovies where
parseJSON (Object v) = JSONListMovies
<$> v .: "movie_count"
<*> v .: "limit"
<*> v .: "page_number"
<*> v .:? "movies" .!= []
parseJSON invalid =
prependFailure "parsing JSONListMovies failed, "
(typeMismatch "Object" invalid)
-- | An entry in the list returned by the list movies endpoint
data JSONMovie = JSONMovie
{ movieTitle :: T.Text
, movieTitleLong :: T.Text
, movieYear :: Int
, movieRating :: Double
, movieRuntime :: Int
, movieGenres :: [T.Text]
, movieSummary :: T.Text
, movieLanguage :: T.Text
, movieTorrents :: [JSONTorrent]
} deriving (Eq, Show)
instance FromJSON JSONMovie where
parseJSON (Object v) = JSONMovie
<$> v .: "title"
<*> v .: "title_long"
<*> v .: "year"
<*> v .: "rating"
<*> v .: "runtime"
<*> v .: "genres"
<*> v .: "summary"
<*> v .: "language"
<*> v .: "torrents"
parseJSON invalid =
prependFailure "parsing JSONMovie failed, "
(typeMismatch "Object" invalid)
-- | A torrent in the list in the movie object
data JSONTorrent = JSONTorrent
{ torrentHash :: T.Text
, torrentQuality :: T.Text
, torrentSeeds :: Int
} deriving (Eq, Show)
instance FromJSON JSONTorrent where
parseJSON (Object v) = JSONTorrent
<$> v .: "hash"
<*> v .: "quality"
<*> v .: "seeds"
parseJSON invalid =
prependFailure "parsing JSONTorrent failed, "
(typeMismatch "Object" invalid)
-- | 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
, _appReqOpts :: WR.Options -- ^ The options to use to make our requests
} deriving (Show)
makeLenses ''AppS