Copyright | This file is part of the package themoviedb. It is subject to the license terms in the LICENSE file found in the top-level directory of this distribution and at: https://github.com/pjones/themoviedb No part of this package including this file may be copied modified propagated or distributed except according to the terms contained in the LICENSE file. |
---|---|
License | MIT |
Safe Haskell | None |
Language | Haskell2010 |
This library provides some data types and functions for fetching movie metadata from http://TheMovieDB.org. To use this library start by requesting an API key from http://docs.themoviedb.apiary.io.
Example:
import Network.API.TheMovieDB main :: IO () main = do -- The API key assigned to you (as aText
value). let key = "your API key" -- Thefetch
function will get aMovie
record based on its ID. result <- runTheMovieDB (defaultSettings key) (fetchMovie 9340) -- Do something with the result (or error). putStrLn (show result)
This library also includes an example executable in the example
directory.
Synopsis
- data Movie = Movie {
- movieID :: ItemID
- movieTitle :: Text
- movieOverview :: Text
- movieGenres :: [Genre]
- moviePopularity :: Double
- moviePosterPath :: Text
- movieReleaseDate :: Maybe Day
- movieAdult :: Bool
- movieIMDB :: Text
- movieRunTime :: Int
- data TV = TV {
- tvID :: ItemID
- tvName :: Text
- tvOverview :: Text
- tvGenres :: [Genre]
- tvPopularity :: Double
- tvPosterPath :: Text
- tvFirstAirDate :: Maybe Day
- tvLastAirDate :: Maybe Day
- tvNumberOfSeasons :: Int
- tvNumberOfEpisodes :: Int
- tvSeasons :: [Season]
- data Season = Season {}
- data Episode = Episode {}
- data Genre = Genre {}
- data Error
- type ItemID = Int
- data Settings = Settings {}
- defaultSettings :: Key -> Settings
- type Key = Text
- type LanguageCode = Text
- data TheMovieDB a
- runTheMovieDB :: Settings -> TheMovieDB a -> IO (Either Error a)
- runTheMovieDBWithManager :: Manager -> Settings -> TheMovieDB a -> IO (Either Error a)
- searchMovies :: Text -> TheMovieDB [Movie]
- fetchMovie :: ItemID -> TheMovieDB Movie
- searchTV :: Text -> TheMovieDB [TV]
- fetchTV :: ItemID -> TheMovieDB TV
- fetchTVSeason :: ItemID -> Int -> TheMovieDB Season
- fetchFullTVSeries :: ItemID -> TheMovieDB TV
- data Configuration
- config :: TheMovieDB Configuration
- moviePosterURLs :: Configuration -> Movie -> [Text]
- tvPosterURLs :: Configuration -> TV -> [Text]
- seasonPosterURLs :: Configuration -> Season -> [Text]
- episodeStillURLs :: Configuration -> Episode -> [Text]
Types
Metadata for a movie.
- The
moviePosterPath
field is an incomplete URL. To construct a complete URL you'll need to use theConfiguration
type and themoviePosterURLs
helper function.
Movie | |
|
Metadata for a TV series.
- The
tvPosterPath
field is an incomplete URL. To construct a complete URL you'll need to use theConfiguration
type and thetvPosterURLs
helper function.
TV | |
|
Metadata for a TV Season.
- The
seasonPosterPath
field is an incomplete URL. To construct a complete URL you'll need to use theConfiguration
type and theseasonPosterURLs
helper function.
Season | |
|
Metadata for a TV Episode.
- The
episodeStillPath
field is an incomplete URL. To construct a complete URL you'll need to use theConfiguration
type and theepisodeStillURLs
helper function.
Episode | |
|
Possible errors returned by the API.
InvalidKeyError | Missing or invalid API key. Make sure you are using a valid API key issued by https://www.themoviedb.org/faq/api. |
HttpExceptionError HttpException | An exception relating to HTTP was thrown while interacting with the API. |
ServiceError String | The HTTP interaction with the API service did not result in a successful response. Information about the failure is encoded in the String. |
ResponseParseError String (Maybe LByteString) | Invalid or error response from the API. |
Library Settings
Settings used by this library.
Settings | |
|
defaultSettings :: Key -> Settings Source #
Default settings.
type LanguageCode = Text Source #
Type for selecting a TMDb language in ISO 639-1 format.
API Functions
data TheMovieDB a Source #
Result type for operations involving TheMovieDB API.
Instances
Monad TheMovieDB Source # | |
Defined in Network.API.TheMovieDB.Internal.TheMovieDB (>>=) :: TheMovieDB a -> (a -> TheMovieDB b) -> TheMovieDB b # (>>) :: TheMovieDB a -> TheMovieDB b -> TheMovieDB b # return :: a -> TheMovieDB a # fail :: String -> TheMovieDB a # | |
Functor TheMovieDB Source # | |
Defined in Network.API.TheMovieDB.Internal.TheMovieDB fmap :: (a -> b) -> TheMovieDB a -> TheMovieDB b # (<$) :: a -> TheMovieDB b -> TheMovieDB a # | |
Applicative TheMovieDB Source # | |
Defined in Network.API.TheMovieDB.Internal.TheMovieDB pure :: a -> TheMovieDB a # (<*>) :: TheMovieDB (a -> b) -> TheMovieDB a -> TheMovieDB b # liftA2 :: (a -> b -> c) -> TheMovieDB a -> TheMovieDB b -> TheMovieDB c # (*>) :: TheMovieDB a -> TheMovieDB b -> TheMovieDB b # (<*) :: TheMovieDB a -> TheMovieDB b -> TheMovieDB a # | |
MonadIO TheMovieDB Source # | |
Defined in Network.API.TheMovieDB.Internal.TheMovieDB liftIO :: IO a -> TheMovieDB a # |
:: Settings | Library settings. |
-> TheMovieDB a | The API calls to make. |
-> IO (Either Error a) | Response or error. |
Execute requests for TheMovieDB with the given API key and produce either an error or a result.
This version creates a temporary Manager
using
tlsManagerSettings
. If you want to use an existing Manager
you
should use runTheMovieDBWithManager
instead.
runTheMovieDBWithManager Source #
:: Manager | The |
-> Settings | Library settings. |
-> TheMovieDB a | The API calls to make. |
-> IO (Either Error a) | Response or error. |
Execute requests for TheMovieDB with the given API key and produce either an error or a result.
This version allows you to provide a Manager
value which should
have been created to allow TLS requests (e.g., with tlsManagerSettings
).
searchMovies :: Text -> TheMovieDB [Movie] Source #
Search TheMovieDB using the given query string.
The movies returned will not have all their fields completely
filled out, to get a complete record you'll need to follow this
call up with a call to fetchMovie
.
:: ItemID | TheMovieDB ID for the movie. |
-> TheMovieDB Movie |
Fetch the metadata for the Movie
with the given ID.
searchTV :: Text -> TheMovieDB [TV] Source #
Search TheMovieDB for matching TV
series.
The TV
values returned from this function will be partial
records. The only fields that will be available are tvID
,
tvName
, tvPosterPath
, tvPopularity
, and possibly
tvFirstAirDate
.
To get full TV
records you need to follow this function with a
call to fetchTV
using the desired tvID
value.
:: ItemID | TheMovieDB ID for the TV series. |
-> TheMovieDB TV |
Fetch metadata for a TV
series given its TheMovieDB ID. The
metadata for Season
s listed in the TV series will not have
complete Episode
information.
After calling this function you should call fetchTVSeason
to fill
in the Episode
metadata, or just begin with fetchFullTVSeries
.
:: ItemID | TheMovieDB ID for the TV series. |
-> Int | Season number (not season ID). |
-> TheMovieDB Season |
Fetch metadata for a Season
, including all Episode
s.
:: ItemID | TheMovieDB ID for the TV series. |
-> TheMovieDB TV |
Fetch full metadata for a TV
series, including all seasons and
episodes.
This function will make multiple HTTP requests to TheMovieDB API.
Utility Types and Functions
data Configuration Source #
TheMovieDB API tries to preserve bandwidth by omitting
information (such as full URLs for poster images) from most of the
API calls. Therefore in order to construct a complete URL for a
movie poster you'll need to use the config
function to retrieve
API configuration information.
A helper function is provided (moviePosterURLs
) that constructs a
list of all poster URLs given a Movie
and Configuration
.
According to the API documentation for TheMovieDB, you should cache
the Configuration
value and only request it every few days.
Instances
config :: TheMovieDB Configuration Source #
Fetch the API configuration information such as base URLs for movie posters. The resulting configuration value should be cached and only requested every few days.
moviePosterURLs :: Configuration -> Movie -> [Text] Source #
Return a list of URLs for all possible movie posters.
tvPosterURLs :: Configuration -> TV -> [Text] Source #
Return a list of URLs for all possible TV posters.
seasonPosterURLs :: Configuration -> Season -> [Text] Source #
Return a list of URLs for all possible season posters.
episodeStillURLs :: Configuration -> Episode -> [Text] Source #
Return a list of URLs for all possible episode still images.