module Network.API.TheMovieDB.Types.Episode
( Episode (..),
episodeStillURLs,
)
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
data Episode = Episode
{
Episode -> ItemID
episodeID :: ItemID,
Episode -> ItemID
episodeNumber :: Int,
Episode -> Text
episodeName :: Text,
Episode -> Text
episodeOverview :: Text,
Episode -> ItemID
episodeSeasonNumber :: Int,
Episode -> Maybe Day
episodeAirDate :: Maybe Day,
Episode -> Text
episodeStillPath :: Text
}
deriving (Episode -> Episode -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Episode -> Episode -> Bool
$c/= :: Episode -> Episode -> Bool
== :: Episode -> Episode -> Bool
$c== :: Episode -> Episode -> Bool
Eq, ItemID -> Episode -> ShowS
[Episode] -> ShowS
Episode -> String
forall a.
(ItemID -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Episode] -> ShowS
$cshowList :: [Episode] -> ShowS
show :: Episode -> String
$cshow :: Episode -> String
showsPrec :: ItemID -> Episode -> ShowS
$cshowsPrec :: ItemID -> Episode -> ShowS
Show)
instance Ord Episode where
compare :: Episode -> Episode -> Ordering
compare Episode
a Episode
b =
forall a. Ord a => a -> a -> Ordering
compare
(Episode -> ItemID
episodeSeasonNumber Episode
a, Episode -> ItemID
episodeNumber Episode
a)
(Episode -> ItemID
episodeSeasonNumber Episode
b, Episode -> ItemID
episodeNumber Episode
b)
instance FromJSON Episode where
parseJSON :: Value -> Parser Episode
parseJSON = forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Episode" forall a b. (a -> b) -> a -> b
$ \Object
v ->
ItemID
-> ItemID -> Text -> Text -> ItemID -> Maybe Day -> Text -> Episode
Episode 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
"episode_number"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"name"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"overview"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"season_number" forall a. Parser (Maybe a) -> a -> Parser a
.!= ItemID
0
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser (Maybe Day)
.:: Key
"air_date"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"still_path" forall a. Parser (Maybe a) -> a -> Parser a
.!= Text
""
episodeStillURLs :: Configuration -> Episode -> [Text]
episodeStillURLs :: Configuration -> Episode -> [Text]
episodeStillURLs Configuration
c Episode
e = Configuration -> Text -> [Text]
posterURLs Configuration
c (Episode -> Text
episodeStillPath Episode
e)