comparison 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
comparison
equal deleted inserted replaced
-1:000000000000 0:718306e29690
1 /* Part of DML (Digital Music Laboratory)
2 Copyright 2014-2015 Samer Abdallah, University of London
3
4 This program is free software; you can redistribute it and/or
5 modify it under the terms of the GNU General Public License
6 as published by the Free Software Foundation; either version 2
7 of the License, or (at your option) any later version.
8
9 This program is distributed in the hope that it will be useful,
10 but WITHOUT ANY WARRANTY; without even the implied warranty of
11 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
12 GNU General Public License for more details.
13
14 You should have received a copy of the GNU General Public
15 License along with this library; if not, write to the Free Software
16 Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA
17 */
18
19 :- module(spotify,
20 [ spotify_authorise/1
21 , spotify_app/2
22 , spotify/2
23 , spotify_user/2
24 , spotify_search/4
25 , spotify_player//2
26 , spotify_player_url/3
27 ]).
28
29 /** <module> Interface to Spotify Web API
30
31 This module provides access to the Spotify web API.
32 It uses dicts, but does not require the .field syntax to be enabled.
33
34 https://developer.spotify.com/web-api/
35
36 */
37
38 :- use_module(library(http/http_dispatch)).
39 :- use_module(library(http/thread_httpd)).
40 :- use_module(library(http/http_parameters)).
41 :- use_module(library(http/http_ssl_plugin)).
42 :- use_module(library(http/html_write)).
43 :- use_module(library(base64)).
44 :- use_module(library(dcg_core)).
45 :- use_module(library(webby)).
46 :- use_module(library(insist)).
47 :- use_module(library(state)).
48
49 :- multifile app_facet/2.
50 :- dynamic state/2.
51 :- set_prolog_flag(double_quotes,string).
52
53 :- http_handler(root(authorise), authorise, []).
54
55 %% spotify_app(+App:ground, +Spec:list) is det.
56 %
57 % Declares App to be a registered Spotify application. Spec must contain contain
58 % the following elements containing information obtained during the application
59 % registration process. They can be atoms or strings.
60 % * id(ClientID:text)
61 % * secret(Secret:text)
62 % * redirect(RedirectURL:text)
63 % * scope(Scopes:text)
64 % This can only be used as a directive, as the expansion process included declaring
65 % an HTTP handler using http_handler/3.%
66 spotify_app(_,_) :- throw(directive(spotify_app/2)).
67
68 user:term_expansion((:- spotify_app(App,Props)), Clauses) :- !,
69 Info=[id(_),secret(_),redirect(Redirect),scope(_)],
70 maplist(spotify:option_inv(Props),Info),
71 insist(url:parse_url(Redirect,Parts),bad_redirect(Redirect)),
72 member(path(Path),Parts),
73 seqmap(spotify:app_clause(App),Info,Clauses,[(:-http_handler(Path, spotify:callback(App), []))]).
74
75 option_inv(Props,Prop) :- insist(option(Prop,Props),missing_app_facet(Prop)).
76 app_clause(App,Prop) --> [spotify:app_facet(App,Prop)].
77
78 app_port(App,Port) :-
79 app_facet(App,redirect(Redirect)),
80 parse_url(Redirect,Parts),
81 member(port(Port),Parts).
82
83
84 %% spotify_authorise(+App) is det.
85 %
86 % Get authorisation for current app from a Spotify user.
87 % This requires a working www_open_url to initiate an interaction with
88 % the user to handle the Spotify login process. If this doesn't
89 % work, consider changing the 'browser' Prolog flag. For example,
90 % on Mac OS X, add the following to your ~/.plrc
91 % ==
92 % :- set_prolog_flag(browser,open).
93 % ==
94 % After logging in (if necessary) and authorising the app, the browser
95 % should show a page confirming that the process succeeded and giving information
96 % about the current user. This predicate (spotify_authorise/0) will wait
97 % until the confirmation page has been shown. It may hang if something
98 % goes wrong.
99 spotify_authorise(App) :-
100 get_time(Time), variant_sha1(App-Time,Hash),
101 login_url(App,Hash,URL),
102 app_port(App,Port),
103 with_message_queue(spotify,[max_size(5)],
104 with_http_server(Port,
105 ( thread_send_message(spotify,login(App,Hash,URL)),
106 print_message(information,spotify:auth_opening_browser(App,Port,URL)),
107 www_open_url(URL),
108 print_message(information,spotify:auth_waiting(App)),
109 thread_get_message(spotify,cont(App,Hash,RC),[timeout(300)]),
110 (RC=error(Ex) -> throw(Ex); true),
111 print_message(information,spotify:auth_complete(App))
112 ))).
113
114
115 with_http_server(Port,Goal) :-
116 setup_call_cleanup(
117 http_server(http_dispatch, [port(Port)]), Goal,
118 http_stop_server(Port,[])).
119
120 with_message_queue(Alias,Opts,Goal) :-
121 setup_call_cleanup(
122 message_queue_create(_,[alias(Alias)|Opts]), Goal,
123 message_queue_destroy(Alias)).
124
125 %% login_url(+App,+Hash,-URL) is det.
126 login_url(App,Hash,URL) :-
127 maplist(app_facet(App),[id(ID),redirect(Redirect),scope(Scope)]),
128 Params=[ response_type=code,client_id=ID,scope=Scope, redirect_uri=Redirect, state=Hash ],
129 parse_url(URL,[ protocol(https), host('accounts.spotify.com'), path('/authorize'), search(Params)]).
130
131
132 %% authorise(Request) is det.
133 %
134 % Authorisation process via a web interface.
135 authorise(Request) :-
136 ( thread_peek_message(spotify,login(_,_,URL))
137 -> http_redirect(see_other,URL,Request)
138 ; reply_html_page(default, [title("SWI Prolog Spotify client")],
139 center(p("Nothing to see here. Move on.")))).
140
141
142 %% callback(+App,+Request) is det.
143 %
144 % Handle the callback from Spotify as part of the authorisation process.
145 % This handler must be registered with library(http_dispatch) associated
146 % with 'redirect' URL property of the current app.
147 callback(App,Request) :-
148 http_parameters(Request,[ code(Code, [string, optional(true)])
149 , error(Error, [string, optional(true)])
150 , error_description(ErrorDesc, [string, optional(true)])
151 , state(Hash, [atom, optional(false)]) ]),
152 debug(spotify,"Got callback (~w)",[Hash]),
153 insist(thread_get_message(spotify,login(App,Hash,_),[timeout(0)]),no_matching_state),
154
155 catch(
156 ( insist(var(Error), auth_error(Error,ErrorDesc)),
157 insist(nonvar(Code),no_code_received),
158 maplist(app_facet(App),[id(ID),secret(Secret),redirect(Redirect)]),
159 get_authorisation([ grant_type='authorization_code'
160 , code=Code, redirect_uri=Redirect
161 , client_id=ID, client_secret=Secret
162 ], [], Reply),
163 debug(spotify,"Received access and refresh tokens.",[]),
164 debug(spotify,"Posting success to login queue ~w...",[Hash]),
165 Status=ok(Reply)
166 ), Ex, Status=error(Ex)),
167 handle_auth_reply(Status,App,Hash).
168
169 handle_auth_reply(ok(Reply),App,Hash) :-
170 set_tokens(App,Reply),
171 debug(spotify,"Posting success to login queue ~w...",[Hash]),
172 thread_send_message(spotify,cont(App,Hash,ok)),
173 spotify(App,me(Me)), is_dict(Me,user),
174 set_state(user(App),Me),
175 reply_html_page(default,
176 [title("SWI-Prolog Spotify Client > Login ok")],
177 [ \html_post(head,style(
178 [ "table.json table.json { border: thin solid gray }"
179 , "table.json { border-collapse: collapse }"
180 , "table.json td:first-child { font-weight: bold; text-align: right; padding-right:0.5em }"
181 , "table.json td { vertical-align:top; padding-left:0.5em }"
182 , "body { margin:2em; }"
183 ]))
184 , center(div([h3("SWI Prolog library app '~w' authorised as user"-App), \json(Me) ]))
185 ]).
186
187 handle_auth_reply(error(Ex),App,Hash) :-
188 debug(spotify,"Posting error to login queue ~w...",[Hash]),
189 thread_send_message(spotify,cont(App,Hash,error(Ex))),
190 ( Ex=http_bad_status(_,Doc), phrase("<!DOCTYPE html>",Doc,_)
191 -> format("Content-type: text/html; charset=UTF-8~n~n~s",[Doc])
192 ; throw(Ex)
193 ).
194
195 %% refresh is det.
196 % Refresh the access token for the current app.
197 refresh(App) :-
198 app_facet(App,id(ID)),
199 app_facet(App,secret(Secret)),
200 get_state(refresh_token(App),Token),
201 format(codes(IDCodes),"~w:~w", [ID,Secret]),
202 phrase(("Basic ",base64(IDCodes)),AuthCodes),
203 string_codes(Auth,AuthCodes),
204 % debug(spotify,"Refreshing access tokens...",[]),
205 get_authorisation([grant_type=refresh_token, refresh_token=Token],
206 [request_header('Authorization'=Auth)], Reply),
207 debug(spotify,"Received new access tokens.",[]),
208 set_tokens(App,Reply).
209
210 %% set_tokens(+App,+Dict) is det.
211 % Updates the record of the current access and refresh tokens,
212 % and their new expiry time.
213 set_tokens(App,Dict) :-
214 _{expires_in:Expiry,access_token:Access} :< Dict,
215 get_time(Now), ExpirationTime is Now+Expiry,
216 set_state(access_token(App),Access-ExpirationTime),
217 ( _{refresh_token:Refresh} :< Dict
218 -> set_state(refresh_token(App),Refresh)
219 ; true
220 ).
221
222 %% usable_token(+App,-Token) is det.
223 % Gets a usable access token, refreshing if the current one expired.
224 usable_token(App,Token) :-
225 get_state(access_token(App),Token0-ExpiryDate),
226 get_time(Now),
227 ( ExpiryDate>Now -> Token=Token0
228 ; refresh(App), usable_token(App,Token)
229 ).
230
231 %% spotify_player(+URI:atom,+Opts:options) is det.
232 % HTML component for showing the Spotify web widget.
233 spotify_player_url(track(URI),Opts,URL) :-
234 option(theme(Th),Opts,white), must_be(oneof([white,black]),Th),
235 option(view(Vw),Opts,list), must_be(oneof([list,coverart]),Vw),
236 parse_url(URL, [ protocol(https),host('embed.spotify.com'),path(/)
237 , search([uri=URI, theme=Th, view=Vw]) ]).
238
239 spotify_player_url(tracks(Title,URIs),Opts,URL) :-
240 option(theme(Th),Opts,white), must_be(oneof([white,black]),Th),
241 option(view(Vw),Opts,list), must_be(oneof([list,coverart]),Vw),
242 maplist(string_concat('spotify:track:'),IDs,URIs),
243 atomics_to_string(IDs,',',IDList),
244 atomics_to_string([spotify,trackset,Title,IDList],':',URI),
245 parse_url(URL, [ protocol(https),host('embed.spotify.com'),path(/)
246 , search([uri=URI, theme=Th, view=Vw]) ]).
247
248 spotify_player(Spec,Opts) -->
249 { spotify_player_url(Spec,Opts,URL),
250 option(width(W),Opts,300), must_be(between(250,640),W),
251 option(height(H),Opts,300), must_be(between(80,720),H)
252 },
253 html(iframe([ src=URL,width=W,height=H,frameborder=0,allowtransparency=true],[])).
254
255 % multiple tracks:
256 % uri='spotify:trackset:PREFEREDTITLE:5Z7ygHQo02SUrFmcgpwsKW,1x6ACsKV4UdWS2FMuPFUiT'
257 json(Dict) -->
258 {is_dict(Dict), !, dict_pairs(Dict,_,Pairs)},
259 html(table(class=json,
260 [colgroup([col(style="border-right:thin solid black"),col([])]), \seqmap(pair_row,Pairs)])).
261 json(List) --> {is_list(List)}, !, html(ol(\seqmap(val_li,List))).
262 json(Val) --> html("~w"-Val).
263 val_li(Val) --> html(li(\json(Val))).
264 pair_row(Name-Val) --> html(tr( [ td(Name), td(\json(Val))])).
265
266 %% spotify(+App,+Request) is nondet.
267 %
268 % This is the main predicate for making calls to the Spotify web API. The nature of
269 % the call, its parameters, and its results are encoded in the term Request.
270 % See request/4 for information about what requests are recognised.
271 % This predicate will formulate the call URL, refresh the access token if necessary,
272 % make the call, and read the results.
273 spotify(App,Req) :-
274 request(Req,PathPhrase,Method,Reader), !,
275 phrase(PathPhrase,PathParts),
276 parts_path([v1|PathParts],Path),
277 usable_token(App,Token),
278 string_concat("Bearer ", Token, Auth),
279 spotify(Method,Reader,'api.spotify.com',Path,
280 [ request_header('Authorization'=Auth) ]).
281
282 % just for internal use
283 get_authorisation(Params,Opts,Reply) :-
284 spotify(post(form(Params)), json(Reply), 'accounts.spotify.com', '/api/token', Opts).
285
286 % All web calls come through here eventually.
287 spotify(Method,Reader,Host,Path,Opts) :-
288 restcall(Method, Reader,
289 [ protocol(https), host(Host), path(Path) ],
290 [ request_header('Accept'='application/json')
291 , cert_verify_hook(spotify:verify)
292 | Opts ]).
293
294 verify(_, Problem, _All, _First, Error) :-
295 debug(ssl,"Accepting problem certificate (~w)\n~w\n",[Error,Problem]).
296
297 %% request(-Req:spotify_request, -PathPhrase:phrase(atom), -Method:web_method, -Reader:web_reader) is nondet.
298 %
299 % Database of mappings from requests to end-points.
300 request( me(Me), [me], get([]), json(Me)).
301 request( track(TID,T), [tracks,TID], get([]), json(T)).
302 request( playlists(UID,Ls), playlists(UID), get([]), json(Ls)).
303 request( playlist(UID,PID,L), playlist(UID,PID), get([]), json(L)).
304 request( playlist_tracks(UID,PID,Ts), tracks(UID,PID), get([]), json(Ts)).
305 request( search(Type,Term,L), [search], get([(type)=Type,q=Term]), json(L)).
306 request( create_playlist(UID,Name,PL), playlists(UID), post(json(_{name:Name})), json(PL)).
307 request( add_tracks(UID,PID,URIs), tracks(UID,PID), post(json(URIs)), nil).
308 request( set_tracks(UID,PID,URIs), tracks(UID,PID), put(json(_{uris:URIs})), nil).
309 request( del_tracks(UID,PID,TIDs), tracks(UID,PID), delete(json(TIDs)), json(_)).
310
311 % DCG for building paths as a list of atoms.
312 playlist(UID,PID) --> playlists(UID), [PID].
313 playlists(UID) --> [users,UID,playlists].
314 tracks(UID,PID) --> playlist(UID,PID), [tracks].
315
316 spotify_user(App,Me) :- get_state(user(App),Me).
317
318 spotify_search(App,Type,Term,Item) :-
319 spotify(App,search(Type,Term,Response)),
320 type_field(Type,Field),
321 get_dict(Field,Response,Results),
322 get_dict(items,Results,Items),
323 member(Item,Items).
324
325 type_field(artist,artists).
326 type_field(track,tracks).
327 type_field(album,albums).
328
329 user:portray(Dict) :-
330 is_dict(Dict),
331 get_dict(uri,Dict,URI),
332 ( get_dict(name,Dict,Name)
333 -> format("<~s|~s>",[URI,Name])
334 ; format("<~s>",[URI])
335 ).
336
337 prolog:message(directive(Pred)) --> ["~w can only be used as a directive."-[Pred]].
338 prolog:message(spotify:refreshing_token) --> ["Refreshing Spotify access token..."].
339 prolog:message(spotify:bad_redirect(R)) --> ["Malformed callback URI '~w'"-[R]].
340 prolog:message(spotify:missing_app_facet(P)) --> ["spotify_app declaration missing property ~w"-[P]].
341 prolog:message(spotify:no_matching_state) --> ["Authorisation synchronisation broken"].
342 prolog:message(spotify:no_code_received) --> ["No authorisation code received"].
343 prolog:message(spotify:auth_waiting(App)) --> ["Waiting for authorisation of ~w..."-[App]].
344 prolog:message(spotify:auth_complete(App)) --> ["Authorisation of ~w complete."-[App]].
345 prolog:message(spotify:auth_opening_browser(App,Port,_)) -->
346 ["Authorising Spotify app ~w. "-[App]],
347 ["Your browser should open automatically. If not, please open it manually and"],
348 [" navigate to < http://localhost:~w/authorise >"-[Port]].