Safe Haskell | None |
---|
Response module
- type Lastfm a = IO (Either LastfmError a)
- type Response = ByteString
- data ResponseType
- callAPI :: ResponseType -> [(String, String)] -> Lastfm Response
- callAPIsigned :: ResponseType -> Secret -> [(String, String)] -> Lastfm Response
- xml :: [String] -> Q [Dec]
- json :: [String] -> Q [Dec]
- newtype Secret = Secret String
- newtype Album = Album String
- newtype AlbumArtist = AlbumArtist String
- newtype APIKey = APIKey String
- newtype Artist = Artist String
- newtype AuthToken = AuthToken String
- newtype Context = Context String
- newtype Country = Country String
- newtype Description = Description String
- newtype Group = Group String
- newtype Language = Language String
- newtype Latitude = Latitude String
- newtype Location = Location String
- newtype Longitude = Longitude String
- newtype Mbid = Mbid String
- newtype Message = Message String
- newtype Method = Method String
- newtype Metro = Metro String
- newtype Name = Name String
- newtype Recipient = Recipient String
- newtype SessionKey = SessionKey String
- newtype Station = Station String
- newtype StreamId = StreamId String
- newtype Tag = Tag String
- newtype TaggingType = TaggingType String
- newtype Title = Title String
- newtype Token = Token String
- newtype Track = Track String
- newtype User = User String
- newtype Username = Username String
- newtype Venuename = Venuename String
- newtype ChosenByUser = ChosenByUser String
- newtype Autocorrect = Autocorrect Bool
- newtype BuyLinks = BuyLinks Bool
- newtype Discovery = Discovery Bool
- newtype FestivalsOnly = FestivalsOnly Bool
- newtype Public = Public Bool
- newtype RecentTracks = RecentTracks Bool
- newtype RTP = RTP Bool
- newtype UseRecs = UseRecs Bool
- newtype Distance = Distance Int
- newtype Duration = Duration Int
- newtype Event = Event Int
- newtype Limit = Limit Int
- newtype Page = Page Int
- newtype Playlist = Playlist Int
- newtype TrackNumber = TrackNumber Int
- newtype Venue = Venue Int
- newtype End = End Integer
- newtype EndTimestamp = EndTimestamp Integer
- newtype Fingerprint = Fingerprint Integer
- newtype From = From Integer
- newtype Start = Start Integer
- newtype StartTimestamp = StartTimestamp Integer
- newtype Timestamp = Timestamp Integer
- newtype To = To Integer
- data Bitrate
- data Multiplier
- data Order
- = Popularity
- | DateAdded
- data Status
- data Value
- = ValueUser User
- | ValueArtists [Artist]
- data Period
- simple :: (FromJSON a, Monad m) => m ByteString -> m a
- class Argument a where
- (#) :: Argument a => a -> (String, String)
- boolToString :: Bool -> String
Documentation
type Response = ByteStringSource
Type synonym for Lastfm response
callAPI :: ResponseType -> [(String, String)] -> Lastfm ResponseSource
Low level function. Sends POST query to Lastfm API.
callAPIsigned :: ResponseType -> Secret -> [(String, String)] -> Lastfm ResponseSource
Low level function. Sends signed POST query to Lastfm API.
simple :: (FromJSON a, Monad m) => m ByteString -> m aSource
boolToString :: Bool -> StringSource