giphy-api-0.7.0.0: Giphy HTTP API wrapper and CLI search tool.

Safe HaskellNone
LanguageHaskell2010

Web.Giphy

Contents

Description

Provides a Giphy monad that can be used to issue selected API calls under a selected API key.

import qualified Web.Giphy as Giphy

let apiKey = Giphy.Key "dc6zaTOxFJmzC"
let config = Giphy.GiphyConfig apiKey
resp <- Giphy.runGiphy (Giphy.search $ Giphy.query "puppies") config
let fstUrl = resp ^? _Right
                   . Giphy.searchItems
                   . _head
                   . Giphy.gifImages
                   . at "original"
                   . traverse
                   . Giphy.imageUrl
                   . traverse
print fstUrl
Synopsis

Request Data Types

These data types are used to encapsulate otherwise weakly typed arguments.

newtype Key Source #

Constructors

Key Text 
Instances
Eq Key Source # 
Instance details

Defined in Web.Giphy

Methods

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

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

Show Key Source # 
Instance details

Defined in Web.Giphy

Methods

showsPrec :: Int -> Key -> ShowS #

show :: Key -> String #

showList :: [Key] -> ShowS #

ToHttpApiData Key Source # 
Instance details

Defined in Web.Giphy

FromHttpApiData Key Source # 
Instance details

Defined in Web.Giphy

newtype Query Source #

A search query.

Constructors

Query Text 
Instances
Eq Query Source # 
Instance details

Defined in Web.Giphy

Methods

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

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

Show Query Source # 
Instance details

Defined in Web.Giphy

Methods

showsPrec :: Int -> Query -> ShowS #

show :: Query -> String #

showList :: [Query] -> ShowS #

ToHttpApiData Query Source # 
Instance details

Defined in Web.Giphy

FromHttpApiData Query Source # 
Instance details

Defined in Web.Giphy

newtype Phrase Source #

A phrase or term used for translation.

Constructors

Phrase Text 
Instances
Eq Phrase Source # 
Instance details

Defined in Web.Giphy

Methods

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

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

Show Phrase Source # 
Instance details

Defined in Web.Giphy

ToHttpApiData Phrase Source # 
Instance details

Defined in Web.Giphy

FromHttpApiData Phrase Source # 
Instance details

Defined in Web.Giphy

newtype Tag Source #

A tag to retrieve a random GIF for.

Constructors

Tag Text 
Instances
Eq Tag Source # 
Instance details

Defined in Web.Giphy

Methods

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

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

Show Tag Source # 
Instance details

Defined in Web.Giphy

Methods

showsPrec :: Int -> Tag -> ShowS #

show :: Tag -> String #

showList :: [Tag] -> ShowS #

ToHttpApiData Tag Source # 
Instance details

Defined in Web.Giphy

FromHttpApiData Tag Source # 
Instance details

Defined in Web.Giphy

data Pagination Source #

Metadata about pagination in a response.

Instances
Eq Pagination Source # 
Instance details

Defined in Web.Giphy

Ord Pagination Source # 
Instance details

Defined in Web.Giphy

Show Pagination Source # 
Instance details

Defined in Web.Giphy

Generic Pagination Source # 
Instance details

Defined in Web.Giphy

Associated Types

type Rep Pagination :: Type -> Type #

FromJSON Pagination Source # 
Instance details

Defined in Web.Giphy

type Rep Pagination Source # 
Instance details

Defined in Web.Giphy

type Rep Pagination = D1 (MetaData "Pagination" "Web.Giphy" "giphy-api-0.7.0.0-GKIHg4B0k0i279jBFZMsh0" False) (C1 (MetaCons "Pagination" PrefixI True) (S1 (MetaSel (Just "_paginationTotalCount") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: (S1 (MetaSel (Just "_paginationCount") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Just "_paginationOffset") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int))))

newtype GifId Source #

A unique gif identifier.

Constructors

GifId Text 
Instances
Eq GifId Source # 
Instance details

Defined in Web.Giphy

Methods

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

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

Show GifId Source # 
Instance details

Defined in Web.Giphy

Methods

showsPrec :: Int -> GifId -> ShowS #

