Mercurial > hg > dml-open-cliopatria
view cpack/dml/lib/spotify/spotify.pl @ 0:718306e29690 tip
commiting public release
author | Daniel Wolff |
---|---|
date | Tue, 09 Feb 2016 21:05:06 +0100 |
parents | |
children |
line wrap: on
line source
/* Part of DML (Digital Music Laboratory) Copyright 2014-2015 Samer Abdallah, University of London This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2 of the License, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this library; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA */ :- module(spotify, [ spotify_authorise/1 , spotify_app/2 , spotify/2 , spotify_user/2 , spotify_search/4 , spotify_player//2 , spotify_player_url/3 ]). /** <module> Interface to Spotify Web API This module provides access to the Spotify web API. It uses dicts, but does not require the .field syntax to be enabled. https://developer.spotify.com/web-api/ */ :- use_module(library(http/http_dispatch)). :- use_module(library(http/thread_httpd)). :- use_module(library(http/http_parameters)). :- use_module(library(http/http_ssl_plugin)). :- use_module(library(http/html_write)). :- use_module(library(base64)). :- use_module(library(dcg_core)). :- use_module(library(webby)). :- use_module(library(insist)). :- use_module(library(state)). :- multifile app_facet/2. :- dynamic state/2. :- set_prolog_flag(double_quotes,string). :- http_handler(root(authorise), authorise, []). %% spotify_app(+App:ground, +Spec:list) is det. % % Declares App to be a registered Spotify application. Spec must contain contain % the following elements containing information obtained during the application % registration process. They can be atoms or strings. % * id(ClientID:text) % * secret(Secret:text) % * redirect(RedirectURL:text) % * scope(Scopes:text) % This can only be used as a directive, as the expansion process included declaring % an HTTP handler using http_handler/3.% spotify_app(_,_) :- throw(directive(spotify_app/2)). user:term_expansion((:- spotify_app(App,Props)), Clauses) :- !, Info=[id(_),secret(_),redirect(Redirect),scope(_)], maplist(spotify:option_inv(Props),Info), insist(url:parse_url(Redirect,Parts),bad_redirect(Redirect)), member(path(Path),Parts), seqmap(spotify:app_clause(App),Info,Clauses,[(:-http_handler(Path, spotify:callback(App), []))]). option_inv(Props,Prop) :- insist(option(Prop,Props),missing_app_facet(Prop)). app_clause(App,Prop) --> [spotify:app_facet(App,Prop)]. app_port(App,Port) :- app_facet(App,redirect(Redirect)), parse_url(Redirect,Parts), member(port(Port),Parts). %% spotify_authorise(+App) is det. % % Get authorisation for current app from a Spotify user. % This requires a working www_open_url to initiate an interaction with % the user to handle the Spotify login process. If this doesn't % work, consider changing the 'browser' Prolog flag. For example, % on Mac OS X, add the following to your ~/.plrc % == % :- set_prolog_flag(browser,open). % == % After logging in (if necessary) and authorising the app, the browser % should show a page confirming that the process succeeded and giving information % about the current user. This predicate (spotify_authorise/0) will wait % until the confirmation page has been shown. It may hang if something % goes wrong. spotify_authorise(App) :- get_time(Time), variant_sha1(App-Time,Hash), login_url(App,Hash,URL), app_port(App,Port), with_message_queue(spotify,[max_size(5)], with_http_server(Port, ( thread_send_message(spotify,login(App,Hash,URL)), print_message(information,spotify:auth_opening_browser(App,Port,URL)), www_open_url(URL), print_message(information,spotify:auth_waiting(App)), thread_get_message(spotify,cont(App,Hash,RC),[timeout(300)]), (RC=error(Ex) -> throw(Ex); true), print_message(information,spotify:auth_complete(App)) ))). with_http_server(Port,Goal) :- setup_call_cleanup( http_server(http_dispatch, [port(Port)]), Goal, http_stop_server(Port,[])). with_message_queue(Alias,Opts,Goal) :- setup_call_cleanup( message_queue_create(_,[alias(Alias)|Opts]), Goal, message_queue_destroy(Alias)). %% login_url(+App,+Hash,-URL) is det. login_url(App,Hash,URL) :- maplist(app_facet(App),[id(ID),redirect(Redirect),scope(Scope)]), Params=[ response_type=code,client_id=ID,scope=Scope, redirect_uri=Redirect, state=Hash ], parse_url(URL,[ protocol(https), host('accounts.spotify.com'), path('/authorize'), search(Params)]). %% authorise(Request) is det. % % Authorisation process via a web interface. authorise(Request) :- ( thread_peek_message(spotify,login(_,_,URL)) -> http_redirect(see_other,URL,Request) ; reply_html_page(default, [title("SWI Prolog Spotify client")], center(p("Nothing to see here. Move on.")))). %% callback(+App,+Request) is det. % % Handle the callback from Spotify as part of the authorisation process. % This handler must be registered with library(http_dispatch) associated % with 'redirect' URL property of the current app. callback(App,Request) :- http_parameters(Request,[ code(Code, [string, optional(true)]) , error(Error, [string, optional(true)]) , error_description(ErrorDesc, [string, optional(true)]) , state(Hash, [atom, optional(false)]) ]), debug(spotify,"Got callback (~w)",[Hash]), insist(thread_get_message(spotify,login(App,Hash,_),[timeout(0)]),no_matching_state), catch( ( insist(var(Error), auth_error(Error,ErrorDesc)), insist(nonvar(Code),no_code_received), maplist(app_facet(App),[id(ID),secret(Secret),redirect(Redirect)]), get_authorisation([ grant_type='authorization_code' , code=Code, redirect_uri=Redirect , client_id=ID, client_secret=Secret ], [], Reply), debug(spotify,"Received access and refresh tokens.",[]), debug(spotify,"Posting success to login queue ~w...",[Hash]), Status=ok(Reply) ), Ex, Status=error(Ex)), handle_auth_reply(Status,App,Hash). handle_auth_reply(ok(Reply),App,Hash) :- set_tokens(App,Reply), debug(spotify,"Posting success to login queue ~w...",[Hash]), thread_send_message(spotify,cont(App,Hash,ok)), spotify(App,me(Me)), is_dict(Me,user), set_state(user(App),Me), reply_html_page(default, [title("SWI-Prolog Spotify Client > Login ok")], [ \html_post(head,style( [ "table.json table.json { border: thin solid gray }" , "table.json { border-collapse: collapse }" , "table.json td:first-child { font-weight: bold; text-align: right; padding-right:0.5em }" , "table.json td { vertical-align:top; padding-left:0.5em }" , "body { margin:2em; }" ])) , center(div([h3("SWI Prolog library app '~w' authorised as user"-App), \json(Me) ])) ]). handle_auth_reply(error(Ex),App,Hash) :- debug(spotify,"Posting error to login queue ~w...",[Hash]), thread_send_message(spotify,cont(App,Hash,error(Ex))), ( Ex=http_bad_status(_,Doc), phrase("<!DOCTYPE html>",Doc,_) -> format("Content-type: text/html; charset=UTF-8~n~n~s",[Doc]) ; throw(Ex) ). %% refresh is det. % Refresh the access token for the current app. refresh(App) :- app_facet(App,id(ID)), app_facet(App,secret(Secret)), get_state(refresh_token(App),Token), format(codes(IDCodes),"~w:~w", [ID,Secret]), phrase(("Basic ",base64(IDCodes)),AuthCodes), string_codes(Auth,AuthCodes), % debug(spotify,"Refreshing access tokens...",[]), get_authorisation([grant_type=refresh_token, refresh_token=Token], [request_header('Authorization'=Auth)], Reply), debug(spotify,"Received new access tokens.",[]), set_tokens(App,Reply). %% set_tokens(+App,+Dict) is det. % Updates the record of the current access and refresh tokens, % and their new expiry time. set_tokens(App,Dict) :- _{expires_in:Expiry,access_token:Access} :< Dict, get_time(Now), ExpirationTime is Now+Expiry, set_state(access_token(App),Access-ExpirationTime), ( _{refresh_token:Refresh} :< Dict -> set_state(refresh_token(App),Refresh) ; true ). %% usable_token(+App,-Token) is det. % Gets a usable access token, refreshing if the current one expired. usable_token(App,Token) :- get_state(access_token(App),Token0-ExpiryDate), get_time(Now), ( ExpiryDate>Now -> Token=Token0 ; refresh(App), usable_token(App,Token) ). %% spotify_player(+URI:atom,+Opts:options) is det. % HTML component for showing the Spotify web widget. spotify_player_url(track(URI),Opts,URL) :- option(theme(Th),Opts,white), must_be(oneof([white,black]),Th), option(view(Vw),Opts,list), must_be(oneof([list,coverart]),Vw), parse_url(URL, [ protocol(https),host('embed.spotify.com'),path(/) , search([uri=URI, theme=Th, view=Vw]) ]). spotify_player_url(tracks(Title,URIs),Opts,URL) :- option(theme(Th),Opts,white), must_be(oneof([white,black]),Th), option(view(Vw),Opts,list), must_be(oneof([list,coverart]),Vw), maplist(string_concat('spotify:track:'),IDs,URIs), atomics_to_string(IDs,',',IDList), atomics_to_string([spotify,trackset,Title,IDList],':',URI), parse_url(URL, [ protocol(https),host('embed.spotify.com'),path(/) , search([uri=URI, theme=Th, view=Vw]) ]). spotify_player(Spec,Opts) --> { spotify_player_url(Spec,Opts,URL), option(width(W),Opts,300), must_be(between(250,640),W), option(height(H),Opts,300), must_be(between(80,720),H) }, html(iframe([ src=URL,width=W,height=H,frameborder=0,allowtransparency=true],[])). % multiple tracks: % uri='spotify:trackset:PREFEREDTITLE:5Z7ygHQo02SUrFmcgpwsKW,1x6ACsKV4UdWS2FMuPFUiT' json(Dict) --> {is_dict(Dict), !, dict_pairs(Dict,_,Pairs)}, html(table(class=json, [colgroup([col(style="border-right:thin solid black"),col([])]), \seqmap(pair_row,Pairs)])). json(List) --> {is_list(List)}, !, html(ol(\seqmap(val_li,List))). json(Val) --> html("~w"-Val). val_li(Val) --> html(li(\json(Val))). pair_row(Name-Val) --> html(tr( [ td(Name), td(\json(Val))])). %% spotify(+App,+Request) is nondet. % % This is the main predicate for making calls to the Spotify web API. The nature of % the call, its parameters, and its results are encoded in the term Request. % See request/4 for information about what requests are recognised. % This predicate will formulate the call URL, refresh the access token if necessary, % make the call, and read the results. spotify(App,Req) :- request(Req,PathPhrase,Method,Reader), !, phrase(PathPhrase,PathParts), parts_path([v1|PathParts],Path), usable_token(App,Token), string_concat("Bearer ", Token, Auth), spotify(Method,Reader,'api.spotify.com',Path, [ request_header('Authorization'=Auth) ]). % just for internal use get_authorisation(Params,Opts,Reply) :- spotify(post(form(Params)), json(Reply), 'accounts.spotify.com', '/api/token', Opts). % All web calls come through here eventually. spotify(Method,Reader,Host,Path,Opts) :- restcall(Method, Reader, [ protocol(https), host(Host), path(Path) ], [ request_header('Accept'='application/json') , cert_verify_hook(spotify:verify) | Opts ]). verify(_, Problem, _All, _First, Error) :- debug(ssl,"Accepting problem certificate (~w)\n~w\n",[Error,Problem]). %% request(-Req:spotify_request, -PathPhrase:phrase(atom), -Method:web_method, -Reader:web_reader) is nondet. % % Database of mappings from requests to end-points. request( me(Me), [me], get([]), json(Me)). request( track(TID,T), [tracks,TID], get([]), json(T)). request( playlists(UID,Ls), playlists(UID), get([]), json(Ls)). request( playlist(UID,PID,L), playlist(UID,PID), get([]), json(L)). request( playlist_tracks(UID,PID,Ts), tracks(UID,PID), get([]), json(Ts)). request( search(Type,Term,L), [search], get([(type)=Type,q=Term]), json(L)). request( create_playlist(UID,Name,PL), playlists(UID), post(json(_{name:Name})), json(PL)). request( add_tracks(UID,PID,URIs), tracks(UID,PID), post(json(URIs)), nil). request( set_tracks(UID,PID,URIs), tracks(UID,PID), put(json(_{uris:URIs})), nil). request( del_tracks(UID,PID,TIDs), tracks(UID,PID), delete(json(TIDs)), json(_)). % DCG for building paths as a list of atoms. playlist(UID,PID) --> playlists(UID), [PID]. playlists(UID) --> [users,UID,playlists]. tracks(UID,PID) --> playlist(UID,PID), [tracks]. spotify_user(App,Me) :- get_state(user(App),Me). spotify_search(App,Type,Term,Item) :- spotify(App,search(Type,Term,Response)), type_field(Type,Field), get_dict(Field,Response,Results), get_dict(items,Results,Items), member(Item,Items). type_field(artist,artists). type_field(track,tracks). type_field(album,albums). user:portray(Dict) :- is_dict(Dict), get_dict(uri,Dict,URI), ( get_dict(name,Dict,Name) -> format("<~s|~s>",[URI,Name]) ; format("<~s>",[URI]) ). prolog:message(directive(Pred)) --> ["~w can only be used as a directive."-[Pred]]. prolog:message(spotify:refreshing_token) --> ["Refreshing Spotify access token..."]. prolog:message(spotify:bad_redirect(R)) --> ["Malformed callback URI '~w'"-[R]]. prolog:message(spotify:missing_app_facet(P)) --> ["spotify_app declaration missing property ~w"-[P]]. prolog:message(spotify:no_matching_state) --> ["Authorisation synchronisation broken"]. prolog:message(spotify:no_code_received) --> ["No authorisation code received"]. prolog:message(spotify:auth_waiting(App)) --> ["Waiting for authorisation of ~w..."-[App]]. prolog:message(spotify:auth_complete(App)) --> ["Authorisation of ~w complete."-[App]]. prolog:message(spotify:auth_opening_browser(App,Port,_)) --> ["Authorising Spotify app ~w. "-[App]], ["Your browser should open automatically. If not, please open it manually and"], [" navigate to < http://localhost:~w/authorise >"-[Port]].