giphy-api-0.5.2.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 Tag Source #

A tag to retrieve a random GIF for.

Constructors

Tag Text 

data Pagination Source #

Metadata about pagination in a response.

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 # 

Methods

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

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

Ord Gif Source # 

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 # 

Methods

showsPrec :: Int -> Gif -> ShowS #

show :: Gif -> String #

showList :: [Gif] -> ShowS #

Generic Gif Source # 

Associated Types

type Rep Gif :: * -> * #

Methods

from :: Gif -> Rep Gif x #

to :: Rep Gif x -> Gif #

FromJSON Gif Source # 
type Rep Gif Source # 

data Image Source #

An image contained in a Giphy response.

Instances

Eq Image Source # 

Methods

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

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

Ord Image Source # 

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 # 

Methods

showsPrec :: Int -> Image -> ShowS #

show :: Image -> String #

showList :: [Image] -> ShowS #

Generic Image Source # 

Associated Types

type Rep Image :: * -> * #

Methods

from :: Image -> Rep Image x #

to :: Rep Image x -> Image #

FromJSON Image Source # 
type Rep Image Source # 

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.

newtype SingleGifResponse Source #

A single gif as part of a response.

Constructors

SingleGifResponse 

Fields

newtype TranslateResponse Source #

A single GIF as part of a translate response.

Constructors

TranslateResponse 

Fields

Giphy Monad

Use runGiphy to lift the Giphy monad into IO.

newtype GiphyConfig Source #

Contains the key to access the API.

Constructors

GiphyConfig 

Fields

type Giphy = ReaderT GiphyContext ClientM Source #

The Giphy monad contains the execution context.

runGiphy :: MonadIO m => Giphy a -> GiphyConfig -> m (Either ServantError 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 ServantError 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