show :: GifId -> String #

showList :: [GifId] -> ShowS #

ToHttpApiData GifId Source # 
Instance details

Defined in Web.Giphy

FromHttpApiData GifId Source # 
Instance details

Defined in Web.Giphy

Response Data Types

These data types contain are the parsed JSON responses from the Giphy API.

data Gif Source #

A search response item.

Constructors

Gif 
Instances
Eq Gif Source # 
Instance details

Defined in Web.Giphy

Methods

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

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

Ord Gif Source # 
Instance details

Defined in Web.Giphy

Methods

compare :: Gif -> Gif -> Ordering #

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

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

(>) :: Gif -> Gif -> Bool #

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

max :: Gif -> Gif -> Gif #

min :: Gif -> Gif -> Gif #

Show Gif Source # 
Instance details

Defined in Web.Giphy

Methods

showsPrec :: Int -> Gif -> ShowS #

show :: Gif -> String #

showList :: [Gif] -> ShowS #

Generic Gif Source # 
Instance details

Defined in Web.Giphy

Associated Types

type Rep Gif :: Type -> Type #

Methods

from :: Gif -> Rep Gif x #

to :: Rep Gif x -> Gif #

FromJSON Gif Source # 
Instance details

Defined in Web.Giphy

type Rep Gif Source # 
Instance details

Defined in Web.Giphy

data Image Source #

An image contained in a Giphy response.

Instances
Eq Image Source # 
Instance details

Defined in Web.Giphy

Methods

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

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

Ord Image Source # 
Instance details

Defined in Web.Giphy

Methods

compare :: Image -> Image -> Ordering #

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

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

(>) :: Image -> Image -> Bool #

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

max :: Image -> Image -> Image #

min :: Image -> Image -> Image #

Show Image Source # 
Instance details

Defined in Web.Giphy

Methods

showsPrec :: Int -> Image -> ShowS #

show :: Image -> String #

showList :: [Image] -> ShowS #

Generic Image Source # 
Instance details

Defined in Web.Giphy

Associated Types

type Rep Image :: Type -> Type #

Methods

from :: Image -> Rep Image x #

to :: Rep Image x -> Image #

FromJSON Image Source # 
Instance details

Defined in Web.Giphy

type Rep Image Source # 
Instance details

Defined in Web.Giphy

type ImageMap = Map Text Image Source #

Mapping from a Text identifier to an Image.

data SearchResponse Source #

A collection of GIFs as part of a search response.

Instances
Eq SearchResponse Source # 
Instance details

Defined in Web.Giphy

Ord SearchResponse Source # 
Instance details

Defined in Web.Giphy

Show SearchResponse Source # 
Instance details

Defined in Web.Giphy

Generic SearchResponse Source # 
Instance details

Defined in Web.Giphy

Associated Types

type Rep SearchResponse :: Type -> Type #

FromJSON SearchResponse Source # 
Instance details

Defined in Web.Giphy

type Rep SearchResponse Source # 
Instance details

Defined in Web.Giphy

type Rep SearchResponse = D1 (MetaData "SearchResponse" "Web.Giphy" "giphy-api-0.7.0.0-GKIHg4B0k0i279jBFZMsh0" False) (C1 (MetaCons "SearchResponse" PrefixI True) (S1 (MetaSel (Just "_searchItems") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Gif]) :*: S1 (MetaSel (Just "_searchPagination") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Pagination)))

newtype SingleGifResponse Source #

A single gif as part of a response.

Constructors

SingleGifResponse 

Fields

Instances
Eq SingleGifResponse Source # 
Instance details

Defined in Web.Giphy

Ord SingleGifResponse Source # 
Instance details

Defined in Web.Giphy

Show SingleGifResponse Source # 
Instance details

Defined in Web.Giphy

Generic SingleGifResponse Source # 
Instance details

Defined in Web.Giphy

Associated Types

type Rep SingleGifResponse :: Type -> Type #

FromJSON SingleGifResponse Source # 
Instance details

Defined in Web.Giphy

type Rep SingleGifResponse Source # 
Instance details

Defined in Web.Giphy

