themoviedb-1.2.0.1: Haskell API bindings for http://themoviedb.org

CopyrightThis 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.
LicenseMIT
Safe HaskellNone
LanguageHaskell2010

Network.API.TheMovieDB

Contents

Description

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 a Text value).
  let key = "your API key"

  -- The fetch function will get a Movie 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

Types

data Movie Source #

Metadata for a movie.

Constructors

Movie 

Fields

Instances
Eq Movie Source # 
Instance details

Defined in Network.API.TheMovieDB.Types.Movie

Methods

(==) :: Movie -> Movie -> Bool #

(/=) :: Movie -> Movie -> Bool #

Show Movie Source # 
Instance details

Defined in Network.API.TheMovieDB.Types.Movie

Methods

showsPrec :: Int -> Movie -> ShowS #

show :: Movie -> String #

showList :: [Movie] -> ShowS #

FromJSON Movie Source # 
Instance details

Defined in Network.API.TheMovieDB.Types.Movie

data TV Source #

Metadata for a TV series.

Constructors

TV 

Fields

Instances
Eq TV Source # 
Instance details

Defined in Network.API.TheMovieDB.Types.TV

Methods

(==) :: TV -> TV -> Bool #

(/=) :: TV -> TV -> Bool #

Ord TV Source # 
Instance details

Defined in Network.API.TheMovieDB.Types.TV

Methods

compare :: TV -> TV -> Ordering #

(<) :: TV -> TV -> Bool #

(<=) :: TV -> TV -> Bool #

(>) :: TV -> TV -> Bool #

(>=) :: TV -> TV -> Bool #

max :: TV -> TV -> TV #

min :: TV -> TV -> TV #

Show TV Source # 
Instance details

Defined in Network.API.TheMovieDB.Types.TV

Methods

showsPrec :: Int -> TV -> ShowS #

show :: TV -> String #

showList :: [TV] -> ShowS #

FromJSON TV Source # 
Instance details

Defined in Network.API.TheMovieDB.Types.TV

data Season Source #

Metadata for a TV Season.

Constructors

Season 

Fields

data Episode Source #

Metadata for a TV Episode.

Constructors

Episode 

Fields

data Genre Source #

Metadata for a genre.

Constructors

Genre 

Fields

Instances
Eq Genre Source # 
Instance details

Defined in Network.API.TheMovieDB.Types.Genre

Methods

(==) :: Genre -> Genre -> Bool #

(/=) :: Genre -> Genre -> Bool #

Show Genre Source # 
Instance details

Defined in Network.API.TheMovieDB.Types.Genre

Methods

showsPrec :: Int -> Genre -> ShowS #

show :: Genre -> String #

showList :: [Genre] -> ShowS #

FromJSON Genre Source # 
Instance details

Defined in Network.API.TheMovieDB.Types.Genre

data Error Source #

Possible errors returned by the API.

Constructors

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.

Instances
Show Error Source # 
Instance details

Defined in Network.API.TheMovieDB.Internal.Types

Methods

showsPrec :: Int -> Error -> ShowS #

show :: Error -> String #

showList :: [Error] -> ShowS #

type ItemID = Int Source #

Type to represent IDs used by the API.

Library Settings

data Settings Source #

Settings used by this library.

Constructors

Settings 

Fields

defaultSettings :: Key -> Settings Source #

Default settings.

type Key = Text Source #

Type for the API key issued by TheMovieDB.

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 # 
Instance details

Defined in Network.API.TheMovieDB.Internal.TheMovieDB

Methods

(>>=) :: TheMovieDB a -> (a -> TheMovieDB b) -> TheMovieDB b #

(>>) :: TheMovieDB a -> TheMovieDB b -> TheMovieDB b #

return :: a -> TheMovieDB a #

fail :: String -> TheMovieDB a #

Functor TheMovieDB Source # 
Instance details

Defined in Network.API.TheMovieDB.Internal.TheMovieDB

Methods

fmap :: (a -> b) -> TheMovieDB a -> TheMovieDB b #

(<$) :: a -> TheMovieDB b -> TheMovieDB a #

Applicative TheMovieDB Source # 
Instance details

Defined in Network.API.TheMovieDB.Internal.TheMovieDB

Methods

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 # 
Instance details

Defined in Network.API.TheMovieDB.Internal.TheMovieDB

Methods

liftIO :: IO a -> TheMovieDB a #

runTheMovieDB Source #

Arguments

:: 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 #

Arguments

:: Manager

The Manager to use.

-> 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.

fetchMovie Source #

Arguments

:: 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.

fetchTV Source #

Arguments

:: ItemID

TheMovieDB ID for the TV series.

-> TheMovieDB TV 

Fetch metadata for a TV series given its TheMovieDB ID. The metadata for Seasons 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.

fetchTVSeason Source #

Arguments

:: ItemID

TheMovieDB ID for the TV series.

-> Int

Season number (not season ID).

-> TheMovieDB Season 

Fetch metadata for a Season, including all Episodes.

fetchFullTVSeries Source #

Arguments

:: 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.

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.