module Network.API.TheMovieDB.Types.Movie
( Movie (..),
moviePosterURLs,
)
where
import Data.Aeson
import Data.Time (Day (..))
import Network.API.TheMovieDB.Internal.Configuration
import Network.API.TheMovieDB.Internal.Date
import Network.API.TheMovieDB.Internal.Types
import Network.API.TheMovieDB.Types.Genre
data Movie = Movie
{
Movie -> ItemID
movieID :: ItemID,
Movie -> Text
movieTitle :: Text,
Movie -> Text
movieOverview :: Text,
Movie -> [Genre]
movieGenres :: [Genre],
Movie -> Double
moviePopularity :: Double,
Movie -> Text
moviePosterPath :: Text,
Movie -> Maybe Day
movieReleaseDate :: Maybe Day,
Movie -> Bool
movieAdult :: Bool,
Movie -> Text
movieIMDB :: Text,
Movie -> ItemID
movieRunTime :: Int
}
deriving (Movie -> Movie -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Movie -> Movie -> Bool
$c/= :: Movie -> Movie -> Bool
== :: Movie -> Movie -> Bool
$c== :: Movie -> Movie -> Bool
Eq, ItemID -> Movie -> ShowS
[Movie] -> ShowS
Movie -> String
forall a.
(ItemID -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Movie] -> ShowS
$cshowList :: [Movie] -> ShowS
show :: Movie -> String
$cshow :: Movie -> String
showsPrec :: ItemID -> Movie -> ShowS
$cshowsPrec :: ItemID -> Movie -> ShowS
Show)
instance FromJSON Movie where
parseJSON :: Value -> Parser Movie
parseJSON = forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Movie" forall a b. (a -> b) -> a -> b
$ \Object
v ->
ItemID
-> Text
-> Text
-> [Genre]
-> Double
-> Text
-> Maybe Day
-> Bool
-> Text
-> ItemID
-> Movie
Movie
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"id"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"title"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"overview" forall a. Parser (Maybe a) -> a -> Parser a
.!= Text
""
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"genres" forall a. Parser (Maybe a) -> a -> Parser a
.!= []
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"popularity" forall a. Parser (Maybe a) -> a -> Parser a
.!= Double
0.0
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"poster_path" forall a. Parser (Maybe a) -> a -> Parser a
.!= Text
""
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser (Maybe Day)
.:: Key
"release_date"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"adult" forall a. Parser (Maybe a) -> a -> Parser a
.!= Bool
False
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"imdb_id" forall a. Parser (Maybe a) -> a -> Parser a
.!= Text
""
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"runtime" forall a. Parser (Maybe a) -> a -> Parser a
.!= ItemID
0
moviePosterURLs :: Configuration -> Movie -> [Text]
moviePosterURLs :: Configuration -> Movie -> [Text]
moviePosterURLs Configuration
c Movie
m = Configuration -> Text -> [Text]
posterURLs Configuration
c (Movie -> Text
moviePosterPath Movie
m)