type Rep SingleGifResponse = D1 (MetaData "SingleGifResponse" "Web.Giphy" "giphy-api-0.7.0.0-GKIHg4B0k0i279jBFZMsh0" True) (C1 (MetaCons "SingleGifResponse" PrefixI True) (S1 (MetaSel (Just "_singleGifItem") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Gif)))

newtype TranslateResponse Source #

A single GIF as part of a translate response.

Constructors

TranslateResponse 

Fields

Instances
Eq TranslateResponse Source # 
Instance details

Defined in Web.Giphy

Ord TranslateResponse Source # 
Instance details

Defined in Web.Giphy

Show TranslateResponse Source # 
Instance details

Defined in Web.Giphy

Generic TranslateResponse Source # 
Instance details

Defined in Web.Giphy

Associated Types

type Rep TranslateResponse :: Type -> Type #

FromJSON TranslateResponse Source # 
Instance details

Defined in Web.Giphy

type Rep TranslateResponse Source # 
Instance details

Defined in Web.Giphy

type Rep TranslateResponse = D1 (MetaData "TranslateResponse" "Web.Giphy" "giphy-api-0.7.0.0-GKIHg4B0k0i279jBFZMsh0" True) (C1 (MetaCons "TranslateResponse" PrefixI True) (S1 (MetaSel (Just "_translateItem") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Gif)))

newtype RandomResponse Source #

A single gif as part of a response.

Constructors

RandomResponse 

Fields

Instances
Eq RandomResponse Source # 
Instance details

Defined in Web.Giphy

Ord RandomResponse Source # 
Instance details

Defined in Web.Giphy

Show RandomResponse Source # 
Instance details

Defined in Web.Giphy

Generic RandomResponse Source # 
Instance details

Defined in Web.Giphy

Associated Types

type Rep RandomResponse :: Type -> Type #

FromJSON RandomResponse Source # 
Instance details

Defined in Web.Giphy

type Rep RandomResponse Source # 
Instance details

Defined in Web.Giphy

type Rep RandomResponse = D1 (MetaData "RandomResponse" "Web.Giphy" "giphy-api-0.7.0.0-GKIHg4B0k0i279jBFZMsh0" True) (C1 (MetaCons "RandomResponse" PrefixI True) (S1 (MetaSel (Just "_randomGifItem") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Gif)))

Giphy Monad

Use runGiphy to lift the Giphy monad into IO.

newtype GiphyConfig Source #

Contains the key to access the API.

Constructors

GiphyConfig 

Fields

Instances
Eq GiphyConfig Source # 
Instance details

Defined in Web.Giphy

Show GiphyConfig Source # 
Instance details

Defined in Web.Giphy

type Giphy = ReaderT GiphyContext ClientM Source #

The Giphy monad contains the execution context.

runGiphy :: MonadIO m => Giphy a -> GiphyConfig -> m (Either ClientError a) Source #

You need to provide a GiphyConfig to lift a Giphy computation into MonadIO.

runGiphy' Source #

Arguments

:: MonadIO m 
=> Manager

This must be a TLS-enabled Manager

-> Giphy a 
-> GiphyConfig 
-> m (Either ClientError a) 

Same as runGiphy but accepts an explicit Manager instead of implicitly creating one for you.

Lenses

You can use these lenses if you prefer them to manually accessing record fields.

API calls

Functions that directly access the Giphy API. All these functions run in the Giphy monad.

search :: Query -> Giphy SearchResponse Source #

Issue a search request for the given query without specifying an offset. E.g. https://api.giphy.com/v1/gifs/search?q=funny+cat&api_key=dc6zaTOxFJmzC

searchOffset Source #

Arguments

:: Query 
-> PaginationOffset

Offset as a number of items you want to skip.

-> Giphy SearchResponse 

Issue a search request for the given query by specifying a pagination offset. E.g. https://api.giphy.com/v1/gifs/search?q=funny+cat&api_key=dc6zaTOxFJmzC&offset=25

random :: Maybe Tag -> Giphy RandomResponse Source #

Issue a request for a random GIF for the given (optional) tag. E.g. https://api.giphy.com/v1/gifs/random?api_key=dc6zaTOxFJmzC&tag=american+psycho