liblastfm-0.7.0: Lastfm API interface

Safe HaskellNone
LanguageHaskell2010

Lastfm.Response

Contents

Description

Request sending and Response parsing

Synopsis

Compute request signature

The signature is required for every authenticated API request. Basically, every such request appends the md5 footprint of its arguments to the query as described at http://www.last.fm/api/authspec#8

newtype Secret Source #

Application secret

Constructors

Secret Text 
Instances
Eq Secret Source # 
Instance details

Defined in Lastfm.Response

Methods

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

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

Show Secret Source # 
Instance details

Defined in Lastfm.Response

IsString Secret Source # 
Instance details

Defined in Lastfm.Response

Methods

fromString :: String -> Secret #

sign :: Secret -> Request f Sign -> Request f Ready Source #

Sign the Request with the Secret so it's ready to be sent

Perform requests

data Connection Source #

Lastfm connection manager

withConnection :: MonadIO m => (Connection -> m a) -> m a Source #

Creating an HTTPS connection manager is expensive; it's advised to use a single Connection for all communications with last.fm

newConnection :: MonadIO m => m Connection Source #

Create a Connection. Note that there's no need to close the connection manually, as it will be closed automatically when no longer in use, that is, all the requests have been processed and it's about to be garbage collected.

lastfm :: Supported f r => Connection -> Request f Ready -> IO (Either LastfmError r) Source #

Perform the Request and parse the response

lastfm_ :: Supported f r => Connection -> Request f Ready -> IO (Either LastfmError ()) Source #

Perform the Request ignoring any responses

class Supported f r | f -> r, r -> f Source #

Supported provides parsing for the chosen Format

JSON is parsed to Value type from aeson, while XML is parsed to Document from xml-conduit

Minimal complete definition

prepareRequest, parseResponseBody, parseResponseEncodedError

data Format Source #

Response format: either JSON or XML

Constructors

JSON 
XML 

Errors

data LastfmError Source #

Different ways last.fm response can be unusable

Constructors

LastfmBadResponse ByteString

last.fm thinks it responded with something legible, but it really isn't

LastfmEncodedError Int Text

last.fm error code and message string

LastfmHttpError HttpException

wrapped http-conduit exception

Instances
Eq LastfmError Source #

Admittedly, this isn't the best Eq instance ever but not having Eq HttpException does not leave much a choice

Instance details

Defined in Lastfm.Response

Show LastfmError Source # 
Instance details

Defined in Lastfm.Response

Exception LastfmError Source # 
Instance details

Defined in Lastfm.Response

_LastfmBadResponse :: (Choice p, Applicative m, AsLastfmError e) => p ByteString (m ByteString) -> p e (m e) Source #

This is a Prism' LastfmError ByteString in disguise

_LastfmEncodedError :: (Choice p, Applicative m, AsLastfmError e) => p (Int, Text) (m (Int, Text)) -> p e (m e) Source #

This is a Prism' LastfmError (Int, String) in disguise

_LastfmHttpError :: (Choice p, Applicative m, AsLastfmError e) => p HttpException (m HttpException) -> p e (m e) Source #

This is a Prism' LastfmError HttpException in disguise