spotify-0.1.0.1: Spotify Web API
Safe HaskellSafe-Inferred
LanguageGHC2021

Spotify

Documentation

class MonadIO m => MonadSpotify m where Source #

Methods

getAuth :: m Auth Source #

getManager :: m Manager Source #

getToken :: m AccessToken Source #

putToken :: AccessToken -> m () Source #

throwClientError :: ClientError -> m a Source #

Instances

Instances details
MonadSpotify IO Source # 
Instance details

Defined in Spotify

MonadSpotify Spotify Source # 
Instance details

Defined in Spotify

newtype Spotify a Source #

Constructors

Spotify 

Fields

Instances

Instances details
MonadIO Spotify Source # 
Instance details

Defined in Spotify

Methods

liftIO :: IO a -> Spotify a #

Applicative Spotify Source # 
Instance details

Defined in Spotify

Methods

pure :: a -> Spotify a #

(<*>) :: Spotify (a -> b) -> Spotify a -> Spotify b #

liftA2 :: (a -> b -> c) -> Spotify a -> Spotify b -> Spotify c #

(*>) :: Spotify a -> Spotify b -> Spotify b #

(<*) :: Spotify a -> Spotify b -> Spotify a #

Functor Spotify Source # 
Instance details

Defined in Spotify

Methods

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

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

Monad Spotify Source # 
Instance details

Defined in Spotify

Methods

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

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

return :: a -> Spotify a #

MonadSpotify Spotify Source # 
Instance details

Defined in Spotify

MonadError ClientError Spotify Source # 
Instance details

Defined in Spotify

MonadState AccessToken Spotify Source # 
Instance details

Defined in Spotify

Methods

get :: Spotify AccessToken #

put :: AccessToken -> Spotify () #

state :: (AccessToken -> (a, AccessToken)) -> Spotify a #

MonadReader (Auth, Manager) Spotify Source # 
Instance details

Defined in Spotify

Methods

ask :: Spotify (Auth, Manager) #

local :: ((Auth, Manager) -> (Auth, Manager)) -> Spotify a -> Spotify a #

reader :: ((Auth, Manager) -> a) -> Spotify a #

runSpotify' :: Maybe Manager -> Maybe AccessToken -> Auth -> Spotify a -> IO (Either ClientError (a, AccessToken)) Source #

inSpot :: forall m a. MonadSpotify m => (AccessToken -> ClientM a) -> m a Source #

newtype Error' Source #

Constructors

Error' 

Fields

Instances

Instances details
FromJSON Error' Source # 
Instance details

Defined in Spotify

Generic Error' Source # 
Instance details

Defined in Spotify

Associated Types

type Rep Error' :: Type -> Type #

Methods

from :: Error' -> Rep Error' x #

to :: Rep Error' x -> Error' #

Show Error' Source # 
Instance details

Defined in Spotify

Eq Error' Source # 
Instance details

Defined in Spotify

Methods

(==) :: Error' -> Error' -> Bool #

(/=) :: Error' -> Error' -> Bool #

Ord Error' Source # 
Instance details

Defined in Spotify

type Rep Error' Source # 
Instance details

Defined in Spotify

type Rep Error' = D1 ('MetaData "Error'" "Spotify" "spotify-0.1.0.1-DSXk6mPWfQGGnICPbDr6pO" 'True) (C1 ('MetaCons "Error'" 'PrefixI 'True) (S1 ('MetaSel ('Just "error") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Error)))

data Auth Source #

Constructors

Auth 

Fields

Instances

Instances details
Show Auth Source # 
Instance details

Defined in Spotify

Methods

showsPrec :: Int -> Auth -> ShowS #

show :: Auth -> String #

showList :: [Auth] -> ShowS #

MonadReader (Auth, Manager) Spotify Source # 
Instance details

Defined in Spotify

Methods

ask :: Spotify (Auth, Manager) #

local :: ((Auth, Manager) -> (Auth, Manager)) -> Spotify a -> Spotify a #

reader :: ((Auth, Manager) -> a) -> Spotify a #

cli :: forall api. HasClient ClientM api => Client ClientM api Source #

noContent :: Functor f => f NoContent -> f () Source #

data PagingParams Source #

Constructors

PagingParams 

Fields

newToken :: MonadSpotify m => m TokenResponse Source #

newTokenIO :: Auth -> Manager -> IO (Either ClientError TokenResponse) Source #

newTokenIO' :: MonadIO m => Manager -> ClientId -> ClientSecret -> URL -> AuthCode -> m (Either ClientError TokenResponse') Source #

getAuthCodeInteractive :: ClientId -> URL -> Maybe (Set Scope) -> IO (Maybe AuthCode) Source #

authorizeUrl :: ClientId -> URL -> Maybe (Set Scope) -> URL Source #

getAlbum :: MonadSpotify m => AlbumID -> m Album Source #

getAlbumTracks :: MonadSpotify m => AlbumID -> PagingParams -> m (Paging TrackSimple) Source #

removeAlbums :: MonadSpotify m => [AlbumID] -> m () Source #

getArtist :: MonadSpotify m => ArtistID -> m Artist Source #

getTrack :: MonadSpotify m => TrackID -> m Track Source #

getSavedTracks :: MonadSpotify m => PagingParams -> m (Paging SavedTrack) Source #

saveTracks :: MonadSpotify m => [TrackID] -> m () Source #

removeTracks :: MonadSpotify m => [TrackID] -> m () Source #

search :: MonadSpotify m => Text -> [SearchType] -> Maybe Text -> Maybe Market -> PagingParams -> m SearchResult Source #

getMe :: MonadSpotify m => m User Source #

getUser :: MonadSpotify m => UserID -> m User Source #

unfollowPlaylist :: MonadSpotify m => PlaylistID -> m () Source #

getPlaylist :: MonadSpotify m => PlaylistID -> m Playlist Source #

addToPlaylist :: MonadSpotify m => PlaylistID -> Maybe Int -> [URI] -> m Text Source #

getMyPlaylists :: MonadSpotify m => PagingParams -> m (Paging PlaylistSimple) Source #

createPlaylist :: MonadSpotify m => UserID -> CreatePlaylistOpts -> m PlaylistSimple Source #

getCategories :: MonadSpotify m => CategoryID -> Maybe Country -> Maybe Locale -> m Category Source #

getPlaybackState :: MonadSpotify m => Maybe Market -> m PlaybackState Source #

transferPlayback :: MonadSpotify m => [DeviceID] -> Bool -> m () Source #

getCurrentlyPlayingTrack :: MonadSpotify m => Maybe Market -> m CurrentlyPlayingTrack Source #

pausePlayback :: MonadSpotify m => Maybe DeviceID -> m () Source #

skipToNext :: MonadSpotify m => Maybe DeviceID -> m () Source #

skipToPrevious :: MonadSpotify m => Maybe DeviceID -> m () Source #

seekToPosition :: MonadSpotify m => Int -> Maybe DeviceID -> m () Source #

allPages :: Monad m => Maybe (Paging a -> m Bool) -> (PagingParams -> m (Paging a)) -> m [a] Source #