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