daniel@53
|
1 /* Part of SWI-Prolog
|
daniel@53
|
2
|
daniel@53
|
3 Author: Jan Wielemaker
|
daniel@53
|
4 E-mail: J.Wielemaker@cs.vu.nl
|
daniel@53
|
5 WWW: http://www.swi-prolog.org
|
daniel@53
|
6 Copyright (C): 2007-2013, University of Amsterdam,
|
daniel@53
|
7 VU University Amsterdam
|
daniel@53
|
8
|
daniel@53
|
9 This program is free software; you can redistribute it and/or
|
daniel@53
|
10 modify it under the terms of the GNU General Public License
|
daniel@53
|
11 as published by the Free Software Foundation; either version 2
|
daniel@53
|
12 of the License, or (at your option) any later version.
|
daniel@53
|
13
|
daniel@53
|
14 This program is distributed in the hope that it will be useful,
|
daniel@53
|
15 but WITHOUT ANY WARRANTY; without even the implied warranty of
|
daniel@53
|
16 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
|
daniel@53
|
17 GNU General Public License for more details.
|
daniel@53
|
18
|
daniel@53
|
19 You should have received a copy of the GNU Lesser General Public
|
daniel@53
|
20 License along with this library; if not, write to the Free Software
|
daniel@53
|
21 Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA
|
daniel@53
|
22
|
daniel@53
|
23 As a special exception, if you link this library with other files,
|
daniel@53
|
24 compiled with a Free Software compiler, to produce an executable, this
|
daniel@53
|
25 library does not by itself cause the resulting executable to be covered
|
daniel@53
|
26 by the GNU General Public License. This exception does not however
|
daniel@53
|
27 invalidate any other reasons why the executable file might be covered by
|
daniel@53
|
28 the GNU General Public License.
|
daniel@53
|
29 */
|
daniel@53
|
30
|
daniel@53
|
31 :- module(http_openid,
|
daniel@53
|
32 [ openid_login/1, % +OpenID
|
daniel@53
|
33 openid_logout/1, % +OpenID
|
daniel@53
|
34 openid_logged_in/1, % -OpenID
|
daniel@53
|
35
|
daniel@53
|
36 % transparent login
|
daniel@53
|
37 openid_user/3, % +Request, -User, +Options
|
daniel@53
|
38
|
daniel@53
|
39 % low-level primitives
|
daniel@53
|
40 openid_verify/2, % +Options, +Request
|
daniel@53
|
41 openid_authenticate/4, % +Request, -Server, -Identity, -ReturnTo
|
daniel@53
|
42 openid_associate/3, % +OpenIDServer, -Handle, -Association
|
daniel@53
|
43 openid_associate/4, % +OpenIDServer, -Handle, -Association,
|
daniel@53
|
44 % +Options
|
daniel@53
|
45 openid_server/2, % +Options, +Request
|
daniel@53
|
46 openid_server/3, % ?OpenIDLogin, ?OpenID, ?Server
|
daniel@53
|
47 openid_grant/1, % +Request
|
daniel@53
|
48
|
daniel@53
|
49 openid_login_form//2, % +ReturnTo, +Options, //
|
daniel@53
|
50
|
daniel@53
|
51 openid_current_url/2, % +Request, -URL
|
daniel@53
|
52 openid_current_host/3 % +Request, -Host, -Port
|
daniel@53
|
53 ]).
|
daniel@53
|
54 :- use_module(library(http/http_open)).
|
daniel@53
|
55 :- use_module(library(http/html_write)).
|
daniel@53
|
56 :- use_module(library(http/http_parameters)).
|
daniel@53
|
57 :- use_module(library(http/http_dispatch)).
|
daniel@53
|
58 :- use_module(library(http/http_session)).
|
daniel@53
|
59 :- use_module(library(http/http_host)).
|
daniel@53
|
60 :- use_module(library(http/http_path)).
|
daniel@53
|
61 :- use_module(library(http/html_head)).
|
daniel@53
|
62 :- use_module(library(http/http_server_files), []).
|
daniel@53
|
63 :- use_module(library(http/yadis)).
|
daniel@53
|
64 :- use_module(library(http/ax)).
|
daniel@53
|
65 :- use_module(library(utf8)).
|
daniel@53
|
66 :- use_module(library(error)).
|
daniel@53
|
67 :- use_module(library(xpath)).
|
daniel@53
|
68 :- use_module(library(sgml)).
|
daniel@53
|
69 :- use_module(library(uri)).
|
daniel@53
|
70 :- use_module(library(occurs)).
|
daniel@53
|
71 :- use_module(library(base64)).
|
daniel@53
|
72 :- use_module(library(debug)).
|
daniel@53
|
73 :- use_module(library(record)).
|
daniel@53
|
74 :- use_module(library(option)).
|
daniel@53
|
75 :- use_module(library(sha)).
|
daniel@53
|
76 :- use_module(library(lists)).
|
daniel@53
|
77 :- use_module(library(settings)).
|
daniel@53
|
78
|
daniel@53
|
79 :- predicate_options(openid_login_form/4, 2,
|
daniel@53
|
80 [ action(atom),
|
daniel@53
|
81 buttons(list),
|
daniel@53
|
82 show_stay(boolean)
|
daniel@53
|
83 ]).
|
daniel@53
|
84 :- predicate_options(openid_server/2, 1,
|
daniel@53
|
85 [ expires_in(any)
|
daniel@53
|
86 ]).
|
daniel@53
|
87 :- predicate_options(openid_user/3, 3,
|
daniel@53
|
88 [ login_url(atom)
|
daniel@53
|
89 ]).
|
daniel@53
|
90 :- predicate_options(openid_verify/2, 1,
|
daniel@53
|
91 [ return_to(atom),
|
daniel@53
|
92 trust_root(atom),
|
daniel@53
|
93 realm(atom),
|
daniel@53
|
94 ax(any)
|
daniel@53
|
95 ]).
|
daniel@53
|
96
|
daniel@53
|
97 /** <module> OpenID consumer and server library
|
daniel@53
|
98
|
daniel@53
|
99 This library implements the OpenID protocol (http://openid.net/). OpenID
|
daniel@53
|
100 is a protocol to share identities on the network. The protocol itself
|
daniel@53
|
101 uses simple basic HTTP, adding reliability using digitally signed
|
daniel@53
|
102 messages.
|
daniel@53
|
103
|
daniel@53
|
104 Steps, as seen from the _consumer_ (or _|relying partner|_).
|
daniel@53
|
105
|
daniel@53
|
106 1. Show login form, asking for =openid_identifier=
|
daniel@53
|
107 2. Get HTML page from =openid_identifier= and lookup
|
daniel@53
|
108 =|<link rel="openid.server" href="server">|=
|
daniel@53
|
109 3. Associate to _server_
|
daniel@53
|
110 4. Redirect browser (302) to server using mode =checkid_setup=,
|
daniel@53
|
111 asking to validate the given OpenID.
|
daniel@53
|
112 5. OpenID server redirects back, providing digitally signed
|
daniel@53
|
113 conformation of the claimed identity.
|
daniel@53
|
114 6. Validate signature and redirect to the target location.
|
daniel@53
|
115
|
daniel@53
|
116 A *consumer* (an application that allows OpenID login) typically uses
|
daniel@53
|
117 this library through openid_user/3. In addition, it must implement the
|
daniel@53
|
118 hook http_openid:openid_hook(trusted(OpenId, Server)) to define accepted
|
daniel@53
|
119 OpenID servers. Typically, this hook is used to provide a white-list of
|
daniel@53
|
120 aceptable servers. Note that accepting any OpenID server is possible,
|
daniel@53
|
121 but anyone on the internet can setup a dummy OpenID server that simply
|
daniel@53
|
122 grants and signs every request. Here is an example:
|
daniel@53
|
123
|
daniel@53
|
124 ==
|
daniel@53
|
125 :- multifile http_openid:openid_hook/1.
|
daniel@53
|
126
|
daniel@53
|
127 http_openid:openid_hook(trusted(_, OpenIdServer)) :-
|
daniel@53
|
128 ( trusted_server(OpenIdServer)
|
daniel@53
|
129 -> true
|
daniel@53
|
130 ; throw(http_reply(moved_temporary('/openid/trustedservers')))
|
daniel@53
|
131 ).
|
daniel@53
|
132
|
daniel@53
|
133 trusted_server('http://www.myopenid.com/server').
|
daniel@53
|
134 ==
|
daniel@53
|
135
|
daniel@53
|
136 By default, information who is logged on is maintained with the session
|
daniel@53
|
137 using http_session_assert/1 with the term openid(Identity). The hooks
|
daniel@53
|
138 login/logout/logged_in can be used to provide alternative administration
|
daniel@53
|
139 of logged-in users (e.g., based on client-IP, using cookies, etc.).
|
daniel@53
|
140
|
daniel@53
|
141 To create a *server*, you must do four things: bind the handlers
|
daniel@53
|
142 openid_server/2 and openid_grant/1 to HTTP locations, provide a
|
daniel@53
|
143 user-page for registered users and define the grant(Request, Options)
|
daniel@53
|
144 hook to verify your users. An example server is provided in in
|
daniel@53
|
145 <plbase>/doc/packages/examples/demo_openid.pl
|
daniel@53
|
146 */
|
daniel@53
|
147
|
daniel@53
|
148 /*******************************
|
daniel@53
|
149 * CONFIGURATION *
|
daniel@53
|
150 *******************************/
|
daniel@53
|
151
|
daniel@53
|
152 http:location(openid, root(openid), [priority(-100)]).
|
daniel@53
|
153
|
daniel@53
|
154 %% openid_hook(+Action)
|
daniel@53
|
155 %
|
daniel@53
|
156 % Call hook on the OpenID management library. Defined hooks are:
|
daniel@53
|
157 %
|
daniel@53
|
158 % * login(+OpenID)
|
daniel@53
|
159 % Consider OpenID logged in.
|
daniel@53
|
160 %
|
daniel@53
|
161 % * logout(+OpenID)
|
daniel@53
|
162 % Logout OpenID
|
daniel@53
|
163 %
|
daniel@53
|
164 % * logged_in(?OpenID)
|
daniel@53
|
165 % True if OpenID is logged in
|
daniel@53
|
166 %
|
daniel@53
|
167 % * grant(+Request, +Options)
|
daniel@53
|
168 % Server: Reply positive on OpenID
|
daniel@53
|
169 %
|
daniel@53
|
170 % * trusted(+OpenID, +Server)
|
daniel@53
|
171 % True if Server is a trusted OpenID server
|
daniel@53
|
172 %
|
daniel@53
|
173 % * ax(Values)
|
daniel@53
|
174 % Called if the server provided AX attributes
|
daniel@53
|
175 %
|
daniel@53
|
176 % * x_parameter(+Server, -Name, -Value)
|
daniel@53
|
177 % Called to find additional HTTP parameters to send with the
|
daniel@53
|
178 % OpenID verify request.
|
daniel@53
|
179
|
daniel@53
|
180 :- multifile
|
daniel@53
|
181 openid_hook/1. % +Action
|
daniel@53
|
182
|
daniel@53
|
183 /*******************************
|
daniel@53
|
184 * DIRECT LOGIN/OUT *
|
daniel@53
|
185 *******************************/
|
daniel@53
|
186
|
daniel@53
|
187 %% openid_login(+OpenID) is det.
|
daniel@53
|
188 %
|
daniel@53
|
189 % Associate the current HTTP session with OpenID. If another
|
daniel@53
|
190 % OpenID is already associated, this association is first removed.
|
daniel@53
|
191
|
daniel@53
|
192 openid_login(OpenID) :-
|
daniel@53
|
193 openid_hook(login(OpenID)), !,
|
daniel@53
|
194 handle_stay_signed_in(OpenID).
|
daniel@53
|
195 openid_login(OpenID) :-
|
daniel@53
|
196 openid_logout(_),
|
daniel@53
|
197 http_session_assert(openid(OpenID)),
|
daniel@53
|
198 handle_stay_signed_in(OpenID).
|
daniel@53
|
199
|
daniel@53
|
200 %% openid_logout(+OpenID) is det.
|
daniel@53
|
201 %
|
daniel@53
|
202 % Remove the association of the current session with any OpenID
|
daniel@53
|
203
|
daniel@53
|
204 openid_logout(OpenID) :-
|
daniel@53
|
205 openid_hook(logout(OpenID)), !.
|
daniel@53
|
206 openid_logout(OpenID) :-
|
daniel@53
|
207 http_session_retractall(openid(OpenID)).
|
daniel@53
|
208
|
daniel@53
|
209 %% openid_logged_in(-OpenID) is semidet.
|
daniel@53
|
210 %
|
daniel@53
|
211 % True if session is associated with OpenID.
|
daniel@53
|
212
|
daniel@53
|
213 openid_logged_in(OpenID) :-
|
daniel@53
|
214 openid_hook(logged_in(OpenID)), !.
|
daniel@53
|
215 openid_logged_in(OpenID) :-
|
daniel@53
|
216 http_in_session(_SessionId), % test in session
|
daniel@53
|
217 http_session_data(openid(OpenID)).
|
daniel@53
|
218
|
daniel@53
|
219
|
daniel@53
|
220 /*******************************
|
daniel@53
|
221 * TOPLEVEL *
|
daniel@53
|
222 *******************************/
|
daniel@53
|
223
|
daniel@53
|
224 %% openid_user(+Request:http_request, -OpenID:url, +Options) is det.
|
daniel@53
|
225 %
|
daniel@53
|
226 % True if OpenID is a validated OpenID associated with the current
|
daniel@53
|
227 % session. The scenario for which this predicate is designed is to
|
daniel@53
|
228 % allow an HTTP handler that requires a valid login to
|
daniel@53
|
229 % use the transparent code below.
|
daniel@53
|
230 %
|
daniel@53
|
231 % ==
|
daniel@53
|
232 % handler(Request) :-
|
daniel@53
|
233 % openid_user(Request, OpenID, []),
|
daniel@53
|
234 % ...
|
daniel@53
|
235 % ==
|
daniel@53
|
236 %
|
daniel@53
|
237 % If the user is not yet logged on a sequence of redirects will
|
daniel@53
|
238 % follow:
|
daniel@53
|
239 %
|
daniel@53
|
240 % 1. Show a page for login (default: page /openid/login),
|
daniel@53
|
241 % predicate reply_openid_login/1)
|
daniel@53
|
242 % 2. By default, the OpenID login page is a form that is
|
daniel@53
|
243 % submitted to the =verify=, which calls openid_verify/2.
|
daniel@53
|
244 % 3. openid_verify/2 does the following:
|
daniel@53
|
245 % - Find the OpenID claimed identity and server
|
daniel@53
|
246 % - Associate to the OpenID server
|
daniel@53
|
247 % - redirects to the OpenID server for validation
|
daniel@53
|
248 % 4. The OpenID server will redirect here with the authetication
|
daniel@53
|
249 % information. This is handled by openid_authenticate/4.
|
daniel@53
|
250 %
|
daniel@53
|
251 % Options:
|
daniel@53
|
252 %
|
daniel@53
|
253 % * login_url(Login)
|
daniel@53
|
254 % (Local) URL of page to enter OpenID information. Default
|
daniel@53
|
255 % is the handler for openid_login_page/1
|
daniel@53
|
256 %
|
daniel@53
|
257 % @see openid_authenticate/4 produces errors if login is invalid
|
daniel@53
|
258 % or cancelled.
|
daniel@53
|
259
|
daniel@53
|
260 :- http_handler(openid(login), openid_login_page, [priority(-10)]).
|
daniel@53
|
261 :- http_handler(openid(verify), openid_verify([]), []).
|
daniel@53
|
262 :- http_handler(openid(authenticate), openid_authenticate, []).
|
daniel@53
|
263 :- http_handler(openid(xrds), openid_xrds, []).
|
daniel@53
|
264
|
daniel@53
|
265 openid_user(_Request, OpenID, _Options) :-
|
daniel@53
|
266 openid_logged_in(OpenID), !.
|
daniel@53
|
267 openid_user(Request, _OpenID, Options) :-
|
daniel@53
|
268 http_link_to_id(openid_login_page, [], DefLoginPage),
|
daniel@53
|
269 option(login_url(LoginPage), Options, DefLoginPage),
|
daniel@53
|
270 openid_current_url(Request, Here),
|
daniel@53
|
271 ( member(referer(Referer),Request)
|
daniel@53
|
272 -> ReturnTo=Referer
|
daniel@53
|
273 ; ReturnTo=Here
|
daniel@53
|
274 ),
|
daniel@53
|
275 redirect_browser(LoginPage,
|
daniel@53
|
276 [ 'openid.return_to' = ReturnTo
|
daniel@53
|
277 ]).
|
daniel@53
|
278
|
daniel@53
|
279 %% openid_xrds(Request)
|
daniel@53
|
280 %
|
daniel@53
|
281 % Reply to a request for "Discovering OpenID Relying Parties".
|
daniel@53
|
282 % This may happen as part of the provider verification procedure.
|
daniel@53
|
283 % The provider will do a Yadis discovery request on
|
daniel@53
|
284 % =openid.return= or =openid.realm=. This is picked up by
|
daniel@53
|
285 % openid_user/3, pointing the provider to openid(xrds). Now, we
|
daniel@53
|
286 % reply with the locations marked =openid= and the locations that
|
daniel@53
|
287 % have actually been doing OpenID validations.
|
daniel@53
|
288
|
daniel@53
|
289 openid_xrds(Request) :-
|
daniel@53
|
290 http_link_to_id(openid_authenticate, [], Autheticate),
|
daniel@53
|
291 public_url(Request, Autheticate, Public),
|
daniel@53
|
292 format('Content-type: text/xml\n\n'),
|
daniel@53
|
293 format('<?xml version="1.0" encoding="UTF-8"?>\n'),
|
daniel@53
|
294 format('<xrds:XRDS\n'),
|
daniel@53
|
295 format(' xmlns:xrds="xri://$xrds"\n'),
|
daniel@53
|
296 format(' xmlns="xri://$xrd*($v*2.0)">\n'),
|
daniel@53
|
297 format(' <XRD>\n'),
|
daniel@53
|
298 format(' <Service>\n'),
|
daniel@53
|
299 format(' <Type>http://specs.openid.net/auth/2.0/return_to</Type>\n'),
|
daniel@53
|
300 format(' <URI>~w</URI>\n', [Public]),
|
daniel@53
|
301 format(' </Service>\n'),
|
daniel@53
|
302 format(' </XRD>\n'),
|
daniel@53
|
303 format('</xrds:XRDS>\n').
|
daniel@53
|
304
|
daniel@53
|
305
|
daniel@53
|
306 %% openid_login_page(+Request) is det.
|
daniel@53
|
307 %
|
daniel@53
|
308 % Present a login-form for OpenID. There are two ways to redefine
|
daniel@53
|
309 % this default login page. One is to provide the option
|
daniel@53
|
310 % =login_url= to openid_user/3 and the other is to define a new
|
daniel@53
|
311 % handler for =|/openid/login|= using http_handler/3.
|
daniel@53
|
312
|
daniel@53
|
313 openid_login_page(Request) :-
|
daniel@53
|
314 http_open_session(_, []),
|
daniel@53
|
315 http_parameters(Request,
|
daniel@53
|
316 [ 'openid.return_to'(Target, [])
|
daniel@53
|
317 ]),
|
daniel@53
|
318 reply_html_page([ title('OpenID login')
|
daniel@53
|
319 ],
|
daniel@53
|
320 [ \openid_login_form(Target, [])
|
daniel@53
|
321 ]).
|
daniel@53
|
322
|
daniel@53
|
323 %% openid_login_form(+ReturnTo, +Options)// is det.
|
daniel@53
|
324 %
|
daniel@53
|
325 % Create the OpenID form. This exported as a seperate DCG,
|
daniel@53
|
326 % allowing applications to redefine /openid/login and reuse this
|
daniel@53
|
327 % part of the page. Options processed:
|
daniel@53
|
328 %
|
daniel@53
|
329 % - action(Action)
|
daniel@53
|
330 % URL of action to call. Default is the handler calling
|
daniel@53
|
331 % openid_verify/1.
|
daniel@53
|
332 % - buttons(+Buttons)
|
daniel@53
|
333 % Buttons is a list of =img= structures where the =href=
|
daniel@53
|
334 % points to an OpenID 2.0 endpoint. These buttons are
|
daniel@53
|
335 % displayed below the OpenID URL field. Clicking the
|
daniel@53
|
336 % button sets the URL field and submits the form. Requires
|
daniel@53
|
337 % Javascript support.
|
daniel@53
|
338 %
|
daniel@53
|
339 % If the =href= is _relative_, clicking it opens the given
|
daniel@53
|
340 % location after adding 'openid.return_to' and `stay'.
|
daniel@53
|
341 % - show_stay(+Boolean)
|
daniel@53
|
342 % If =true=, show a checkbox that allows the user to stay
|
daniel@53
|
343 % logged on.
|
daniel@53
|
344
|
daniel@53
|
345 openid_login_form(ReturnTo, Options) -->
|
daniel@53
|
346 { http_link_to_id(openid_verify, [], VerifyLocation),
|
daniel@53
|
347 option(action(Action), Options, VerifyLocation),
|
daniel@53
|
348 http_session_retractall(openid(_)),
|
daniel@53
|
349 http_session_retractall(openid_login(_,_,_,_)),
|
daniel@53
|
350 http_session_retractall(ax(_))
|
daniel@53
|
351 },
|
daniel@53
|
352 html(div([ class('openid-login')
|
daniel@53
|
353 ],
|
daniel@53
|
354 [ \openid_title,
|
daniel@53
|
355 form([ name(login),
|
daniel@53
|
356 id(login),
|
daniel@53
|
357 action(Action),
|
daniel@53
|
358 method('GET')
|
daniel@53
|
359 ],
|
daniel@53
|
360 [ \hidden('openid.return_to', ReturnTo),
|
daniel@53
|
361 div([ input([ class('openid-input'),
|
daniel@53
|
362 name(openid_url),
|
daniel@53
|
363 id(openid_url),
|
daniel@53
|
364 size(30),
|
daniel@53
|
365 placeholder('Your OpenID URL')
|
daniel@53
|
366 ]),
|
daniel@53
|
367 input([ type(submit),
|
daniel@53
|
368 value('Verify!')
|
daniel@53
|
369 ])
|
daniel@53
|
370 ]),
|
daniel@53
|
371 \buttons(Options),
|
daniel@53
|
372 \stay_logged_on(Options)
|
daniel@53
|
373 ])
|
daniel@53
|
374 ])).
|
daniel@53
|
375
|
daniel@53
|
376 stay_logged_on(Options) -->
|
daniel@53
|
377 { option(show_stay(true), Options) }, !,
|
daniel@53
|
378 html(div(class('openid-stay'),
|
daniel@53
|
379 [ input([ type(checkbox), id(stay), name(stay), value(yes)]),
|
daniel@53
|
380 'Stay signed in'
|
daniel@53
|
381 ])).
|
daniel@53
|
382 stay_logged_on(_) --> [].
|
daniel@53
|
383
|
daniel@53
|
384 buttons(Options) -->
|
daniel@53
|
385 { option(buttons(Buttons), Options),
|
daniel@53
|
386 Buttons \== []
|
daniel@53
|
387 },
|
daniel@53
|
388 html(div(class('openid-buttons'),
|
daniel@53
|
389 [ 'Sign in with '
|
daniel@53
|
390 | \prelogin_buttons(Buttons)
|
daniel@53
|
391 ])).
|
daniel@53
|
392 buttons(_) --> [].
|
daniel@53
|
393
|
daniel@53
|
394 prelogin_buttons([]) --> [].
|
daniel@53
|
395 prelogin_buttons([H|T]) --> prelogin_button(H), prelogin_buttons(T).
|
daniel@53
|
396
|
daniel@53
|
397 %% prelogin_button(+Image)// is det.
|
daniel@53
|
398 %
|
daniel@53
|
399 % Handle OpenID 2.0 and other pre-login buttons. If the image has
|
daniel@53
|
400 % a =href= attribute that is absolute, it is taken as an OpenID
|
daniel@53
|
401 % 2.0 endpoint. Otherwise it is taken as a link on the current
|
daniel@53
|
402 % server. This allows us to present non-OpenId logons in the same
|
daniel@53
|
403 % screen. The dedicated handler is passed the HTTP paramters
|
daniel@53
|
404 % =openid.return_to= and =stay=.
|
daniel@53
|
405
|
daniel@53
|
406 prelogin_button(img(Attrs)) -->
|
daniel@53
|
407 { select_option(href(HREF), Attrs, RestAttrs),
|
daniel@53
|
408 uri_is_global(HREF), !
|
daniel@53
|
409 },
|
daniel@53
|
410 html(img([ onClick('javascript:{$("#openid_url").val("'+HREF+'");'+
|
daniel@53
|
411 '$("form#login").submit();}'
|
daniel@53
|
412 )
|
daniel@53
|
413 | RestAttrs
|
daniel@53
|
414 ])).
|
daniel@53
|
415 prelogin_button(img(Attrs)) -->
|
daniel@53
|
416 { select_option(href(HREF), Attrs, RestAttrs)
|
daniel@53
|
417 },
|
daniel@53
|
418 html(img([ onClick('window.location = "'+HREF+
|
daniel@53
|
419 '?openid.return_to="'+
|
daniel@53
|
420 '+encodeURIComponent($("#return_to").val())'+
|
daniel@53
|
421 '+"&stay="'+
|
daniel@53
|
422 '+$("#stay").val()')
|
daniel@53
|
423 | RestAttrs
|
daniel@53
|
424 ])).
|
daniel@53
|
425
|
daniel@53
|
426
|
daniel@53
|
427 /*******************************
|
daniel@53
|
428 * HTTP REPLIES *
|
daniel@53
|
429 *******************************/
|
daniel@53
|
430
|
daniel@53
|
431 %% openid_verify(+Options, +Request)
|
daniel@53
|
432 %
|
daniel@53
|
433 % Handle the initial login form presented to the user by the
|
daniel@53
|
434 % relying party (consumer). This predicate discovers the OpenID
|
daniel@53
|
435 % server, associates itself with this server and redirects the
|
daniel@53
|
436 % user's browser to the OpenID server, providing the extra
|
daniel@53
|
437 % openid.X name-value pairs. Options is, against the conventions,
|
daniel@53
|
438 % placed in front of the Request to allow for smooth cooperation
|
daniel@53
|
439 % with http_dispatch.pl. Options processes:
|
daniel@53
|
440 %
|
daniel@53
|
441 % * return_to(+URL)
|
daniel@53
|
442 % Specifies where the OpenID provider should return to.
|
daniel@53
|
443 % Normally, that is the current location.
|
daniel@53
|
444 % * trust_root(+URL)
|
daniel@53
|
445 % Specifies the =openid.trust_root= attribute. Defaults to
|
daniel@53
|
446 % the root of the current server (i.e., =|http://host[.port]/|=).
|
daniel@53
|
447 % * realm(+URL)
|
daniel@53
|
448 % Specifies the =openid.realm= attribute. Default is the
|
daniel@53
|
449 % =trust_root=.
|
daniel@53
|
450 % * ax(+Spec)
|
daniel@53
|
451 % Request the exchange of additional attributes from the
|
daniel@53
|
452 % identity provider. See http_ax_attributes/2 for details.
|
daniel@53
|
453 %
|
daniel@53
|
454 % The OpenId server will redirect to the =openid.return_to= URL.
|
daniel@53
|
455 %
|
daniel@53
|
456 % @throws http_reply(moved_temporary(Redirect))
|
daniel@53
|
457
|
daniel@53
|
458 openid_verify(Options, Request) :-
|
daniel@53
|
459 http_parameters(Request,
|
daniel@53
|
460 [ openid_url(URL, [length>1]),
|
daniel@53
|
461 'openid.return_to'(ReturnTo0, [optional(true)]),
|
daniel@53
|
462 stay(Stay, [optional(true), default(no)])
|
daniel@53
|
463 ]),
|
daniel@53
|
464 ( option(return_to(ReturnTo1), Options) % Option
|
daniel@53
|
465 -> openid_current_url(Request, CurrentLocation),
|
daniel@53
|
466 global_url(ReturnTo1, CurrentLocation, ReturnTo)
|
daniel@53
|
467 ; nonvar(ReturnTo0)
|
daniel@53
|
468 -> ReturnTo = ReturnTo0 % Form-data
|
daniel@53
|
469 ; openid_current_url(Request, CurrentLocation),
|
daniel@53
|
470 ReturnTo = CurrentLocation % Current location
|
daniel@53
|
471 ),
|
daniel@53
|
472 public_url(Request, /, CurrentRoot),
|
daniel@53
|
473 option(trust_root(TrustRoot), Options, CurrentRoot),
|
daniel@53
|
474 option(realm(Realm), Options, TrustRoot),
|
daniel@53
|
475 openid_resolve(URL, OpenIDLogin, OpenID, Server, ServerOptions),
|
daniel@53
|
476 trusted(OpenID, Server),
|
daniel@53
|
477 openid_associate(Server, Handle, _Assoc),
|
daniel@53
|
478 assert_openid(OpenIDLogin, OpenID, Server, ReturnTo),
|
daniel@53
|
479 stay(Stay),
|
daniel@53
|
480 option(ns(NS), Options, 'http://specs.openid.net/auth/2.0'),
|
daniel@53
|
481 ( realm_attribute(NS, RealmAttribute)
|
daniel@53
|
482 -> true
|
daniel@53
|
483 ; domain_error('openid.ns', NS)
|
daniel@53
|
484 ),
|
daniel@53
|
485 findall(P=V, openid_hook(x_parameter(Server, P, V)), XAttrs, AXAttrs),
|
daniel@53
|
486 debug(openid(verify), 'XAttrs: ~p', [XAttrs]),
|
daniel@53
|
487 ax_options(ServerOptions, Options, AXAttrs),
|
daniel@53
|
488 http_link_to_id(openid_authenticate, [], AuthenticateLoc),
|
daniel@53
|
489 public_url(Request, AuthenticateLoc, Authenticate),
|
daniel@53
|
490 redirect_browser(Server, [ 'openid.ns' = NS,
|
daniel@53
|
491 'openid.mode' = checkid_setup,
|
daniel@53
|
492 'openid.identity' = OpenID,
|
daniel@53
|
493 'openid.claimed_id' = OpenID,
|
daniel@53
|
494 'openid.assoc_handle' = Handle,
|
daniel@53
|
495 'openid.return_to' = Authenticate,
|
daniel@53
|
496 RealmAttribute = Realm
|
daniel@53
|
497 | XAttrs
|
daniel@53
|
498 ]).
|
daniel@53
|
499
|
daniel@53
|
500 realm_attribute('http://specs.openid.net/auth/2.0', 'openid.realm').
|
daniel@53
|
501 realm_attribute('http://openid.net/signon/1.1', 'openid.trust_root').
|
daniel@53
|
502
|
daniel@53
|
503
|
daniel@53
|
504 %% stay(+Response)
|
daniel@53
|
505 %
|
daniel@53
|
506 % Called if the user ask to stay signed in. This is called
|
daniel@53
|
507 % _before_ control is handed to the OpenID server. It leaves the
|
daniel@53
|
508 % data openid_stay_signed_in(true) in the current session.
|
daniel@53
|
509
|
daniel@53
|
510 stay(yes) :- !,
|
daniel@53
|
511 http_session_assert(openid_stay_signed_in(true)).
|
daniel@53
|
512 stay(_).
|
daniel@53
|
513
|
daniel@53
|
514 %% handle_stay_signed_in(+OpenID)
|
daniel@53
|
515 %
|
daniel@53
|
516 % Handle stay_signed_in option after the user has logged on
|
daniel@53
|
517
|
daniel@53
|
518 handle_stay_signed_in(OpenID) :-
|
daniel@53
|
519 http_session_retract(openid_stay_signed_in(true)), !,
|
daniel@53
|
520 http_set_session(timeout(0)),
|
daniel@53
|
521 ignore(openid_hook(stay_signed_in(OpenID))).
|
daniel@53
|
522 handle_stay_signed_in(_).
|
daniel@53
|
523
|
daniel@53
|
524 %% assert_openid(+OpenIDLogin, +OpenID, +Server, +Target) is det.
|
daniel@53
|
525 %
|
daniel@53
|
526 % Associate the OpenID as typed by the user, the OpenID as
|
daniel@53
|
527 % validated by the Server with the current HTTP session.
|
daniel@53
|
528 %
|
daniel@53
|
529 % @param OpenIDLogin Canonized OpenID typed by user
|
daniel@53
|
530 % @param OpenID OpenID verified by Server.
|
daniel@53
|
531
|
daniel@53
|
532 assert_openid(OpenIDLogin, OpenID, Server, Target) :-
|
daniel@53
|
533 openid_identifier_select_url(OpenIDLogin),
|
daniel@53
|
534 openid_identifier_select_url(OpenID), !,
|
daniel@53
|
535 http_session_assert(openid_login(Identity, Identity, Server, Target)).
|
daniel@53
|
536 assert_openid(OpenIDLogin, OpenID, Server, Target) :-
|
daniel@53
|
537 http_session_assert(openid_login(OpenIDLogin, OpenID, Server, Target)).
|
daniel@53
|
538
|
daniel@53
|
539 %% openid_server(?OpenIDLogin, ?OpenID, ?Server) is nondet.
|
daniel@53
|
540 %
|
daniel@53
|
541 % True if OpenIDLogin is the typed id for OpenID verified by
|
daniel@53
|
542 % Server.
|
daniel@53
|
543 %
|
daniel@53
|
544 % @param OpenIDLogin ID as typed by user (canonized)
|
daniel@53
|
545 % @param OpenID ID as verified by server
|
daniel@53
|
546 % @param Server URL of the OpenID server
|
daniel@53
|
547
|
daniel@53
|
548 openid_server(OpenIDLogin, OpenID, Server) :-
|
daniel@53
|
549 openid_server(OpenIDLogin, OpenID, Server, _Target).
|
daniel@53
|
550
|
daniel@53
|
551 openid_server(OpenIDLogin, OpenID, Server, Target) :-
|
daniel@53
|
552 http_in_session(_),
|
daniel@53
|
553 http_session_data(openid_login(OpenIDLogin, OpenID, Server, Target)), !.
|
daniel@53
|
554
|
daniel@53
|
555
|
daniel@53
|
556 %% public_url(+Request, +Path, -URL) is det.
|
daniel@53
|
557 %
|
daniel@53
|
558 % True when URL is a publically useable URL that leads to Path on
|
daniel@53
|
559 % the current server.
|
daniel@53
|
560
|
daniel@53
|
561 public_url(Request, Path, URL) :-
|
daniel@53
|
562 openid_current_host(Request, Host, Port),
|
daniel@53
|
563 setting(http:public_scheme, Scheme),
|
daniel@53
|
564 set_port(Scheme, Port, AuthC),
|
daniel@53
|
565 uri_authority_data(host, AuthC, Host),
|
daniel@53
|
566 uri_authority_components(Auth, AuthC),
|
daniel@53
|
567 uri_data(scheme, Components, Scheme),
|
daniel@53
|
568 uri_data(authority, Components, Auth),
|
daniel@53
|
569 uri_data(path, Components, Path),
|
daniel@53
|
570 uri_components(URL, Components).
|
daniel@53
|
571
|
daniel@53
|
572 set_port(Scheme, Port, _) :-
|
daniel@53
|
573 scheme_port(Scheme, Port), !.
|
daniel@53
|
574 set_port(_, Port, AuthC) :-
|
daniel@53
|
575 uri_authority_data(port, AuthC, Port).
|
daniel@53
|
576
|
daniel@53
|
577 scheme_port(http, 80).
|
daniel@53
|
578 scheme_port(https, 443).
|
daniel@53
|
579
|
daniel@53
|
580
|
daniel@53
|
581 %% openid_current_url(+Request, -URL) is det.
|
daniel@53
|
582 %
|
daniel@53
|
583 % @deprecated New code should use http_public_url/2 with the
|
daniel@53
|
584 % same semantics.
|
daniel@53
|
585
|
daniel@53
|
586 openid_current_url(Request, URL) :-
|
daniel@53
|
587 http_public_url(Request, URL).
|
daniel@53
|
588
|
daniel@53
|
589 %% openid_current_host(Request, Host, Port)
|
daniel@53
|
590 %
|
daniel@53
|
591 % Find current location of the server.
|
daniel@53
|
592 %
|
daniel@53
|
593 % @deprecated New code should use http_current_host/4 with the
|
daniel@53
|
594 % option global(true).
|
daniel@53
|
595
|
daniel@53
|
596 openid_current_host(Request, Host, Port) :-
|
daniel@53
|
597 http_current_host(Request, Host, Port,
|
daniel@53
|
598 [ global(true)
|
daniel@53
|
599 ]).
|
daniel@53
|
600
|
daniel@53
|
601
|
daniel@53
|
602 %% redirect_browser(+URL, +FormExtra)
|
daniel@53
|
603 %
|
daniel@53
|
604 % Generate a 302 temporary redirect to URL, adding the extra form
|
daniel@53
|
605 % information from FormExtra. The specs says we must retain the
|
daniel@53
|
606 % search specification already attached to the URL.
|
daniel@53
|
607
|
daniel@53
|
608 redirect_browser(URL, FormExtra) :-
|
daniel@53
|
609 uri_components(URL, C0),
|
daniel@53
|
610 uri_data(search, C0, Search0),
|
daniel@53
|
611 ( var(Search0)
|
daniel@53
|
612 -> uri_query_components(Search, FormExtra)
|
daniel@53
|
613 ; uri_query_components(Search0, Form0),
|
daniel@53
|
614 append(FormExtra, Form0, Form),
|
daniel@53
|
615 uri_query_components(Search, Form)
|
daniel@53
|
616 ),
|
daniel@53
|
617 uri_data(search, C0, Search, C),
|
daniel@53
|
618 uri_components(Redirect, C),
|
daniel@53
|
619 throw(http_reply(moved_temporary(Redirect))).
|
daniel@53
|
620
|
daniel@53
|
621
|
daniel@53
|
622 /*******************************
|
daniel@53
|
623 * RESOLVE *
|
daniel@53
|
624 *******************************/
|
daniel@53
|
625
|
daniel@53
|
626 %% openid_resolve(+URL, -OpenIDOrig, -OpenID, -Server, -ServerOptions)
|
daniel@53
|
627 %
|
daniel@53
|
628 % True if OpenID is the claimed OpenID that belongs to URL and
|
daniel@53
|
629 % Server is the URL of the OpenID server that can be asked to
|
daniel@53
|
630 % verify this claim.
|
daniel@53
|
631 %
|
daniel@53
|
632 % @param URL The OpenID typed by the user
|
daniel@53
|
633 % @param OpenIDOrig Canonized OpenID typed by user
|
daniel@53
|
634 % @param OpenID Possibly delegated OpenID
|
daniel@53
|
635 % @param Server OpenID server that must validate OpenID
|
daniel@53
|
636 % @param ServerOptions provides additional XRDS information about
|
daniel@53
|
637 % the server. Currently supports xrds_types(Types).
|
daniel@53
|
638 % @tbd Implement complete URL canonization as defined by the
|
daniel@53
|
639 % OpenID 2.0 proposal.
|
daniel@53
|
640
|
daniel@53
|
641 openid_resolve(URL, OpenID, OpenID, Server, [xrds_types(Types)]) :-
|
daniel@53
|
642 xrds_dom(URL, DOM),
|
daniel@53
|
643 xpath(DOM, //(_:'Service'), Service),
|
daniel@53
|
644 findall(Type, xpath(Service, _:'Type'(text), Type), Types),
|
daniel@53
|
645 memberchk('http://specs.openid.net/auth/2.0/server', Types),
|
daniel@53
|
646 xpath(Service, _:'URI'(text), Server), !,
|
daniel@53
|
647 debug(openid(yadis), 'Yadis: server: ~q, types: ~q', [Server, Types]),
|
daniel@53
|
648 ( xpath(Service, _:'LocalID'(text), OpenID)
|
daniel@53
|
649 -> true
|
daniel@53
|
650 ; openid_identifier_select_url(OpenID)
|
daniel@53
|
651 ).
|
daniel@53
|
652 openid_resolve(URL, OpenID0, OpenID, Server, []) :-
|
daniel@53
|
653 debug(openid(resolve), 'Opening ~w ...', [URL]),
|
daniel@53
|
654 dtd(html, DTD),
|
daniel@53
|
655 setup_call_cleanup(
|
daniel@53
|
656 http_open(URL, Stream,
|
daniel@53
|
657 [ final_url(OpenID0),
|
daniel@53
|
658 cert_verify_hook(ssl_verify)
|
daniel@53
|
659 ]),
|
daniel@53
|
660 load_structure(Stream, Term,
|
daniel@53
|
661 [ dtd(DTD),
|
daniel@53
|
662 dialect(sgml),
|
daniel@53
|
663 shorttag(false),
|
daniel@53
|
664 syntax_errors(quiet)
|
daniel@53
|
665 ]),
|
daniel@53
|
666 close(Stream)),
|
daniel@53
|
667 debug(openid(resolve), 'Scanning HTML document ...', [URL]),
|
daniel@53
|
668 contains_term(element(head, _, Head), Term),
|
daniel@53
|
669 ( link(Head, 'openid.server', Server)
|
daniel@53
|
670 -> debug(openid(resolve), 'OpenID Server=~q', [Server])
|
daniel@53
|
671 ; debug(openid(resolve), 'No server in ~q', [Head]),
|
daniel@53
|
672 fail
|
daniel@53
|
673 ),
|
daniel@53
|
674 ( link(Head, 'openid.delegate', OpenID)
|
daniel@53
|
675 -> debug(openid(resolve), 'OpenID = ~q (delegated)', [OpenID])
|
daniel@53
|
676 ; OpenID = OpenID0,
|
daniel@53
|
677 debug(openid(resolve), 'OpenID = ~q', [OpenID])
|
daniel@53
|
678 ).
|
daniel@53
|
679
|
daniel@53
|
680 openid_identifier_select_url(
|
daniel@53
|
681 'http://specs.openid.net/auth/2.0/identifier_select').
|
daniel@53
|
682
|
daniel@53
|
683 :- public ssl_verify/5.
|
daniel@53
|
684
|
daniel@53
|
685 %% ssl_verify(+SSL, +ProblemCert, +AllCerts, +FirstCert, +Error)
|
daniel@53
|
686 %
|
daniel@53
|
687 % Accept all certificates. We do not care too much. Only the user
|
daniel@53
|
688 % cares s/he is not entering her credentials with a spoofed side.
|
daniel@53
|
689 % As we redirect, the browser will take care of this.
|
daniel@53
|
690
|
daniel@53
|
691 ssl_verify(_SSL,
|
daniel@53
|
692 _ProblemCertificate, _AllCertificates, _FirstCertificate,
|
daniel@53
|
693 _Error).
|
daniel@53
|
694
|
daniel@53
|
695
|
daniel@53
|
696 link(DOM, Type, Target) :-
|
daniel@53
|
697 sub_term(element(link, Attrs, []), DOM),
|
daniel@53
|
698 memberchk(rel=Type, Attrs),
|
daniel@53
|
699 memberchk(href=Target, Attrs).
|
daniel@53
|
700
|
daniel@53
|
701
|
daniel@53
|
702 /*******************************
|
daniel@53
|
703 * AUTHENTICATE *
|
daniel@53
|
704 *******************************/
|
daniel@53
|
705
|
daniel@53
|
706 %% openid_authenticate(+Request)
|
daniel@53
|
707 %
|
daniel@53
|
708 % HTTP handler when redirected back from the OpenID provider.
|
daniel@53
|
709
|
daniel@53
|
710 openid_authenticate(Request) :-
|
daniel@53
|
711 memberchk(accept(Accept), Request),
|
daniel@53
|
712 Accept = [media(application/'xrds+xml',_,_,_)], !,
|
daniel@53
|
713 http_link_to_id(openid_xrds, [], XRDSLocation),
|
daniel@53
|
714 http_absolute_uri(XRDSLocation, XRDSServer),
|
daniel@53
|
715 debug(openid(yadis), 'Sending XRDS server: ~q', [XRDSServer]),
|
daniel@53
|
716 format('X-XRDS-Location: ~w\n', [XRDSServer]),
|
daniel@53
|
717 format('Content-type: text/plain\n\n').
|
daniel@53
|
718 openid_authenticate(Request) :-
|
daniel@53
|
719 openid_authenticate(Request, _OpenIdServer, OpenID, _ReturnTo),
|
daniel@53
|
720 openid_server(User, OpenID, _, Target),
|
daniel@53
|
721 openid_login(User),
|
daniel@53
|
722 redirect_browser(Target, []).
|
daniel@53
|
723
|
daniel@53
|
724
|
daniel@53
|
725 %% openid_authenticate(+Request, -Server:url, -OpenID:url,
|
daniel@53
|
726 %% -ReturnTo:url) is semidet.
|
daniel@53
|
727 %
|
daniel@53
|
728 % Succeeds if Request comes from the OpenID server and confirms
|
daniel@53
|
729 % that User is a verified OpenID user. ReturnTo provides the URL
|
daniel@53
|
730 % to return to.
|
daniel@53
|
731 %
|
daniel@53
|
732 % After openid_verify/2 has redirected the browser to the OpenID
|
daniel@53
|
733 % server, and the OpenID server did its magic, it redirects the
|
daniel@53
|
734 % browser back to this address. The work is fairly trivial. If
|
daniel@53
|
735 % =mode= is =cancel=, the OpenId server denied. If =id_res=, the
|
daniel@53
|
736 % OpenId server replied positive, but we must verify what the
|
daniel@53
|
737 % server told us by checking the HMAC-SHA signature.
|
daniel@53
|
738 %
|
daniel@53
|
739 % This call fails silently if their is no =|openid.mode|= field in
|
daniel@53
|
740 % the request.
|
daniel@53
|
741 %
|
daniel@53
|
742 % @throws openid(cancel)
|
daniel@53
|
743 % if request was cancelled by the OpenId server
|
daniel@53
|
744 % @throws openid(signature_mismatch)
|
daniel@53
|
745 % if the HMAC signature check failed
|
daniel@53
|
746
|
daniel@53
|
747 openid_authenticate(Request, OpenIdServer, Identity, ReturnTo) :-
|
daniel@53
|
748 memberchk(method(get), Request),
|
daniel@53
|
749 http_parameters(Request,
|
daniel@53
|
750 [ 'openid.mode'(Mode, [optional(true)])
|
daniel@53
|
751 ]),
|
daniel@53
|
752 ( var(Mode)
|
daniel@53
|
753 -> fail
|
daniel@53
|
754 ; Mode == cancel
|
daniel@53
|
755 -> throw(openid(cancel))
|
daniel@53
|
756 ; Mode == id_res
|
daniel@53
|
757 -> debug(openid(authenticate), 'Mode=id_res, validating response', []),
|
daniel@53
|
758 http_parameters(Request,
|
daniel@53
|
759 [ 'openid.identity'(Identity, []),
|
daniel@53
|
760 'openid.assoc_handle'(Handle, []),
|
daniel@53
|
761 'openid.return_to'(ReturnTo, []),
|
daniel@53
|
762 'openid.signed'(AtomFields, []),
|
daniel@53
|
763 'openid.sig'(Base64Signature, []),
|
daniel@53
|
764 'openid.invalidate_handle'(Invalidate,
|
daniel@53
|
765 [optional(true)])
|
daniel@53
|
766 ],
|
daniel@53
|
767 [ form_data(Form)
|
daniel@53
|
768 ]),
|
daniel@53
|
769 atomic_list_concat(SignedFields, ',', AtomFields),
|
daniel@53
|
770 check_obligatory_fields(SignedFields),
|
daniel@53
|
771 signed_pairs(SignedFields,
|
daniel@53
|
772 [ mode-Mode,
|
daniel@53
|
773 identity-Identity,
|
daniel@53
|
774 assoc_handle-Handle,
|
daniel@53
|
775 return_to-ReturnTo,
|
daniel@53
|
776 invalidate_handle-Invalidate
|
daniel@53
|
777 ],
|
daniel@53
|
778 Form,
|
daniel@53
|
779 SignedPairs),
|
daniel@53
|
780 ( openid_associate(OpenIdServer, Handle, Assoc)
|
daniel@53
|
781 -> signature(SignedPairs, Assoc, Sig),
|
daniel@53
|
782 atom_codes(Base64Signature, Base64SigCodes),
|
daniel@53
|
783 phrase(base64(Signature), Base64SigCodes),
|
daniel@53
|
784 ( Sig == Signature
|
daniel@53
|
785 -> true
|
daniel@53
|
786 ; throw(openid(signature_mismatch))
|
daniel@53
|
787 )
|
daniel@53
|
788 ; check_authentication(Request, Form)
|
daniel@53
|
789 ),
|
daniel@53
|
790 ax_store(Form)
|
daniel@53
|
791 ).
|
daniel@53
|
792
|
daniel@53
|
793 %% signed_pairs(+FieldNames, +Pairs:list(Field-Value),
|
daniel@53
|
794 %% +Form, -SignedPairs) is det.
|
daniel@53
|
795 %
|
daniel@53
|
796 % Extract the signed field in the order they appear in FieldNames.
|
daniel@53
|
797
|
daniel@53
|
798 signed_pairs([], _, _, []).
|
daniel@53
|
799 signed_pairs([Field|T0], Pairs, Form, [Field-Value|T]) :-
|
daniel@53
|
800 memberchk(Field-Value, Pairs), !,
|
daniel@53
|
801 signed_pairs(T0, Pairs, Form, T).
|
daniel@53
|
802 signed_pairs([Field|T0], Pairs, Form, [Field-Value|T]) :-
|
daniel@53
|
803 atom_concat('openid.', Field, OpenIdField),
|
daniel@53
|
804 memberchk(OpenIdField=Value, Form), !,
|
daniel@53
|
805 signed_pairs(T0, Pairs, Form, T).
|
daniel@53
|
806 signed_pairs([Field|T0], Pairs, Form, T) :-
|
daniel@53
|
807 format(user_error, 'Form = ~p~n', [Form]),
|
daniel@53
|
808 throw(error(existence_error(field, Field),
|
daniel@53
|
809 context(_, 'OpenID Signed field is not present'))),
|
daniel@53
|
810 signed_pairs(T0, Pairs, Form, T).
|
daniel@53
|
811
|
daniel@53
|
812
|
daniel@53
|
813 %% check_obligatory_fields(+SignedFields:list) is det.
|
daniel@53
|
814 %
|
daniel@53
|
815 % Verify fields from obligatory_field/1 are in the signed field
|
daniel@53
|
816 % list.
|
daniel@53
|
817 %
|
daniel@53
|
818 % @error existence_error(field, Field)
|
daniel@53
|
819
|
daniel@53
|
820 check_obligatory_fields(Fields) :-
|
daniel@53
|
821 ( obligatory_field(Field),
|
daniel@53
|
822 ( memberchk(Field, Fields)
|
daniel@53
|
823 -> true
|
daniel@53
|
824 ; throw(error(existence_error(field, Field),
|
daniel@53
|
825 context(_, 'OpenID field is not in signed fields')))
|
daniel@53
|
826 ),
|
daniel@53
|
827 fail
|
daniel@53
|
828 ; true
|
daniel@53
|
829 ).
|
daniel@53
|
830
|
daniel@53
|
831 obligatory_field(identity).
|
daniel@53
|
832
|
daniel@53
|
833
|
daniel@53
|
834 %% check_authentication(+Request, +Form) is semidet.
|
daniel@53
|
835 %
|
daniel@53
|
836 % Implement the stateless verification method. This seems needed
|
daniel@53
|
837 % for stackexchange.com, which provides the =res_id= with a new
|
daniel@53
|
838 % association handle.
|
daniel@53
|
839
|
daniel@53
|
840 check_authentication(_Request, Form) :-
|
daniel@53
|
841 openid_server(_OpenIDLogin, _OpenID, Server),
|
daniel@53
|
842 debug(openid(check_authentication),
|
daniel@53
|
843 'Using stateless verification with ~q form~n~q', [Server, Form]),
|
daniel@53
|
844 select('openid.mode' = _, Form, Form1),
|
daniel@53
|
845 setup_call_cleanup(
|
daniel@53
|
846 http_open(Server, In,
|
daniel@53
|
847 [ post(form([ 'openid.mode' = check_authentication
|
daniel@53
|
848 | Form1
|
daniel@53
|
849 ])),
|
daniel@53
|
850 cert_verify_hook(ssl_verify)
|
daniel@53
|
851 ]),
|
daniel@53
|
852 read_stream_to_codes(In, Reply),
|
daniel@53
|
853 close(In)),
|
daniel@53
|
854 debug(openid(check_authentication),
|
daniel@53
|
855 'Reply: ~n~s~n', [Reply]),
|
daniel@53
|
856 key_values_data(Pairs, Reply),
|
daniel@53
|
857 forall(member(invalidate_handle-Handle, Pairs),
|
daniel@53
|
858 retractall(association(_, Handle, _))),
|
daniel@53
|
859 memberchk(is_valid-true, Pairs).
|
daniel@53
|
860
|
daniel@53
|
861
|
daniel@53
|
862 /*******************************
|
daniel@53
|
863 * AX HANDLING *
|
daniel@53
|
864 *******************************/
|
daniel@53
|
865
|
daniel@53
|
866 %% ax_options(+ServerOptions, +Options, +AXAttrs) is det.
|
daniel@53
|
867 %
|
daniel@53
|
868 % True when AXAttrs is a list of additional attribute exchange
|
daniel@53
|
869 % options to add to the OpenID redirect request.
|
daniel@53
|
870
|
daniel@53
|
871 ax_options(ServerOptions, Options, AXAttrs) :-
|
daniel@53
|
872 option(ax(Spec), Options),
|
daniel@53
|
873 option(xrds_types(Types), ServerOptions),
|
daniel@53
|
874 memberchk('http://openid.net/srv/ax/1.0', Types), !,
|
daniel@53
|
875 http_ax_attributes(Spec, AXAttrs),
|
daniel@53
|
876 debug(openid(ax), 'AX attributes: ~q', [AXAttrs]).
|
daniel@53
|
877 ax_options(_, _, []) :-
|
daniel@53
|
878 debug(openid(ax), 'AX: not supported', []).
|
daniel@53
|
879
|
daniel@53
|
880 %% ax_store(+Form)
|
daniel@53
|
881 %
|
daniel@53
|
882 % Extract reported AX data and store this into the session. If
|
daniel@53
|
883 % there is a non-empty list of exchanged values, this calls
|
daniel@53
|
884 %
|
daniel@53
|
885 % openid_hook(ax(Values))
|
daniel@53
|
886 %
|
daniel@53
|
887 % If this hook fails, Values are added to the session data using
|
daniel@53
|
888 % http_session_assert(ax(Values)).
|
daniel@53
|
889
|
daniel@53
|
890 ax_store(Form) :-
|
daniel@53
|
891 debug(openid(ax), 'Form: ~q', [Form]),
|
daniel@53
|
892 ax_form_attributes(Form, Values),
|
daniel@53
|
893 debug(openid(ax), 'AX: ~q', [Values]),
|
daniel@53
|
894 ( Values \== []
|
daniel@53
|
895 -> ( openid_hook(ax(Values))
|
daniel@53
|
896 -> true
|
daniel@53
|
897 ; http_session_assert(ax(Values))
|
daniel@53
|
898 )
|
daniel@53
|
899 ; true
|
daniel@53
|
900 ).
|
daniel@53
|
901
|
daniel@53
|
902
|
daniel@53
|
903 /*******************************
|
daniel@53
|
904 * OPENID SERVER *
|
daniel@53
|
905 *******************************/
|
daniel@53
|
906
|
daniel@53
|
907 :- dynamic
|
daniel@53
|
908 server_association/3. % URL, Handle, Term
|
daniel@53
|
909
|
daniel@53
|
910 %% openid_server(+Options, +Request)
|
daniel@53
|
911 %
|
daniel@53
|
912 % Realise the OpenID server. The protocol demands a POST request
|
daniel@53
|
913 % here.
|
daniel@53
|
914
|
daniel@53
|
915 openid_server(Options, Request) :-
|
daniel@53
|
916 http_parameters(Request,
|
daniel@53
|
917 [ 'openid.mode'(Mode)
|
daniel@53
|
918 ],
|
daniel@53
|
919 [ attribute_declarations(openid_attribute),
|
daniel@53
|
920 form_data(Form)
|
daniel@53
|
921 ]),
|
daniel@53
|
922 ( Mode == associate
|
daniel@53
|
923 -> associate_server(Request, Form, Options)
|
daniel@53
|
924 ; Mode == checkid_setup
|
daniel@53
|
925 -> checkid_setup_server(Request, Form, Options)
|
daniel@53
|
926 ).
|
daniel@53
|
927
|
daniel@53
|
928 %% associate_server(+Request, +Form, +Options)
|
daniel@53
|
929 %
|
daniel@53
|
930 % Handle the association-request. If successful, create a clause
|
daniel@53
|
931 % for server_association/3 to record the current association.
|
daniel@53
|
932
|
daniel@53
|
933 associate_server(Request, Form, Options) :-
|
daniel@53
|
934 memberchk('openid.assoc_type' = AssocType, Form),
|
daniel@53
|
935 memberchk('openid.session_type' = SessionType, Form),
|
daniel@53
|
936 memberchk('openid.dh_modulus' = P64, Form),
|
daniel@53
|
937 memberchk('openid.dh_gen' = G64, Form),
|
daniel@53
|
938 memberchk('openid.dh_consumer_public' = CPX64, Form),
|
daniel@53
|
939 base64_btwoc(P, P64),
|
daniel@53
|
940 base64_btwoc(G, G64),
|
daniel@53
|
941 base64_btwoc(CPX, CPX64),
|
daniel@53
|
942 Y is 1+random(P-1), % Our secret
|
daniel@53
|
943 DiffieHellman is powm(CPX, Y, P),
|
daniel@53
|
944 btwoc(DiffieHellman, DHBytes),
|
daniel@53
|
945 signature_algorithm(SessionType, SHA_Algo),
|
daniel@53
|
946 sha_hash(DHBytes, SHA1, [encoding(octet), algorithm(SHA_Algo)]),
|
daniel@53
|
947 CPY is powm(G, Y, P),
|
daniel@53
|
948 base64_btwoc(CPY, CPY64),
|
daniel@53
|
949 mackey_bytes(SessionType, MacBytes),
|
daniel@53
|
950 new_assoc_handle(MacBytes, Handle),
|
daniel@53
|
951 random_bytes(MacBytes, MacKey),
|
daniel@53
|
952 xor_codes(MacKey, SHA1, EncKey),
|
daniel@53
|
953 phrase(base64(EncKey), Base64EncKey),
|
daniel@53
|
954 DefExpriresIn is 24*3600,
|
daniel@53
|
955 option(expires_in(ExpriresIn), Options, DefExpriresIn),
|
daniel@53
|
956
|
daniel@53
|
957 get_time(Now),
|
daniel@53
|
958 ExpiresAt is integer(Now+ExpriresIn),
|
daniel@53
|
959 make_association([ session_type(SessionType),
|
daniel@53
|
960 expires_at(ExpiresAt),
|
daniel@53
|
961 mac_key(MacKey)
|
daniel@53
|
962 ],
|
daniel@53
|
963 Record),
|
daniel@53
|
964 memberchk(peer(Peer), Request),
|
daniel@53
|
965 assert(server_association(Peer, Handle, Record)),
|
daniel@53
|
966
|
daniel@53
|
967 key_values_data([ assoc_type-AssocType,
|
daniel@53
|
968 assoc_handle-Handle,
|
daniel@53
|
969 expires_in-ExpriresIn,
|
daniel@53
|
970 session_type-SessionType,
|
daniel@53
|
971 dh_server_public-CPY64,
|
daniel@53
|
972 enc_mac_key-Base64EncKey
|
daniel@53
|
973 ],
|
daniel@53
|
974 Text),
|
daniel@53
|
975 format('Content-type: text/plain~n~n~s', [Text]).
|
daniel@53
|
976
|
daniel@53
|
977 mackey_bytes('DH-SHA1', 20).
|
daniel@53
|
978 mackey_bytes('DH-SHA256', 32).
|
daniel@53
|
979
|
daniel@53
|
980 new_assoc_handle(Length, Handle) :-
|
daniel@53
|
981 random_bytes(Length, Bytes),
|
daniel@53
|
982 phrase(base64(Bytes), HandleCodes),
|
daniel@53
|
983 atom_codes(Handle, HandleCodes).
|
daniel@53
|
984
|
daniel@53
|
985
|
daniel@53
|
986 %% checkid_setup_server(+Request, +Form, +Options)
|
daniel@53
|
987 %
|
daniel@53
|
988 % Validate an OpenID for a TrustRoot and redirect the browser back
|
daniel@53
|
989 % to the ReturnTo argument. There are many possible scenarios
|
daniel@53
|
990 % here:
|
daniel@53
|
991 %
|
daniel@53
|
992 % 1. Check some cookie and if present, grant immediately
|
daniel@53
|
993 % 2. Use a 401 challenge page
|
daniel@53
|
994 % 3. Present a normal grant/password page
|
daniel@53
|
995 % 4. As (3), but use HTTPS for the exchange
|
daniel@53
|
996 % 5. etc.
|
daniel@53
|
997 %
|
daniel@53
|
998 % First thing to check is the immediate acknowledgement.
|
daniel@53
|
999
|
daniel@53
|
1000 checkid_setup_server(_Request, Form, _Options) :-
|
daniel@53
|
1001 memberchk('openid.identity' = Identity, Form),
|
daniel@53
|
1002 memberchk('openid.assoc_handle' = Handle, Form),
|
daniel@53
|
1003 memberchk('openid.return_to' = ReturnTo, Form),
|
daniel@53
|
1004 memberchk('openid.trust_root' = TrustRoot, Form),
|
daniel@53
|
1005
|
daniel@53
|
1006 server_association(_, Handle, _Association), % check
|
daniel@53
|
1007
|
daniel@53
|
1008 reply_html_page(
|
daniel@53
|
1009 [ title('OpenID login')
|
daniel@53
|
1010 ],
|
daniel@53
|
1011 [ \openid_title,
|
daniel@53
|
1012 div(class('openid-message'),
|
daniel@53
|
1013 ['Site ', a(href(TrustRoot), TrustRoot),
|
daniel@53
|
1014 ' requests permission to login with OpenID ',
|
daniel@53
|
1015 a(href(Identity), Identity), '.'
|
daniel@53
|
1016 ]),
|
daniel@53
|
1017 table(class('openid-form'),
|
daniel@53
|
1018 [ tr(td(form([ action(grant), method('GET') ],
|
daniel@53
|
1019 [ \hidden('openid.grant', yes),
|
daniel@53
|
1020 \hidden('openid.identity', Identity),
|
daniel@53
|
1021 \hidden('openid.assoc_handle', Handle),
|
daniel@53
|
1022 \hidden('openid.return_to', ReturnTo),
|
daniel@53
|
1023 \hidden('openid.trust_root', TrustRoot),
|
daniel@53
|
1024 div(['Password: ',
|
daniel@53
|
1025 input([ type(password),
|
daniel@53
|
1026 name('openid.password')
|
daniel@53
|
1027 ]),
|
daniel@53
|
1028 input([ type(submit),
|
daniel@53
|
1029 value('Grant')
|
daniel@53
|
1030 ])
|
daniel@53
|
1031 ])
|
daniel@53
|
1032 ]))),
|
daniel@53
|
1033 tr(td(align(right),
|
daniel@53
|
1034 form([ action(grant), method('GET') ],
|
daniel@53
|
1035 [ \hidden('openid.grant', no),
|
daniel@53
|
1036 \hidden('openid.return_to', ReturnTo),
|
daniel@53
|
1037 input([type(submit), value('Deny')])
|
daniel@53
|
1038 ])))
|
daniel@53
|
1039 ])
|
daniel@53
|
1040 ]).
|
daniel@53
|
1041
|
daniel@53
|
1042 hidden(Name, Value) -->
|
daniel@53
|
1043 html(input([type(hidden), id(return_to), name(Name), value(Value)])).
|
daniel@53
|
1044
|
daniel@53
|
1045
|
daniel@53
|
1046 openid_title -->
|
daniel@53
|
1047 { http_absolute_location(icons('openid-logo-square.png'), SRC, []) },
|
daniel@53
|
1048 html_requires(css('openid.css')),
|
daniel@53
|
1049 html(div(class('openid-title'),
|
daniel@53
|
1050 [ a(href('http://openid.net/'),
|
daniel@53
|
1051 img([ src(SRC), alt('OpenID') ])),
|
daniel@53
|
1052 span('Login')
|
daniel@53
|
1053 ])).
|
daniel@53
|
1054
|
daniel@53
|
1055
|
daniel@53
|
1056 %% openid_grant(+Request)
|
daniel@53
|
1057 %
|
daniel@53
|
1058 % Handle the reply from checkid_setup_server/3. If the reply is
|
daniel@53
|
1059 % =yes=, check the authority (typically the password) and if all
|
daniel@53
|
1060 % looks good redirect the browser to ReturnTo, adding the OpenID
|
daniel@53
|
1061 % properties needed by the Relying Party to verify the login.
|
daniel@53
|
1062
|
daniel@53
|
1063 openid_grant(Request) :-
|
daniel@53
|
1064 http_parameters(Request,
|
daniel@53
|
1065 [ 'openid.grant'(Grant),
|
daniel@53
|
1066 'openid.return_to'(ReturnTo)
|
daniel@53
|
1067 ],
|
daniel@53
|
1068 [ attribute_declarations(openid_attribute)
|
daniel@53
|
1069 ]),
|
daniel@53
|
1070 ( Grant == yes
|
daniel@53
|
1071 -> http_parameters(Request,
|
daniel@53
|
1072 [ 'openid.identity'(Identity),
|
daniel@53
|
1073 'openid.assoc_handle'(Handle),
|
daniel@53
|
1074 'openid.trust_root'(TrustRoot),
|
daniel@53
|
1075 'openid.password'(Password)
|
daniel@53
|
1076 ],
|
daniel@53
|
1077 [ attribute_declarations(openid_attribute)
|
daniel@53
|
1078 ]),
|
daniel@53
|
1079 server_association(_, Handle, Association),
|
daniel@53
|
1080 grant_login(Request,
|
daniel@53
|
1081 [ identity(Identity),
|
daniel@53
|
1082 password(Password),
|
daniel@53
|
1083 trustroot(TrustRoot)
|
daniel@53
|
1084 ]),
|
daniel@53
|
1085 SignedPairs = [ 'mode'-id_res,
|
daniel@53
|
1086 'identity'-Identity,
|
daniel@53
|
1087 'assoc_handle'-Handle,
|
daniel@53
|
1088 'return_to'-ReturnTo
|
daniel@53
|
1089 ],
|
daniel@53
|
1090 signed_fields(SignedPairs, Signed),
|
daniel@53
|
1091 signature(SignedPairs, Association, Signature),
|
daniel@53
|
1092 phrase(base64(Signature), Bas64Sig),
|
daniel@53
|
1093 redirect_browser(ReturnTo,
|
daniel@53
|
1094 [ 'openid.mode' = id_res,
|
daniel@53
|
1095 'openid.identity' = Identity,
|
daniel@53
|
1096 'openid.assoc_handle' = Handle,
|
daniel@53
|
1097 'openid.return_to' = ReturnTo,
|
daniel@53
|
1098 'openid.signed' = Signed,
|
daniel@53
|
1099 'openid.sig' = Bas64Sig
|
daniel@53
|
1100 ])
|
daniel@53
|
1101 ; redirect_browser(ReturnTo,
|
daniel@53
|
1102 [ 'openid.mode' = cancel
|
daniel@53
|
1103 ])
|
daniel@53
|
1104 ).
|
daniel@53
|
1105
|
daniel@53
|
1106
|
daniel@53
|
1107 %% grant_login(+Request, +Options) is det.
|
daniel@53
|
1108 %
|
daniel@53
|
1109 % Validate login from Request (can be used to get cookies) and
|
daniel@53
|
1110 % Options, which contains at least:
|
daniel@53
|
1111 %
|
daniel@53
|
1112 % * identity(Identity)
|
daniel@53
|
1113 % * password(Password)
|
daniel@53
|
1114 % * trustroot(TrustRoot)
|
daniel@53
|
1115
|
daniel@53
|
1116 grant_login(Request, Options) :-
|
daniel@53
|
1117 openid_hook(grant(Request, Options)).
|
daniel@53
|
1118
|
daniel@53
|
1119 %% trusted(+OpenID, +Server)
|
daniel@53
|
1120 %
|
daniel@53
|
1121 % True if we trust the given OpenID server. Must throw an
|
daniel@53
|
1122 % exception, possibly redirecting to a page with trusted servers
|
daniel@53
|
1123 % if the given server is not trusted.
|
daniel@53
|
1124
|
daniel@53
|
1125 trusted(OpenID, Server) :-
|
daniel@53
|
1126 openid_hook(trusted(OpenID, Server)).
|
daniel@53
|
1127
|
daniel@53
|
1128
|
daniel@53
|
1129 %% signed_fields(+Pairs, -Signed) is det.
|
daniel@53
|
1130 %
|
daniel@53
|
1131 % Create a comma-separated atom from the field-names without
|
daniel@53
|
1132 % 'openid.' from Pairs.
|
daniel@53
|
1133
|
daniel@53
|
1134 signed_fields(Pairs, Signed) :-
|
daniel@53
|
1135 signed_field_names(Pairs, Names),
|
daniel@53
|
1136 atomic_list_concat(Names, ',', Signed).
|
daniel@53
|
1137
|
daniel@53
|
1138 signed_field_names([], []).
|
daniel@53
|
1139 signed_field_names([H0-_|T0], [H|T]) :-
|
daniel@53
|
1140 ( atom_concat('openid.', H, H0)
|
daniel@53
|
1141 -> true
|
daniel@53
|
1142 ; H = H0
|
daniel@53
|
1143 ),
|
daniel@53
|
1144 signed_field_names(T0, T).
|
daniel@53
|
1145
|
daniel@53
|
1146 %% signature(+Pairs, +Association, -Signature)
|
daniel@53
|
1147 %
|
daniel@53
|
1148 % Determine the signature for Pairs
|
daniel@53
|
1149
|
daniel@53
|
1150 signature(Pairs, Association, Signature) :-
|
daniel@53
|
1151 key_values_data(Pairs, TokenContents),
|
daniel@53
|
1152 association_mac_key(Association, MacKey),
|
daniel@53
|
1153 association_session_type(Association, SessionType),
|
daniel@53
|
1154 signature_algorithm(SessionType, SHA),
|
daniel@53
|
1155 hmac_sha(MacKey, TokenContents, Signature, [algorithm(SHA)]),
|
daniel@53
|
1156 debug(openid(crypt),
|
daniel@53
|
1157 'Signed:~n~s~nSignature: ~w', [TokenContents, Signature]).
|
daniel@53
|
1158
|
daniel@53
|
1159 signature_algorithm('DH-SHA1', sha1).
|
daniel@53
|
1160 signature_algorithm('DH-SHA256', sha256).
|
daniel@53
|
1161
|
daniel@53
|
1162
|
daniel@53
|
1163 /*******************************
|
daniel@53
|
1164 * ASSOCIATE *
|
daniel@53
|
1165 *******************************/
|
daniel@53
|
1166
|
daniel@53
|
1167 :- dynamic
|
daniel@53
|
1168 association/3. % URL, Handle, Data
|
daniel@53
|
1169
|
daniel@53
|
1170 :- record
|
daniel@53
|
1171 association(session_type='DH-SHA1',
|
daniel@53
|
1172 expires_at, % time-stamp
|
daniel@53
|
1173 mac_key). % code-list
|
daniel@53
|
1174
|
daniel@53
|
1175 %% openid_associate(?URL, ?Handle, ?Assoc) is det.
|
daniel@53
|
1176 %
|
daniel@53
|
1177 % Calls openid_associate/4 as
|
daniel@53
|
1178 %
|
daniel@53
|
1179 % ==
|
daniel@53
|
1180 % openid_associate(URL, Handle, Assoc, []).
|
daniel@53
|
1181 % ==
|
daniel@53
|
1182
|
daniel@53
|
1183 openid_associate(URL, Handle, Assoc) :-
|
daniel@53
|
1184 openid_associate(URL, Handle, Assoc, []).
|
daniel@53
|
1185
|
daniel@53
|
1186 %% openid_associate(+URL, -Handle, -Assoc, +Options) is det.
|
daniel@53
|
1187 %% openid_associate(?URL, +Handle, -Assoc, +Options) is semidet.
|
daniel@53
|
1188 %
|
daniel@53
|
1189 % Associate with an open-id server. We first check for a still
|
daniel@53
|
1190 % valid old association. If there is none or it is expired, we
|
daniel@53
|
1191 % esstablish one and remember it. Options:
|
daniel@53
|
1192 %
|
daniel@53
|
1193 % * ns(URL)
|
daniel@53
|
1194 % One of =http://specs.openid.net/auth/2.0= (default) or
|
daniel@53
|
1195 % =http://openid.net/signon/1.1=.
|
daniel@53
|
1196 %
|
daniel@53
|
1197 % @tbd Should we store known associations permanently? Where?
|
daniel@53
|
1198
|
daniel@53
|
1199 openid_associate(URL, Handle, Assoc, _Options) :-
|
daniel@53
|
1200 nonvar(Handle), !,
|
daniel@53
|
1201 debug(openid(associate),
|
daniel@53
|
1202 'OpenID: Lookup association with handle ~q', [Handle]),
|
daniel@53
|
1203 ( association(URL, Handle, Assoc)
|
daniel@53
|
1204 -> true
|
daniel@53
|
1205 ; debug(openid(associate),
|
daniel@53
|
1206 'OpenID: no association with handle ~q', [Handle]),
|
daniel@53
|
1207 fail
|
daniel@53
|
1208 ).
|
daniel@53
|
1209 openid_associate(URL, Handle, Assoc, _Options) :-
|
daniel@53
|
1210 must_be(atom, URL),
|
daniel@53
|
1211 association(URL, Handle, Assoc),
|
daniel@53
|
1212 association_expires_at(Assoc, Expires),
|
daniel@53
|
1213 get_time(Now),
|
daniel@53
|
1214 ( Now < Expires
|
daniel@53
|
1215 -> !,
|
daniel@53
|
1216 debug(openid(associate),
|
daniel@53
|
1217 'OpenID: Reusing association with ~q', [URL])
|
daniel@53
|
1218 ; retractall(association(URL, Handle, _)),
|
daniel@53
|
1219 fail
|
daniel@53
|
1220 ).
|
daniel@53
|
1221 openid_associate(URL, Handle, Assoc, Options) :-
|
daniel@53
|
1222 associate_data(Data, P, _G, X, Options),
|
daniel@53
|
1223 debug(openid(associate), 'OpenID: Associating with ~q', [URL]),
|
daniel@53
|
1224 setup_call_cleanup(
|
daniel@53
|
1225 http_open(URL, In,
|
daniel@53
|
1226 [ post(form(Data)),
|
daniel@53
|
1227 cert_verify_hook(ssl_verify)
|
daniel@53
|
1228 ]),
|
daniel@53
|
1229 read_stream_to_codes(In, Reply),
|
daniel@53
|
1230 close(In)),
|
daniel@53
|
1231 debug(openid(associate), 'Reply: ~n~s', [Reply]),
|
daniel@53
|
1232 key_values_data(Pairs, Reply),
|
daniel@53
|
1233 shared_secret(Pairs, P, X, MacKey),
|
daniel@53
|
1234 expires_at(Pairs, ExpiresAt),
|
daniel@53
|
1235 memberchk(assoc_handle-Handle, Pairs),
|
daniel@53
|
1236 memberchk(session_type-Type, Pairs),
|
daniel@53
|
1237 make_association([ session_type(Type),
|
daniel@53
|
1238 expires_at(ExpiresAt),
|
daniel@53
|
1239 mac_key(MacKey)
|
daniel@53
|
1240 ], Assoc),
|
daniel@53
|
1241 assert(association(URL, Handle, Assoc)).
|
daniel@53
|
1242
|
daniel@53
|
1243
|
daniel@53
|
1244 %% shared_secret(+Pairs, +P, +X, -Secret:list(codes))
|
daniel@53
|
1245 %
|
daniel@53
|
1246 % Find the shared secret from the peer's reply and our data. First
|
daniel@53
|
1247 % clause deals with the (deprecated) non-encoded version.
|
daniel@53
|
1248
|
daniel@53
|
1249 shared_secret(Pairs, _, _, Secret) :-
|
daniel@53
|
1250 memberchk(mac_key-Base64, Pairs), !,
|
daniel@53
|
1251 atom_codes(Base64, Base64Codes),
|
daniel@53
|
1252 phrase(base64(Base64Codes), Secret).
|
daniel@53
|
1253 shared_secret(Pairs, P, X, Secret) :-
|
daniel@53
|
1254 memberchk(dh_server_public-Base64Public, Pairs),
|
daniel@53
|
1255 memberchk(enc_mac_key-Base64EncMacKey, Pairs),
|
daniel@53
|
1256 memberchk(session_type-SessionType, Pairs),
|
daniel@53
|
1257 base64_btwoc(ServerPublic, Base64Public),
|
daniel@53
|
1258 DiffieHellman is powm(ServerPublic, X, P),
|
daniel@53
|
1259 atom_codes(Base64EncMacKey, Base64EncMacKeyCodes),
|
daniel@53
|
1260 phrase(base64(EncMacKey), Base64EncMacKeyCodes),
|
daniel@53
|
1261 btwoc(DiffieHellman, DiffieHellmanBytes),
|
daniel@53
|
1262 signature_algorithm(SessionType, SHA_Algo),
|
daniel@53
|
1263 sha_hash(DiffieHellmanBytes, DHHash,
|
daniel@53
|
1264 [encoding(octet), algorithm(SHA_Algo)]),
|
daniel@53
|
1265 xor_codes(DHHash, EncMacKey, Secret).
|
daniel@53
|
1266
|
daniel@53
|
1267
|
daniel@53
|
1268 %% expires_at(+Pairs, -Time) is det.
|
daniel@53
|
1269 %
|
daniel@53
|
1270 % Unify Time with a time-stamp stating when the association
|
daniel@53
|
1271 % exires.
|
daniel@53
|
1272
|
daniel@53
|
1273 expires_at(Pairs, Time) :-
|
daniel@53
|
1274 memberchk(expires_in-ExpAtom, Pairs),
|
daniel@53
|
1275 atom_number(ExpAtom, Seconds),
|
daniel@53
|
1276 get_time(Now),
|
daniel@53
|
1277 Time is integer(Now)+Seconds.
|
daniel@53
|
1278
|
daniel@53
|
1279
|
daniel@53
|
1280 %% associate_data(-Data, -P, -G, -X, +Options) is det.
|
daniel@53
|
1281 %
|
daniel@53
|
1282 % Generate the data to initiate an association using Diffie-Hellman
|
daniel@53
|
1283 % shared secret key negotiation.
|
daniel@53
|
1284
|
daniel@53
|
1285 associate_data(Data, P, G, X, Options) :-
|
daniel@53
|
1286 openid_dh_p(P),
|
daniel@53
|
1287 openid_dh_g(G),
|
daniel@53
|
1288 X is 1+random(P-1), % 1<=X<P-1
|
daniel@53
|
1289 CP is powm(G, X, P),
|
daniel@53
|
1290 base64_btwoc(P, P64),
|
daniel@53
|
1291 base64_btwoc(G, G64),
|
daniel@53
|
1292 base64_btwoc(CP, CP64),
|
daniel@53
|
1293 option(ns(NS), Options, 'http://specs.openid.net/auth/2.0'),
|
daniel@53
|
1294 ( assoc_type(NS, DefAssocType, DefSessionType)
|
daniel@53
|
1295 -> true
|
daniel@53
|
1296 ; domain_error('openid.ns', NS)
|
daniel@53
|
1297 ),
|
daniel@53
|
1298 option(assoc_type(AssocType), Options, DefAssocType),
|
daniel@53
|
1299 option(assoc_type(SessionType), Options, DefSessionType),
|
daniel@53
|
1300 Data = [ 'openid.ns' = NS,
|
daniel@53
|
1301 'openid.mode' = associate,
|
daniel@53
|
1302 'openid.assoc_type' = AssocType,
|
daniel@53
|
1303 'openid.session_type' = SessionType,
|
daniel@53
|
1304 'openid.dh_modulus' = P64,
|
daniel@53
|
1305 'openid.dh_gen' = G64,
|
daniel@53
|
1306 'openid.dh_consumer_public' = CP64
|
daniel@53
|
1307 ].
|
daniel@53
|
1308
|
daniel@53
|
1309 assoc_type('http://specs.openid.net/auth/2.0',
|
daniel@53
|
1310 'HMAC-SHA256',
|
daniel@53
|
1311 'DH-SHA256').
|
daniel@53
|
1312 assoc_type('http://openid.net/signon/1.1',
|
daniel@53
|
1313 'HMAC-SHA1',
|
daniel@53
|
1314 'DH-SHA1').
|
daniel@53
|
1315
|
daniel@53
|
1316
|
daniel@53
|
1317 /*******************************
|
daniel@53
|
1318 * RANDOM *
|
daniel@53
|
1319 *******************************/
|
daniel@53
|
1320
|
daniel@53
|
1321 %% random_bytes(+N, -Bytes) is det.
|
daniel@53
|
1322 %
|
daniel@53
|
1323 % Bytes is a list of N random bytes (integers 0..255).
|
daniel@53
|
1324
|
daniel@53
|
1325 random_bytes(N, [H|T]) :-
|
daniel@53
|
1326 N > 0, !,
|
daniel@53
|
1327 H is random(256),
|
daniel@53
|
1328 N2 is N - 1,
|
daniel@53
|
1329 random_bytes(N2, T).
|
daniel@53
|
1330 random_bytes(_, []).
|
daniel@53
|
1331
|
daniel@53
|
1332
|
daniel@53
|
1333 /*******************************
|
daniel@53
|
1334 * CONSTANTS *
|
daniel@53
|
1335 *******************************/
|
daniel@53
|
1336
|
daniel@53
|
1337 openid_dh_p(155172898181473697471232257763715539915724801966915404479707795314057629378541917580651227423698188993727816152646631438561595825688188889951272158842675419950341258706556549803580104870537681476726513255747040765857479291291572334510643245094715007229621094194349783925984760375594985848253359305585439638443).
|
daniel@53
|
1338
|
daniel@53
|
1339 openid_dh_g(2).
|
daniel@53
|
1340
|
daniel@53
|
1341
|
daniel@53
|
1342 /*******************************
|
daniel@53
|
1343 * UTIL *
|
daniel@53
|
1344 *******************************/
|
daniel@53
|
1345
|
daniel@53
|
1346 %% key_values_data(+KeyValues:list(Key-Value), -Data:list(code)) is det.
|
daniel@53
|
1347 %% key_values_data(-KeyValues:list(Key-Value), +Data:list(code)) is det.
|
daniel@53
|
1348 %
|
daniel@53
|
1349 % Encoding and decoding of key-value pairs for OpenID POST
|
daniel@53
|
1350 % messages according to Appendix C of the OpenID 1.1
|
daniel@53
|
1351 % specification.
|
daniel@53
|
1352
|
daniel@53
|
1353 key_values_data(Pairs, Data) :-
|
daniel@53
|
1354 nonvar(Data), !,
|
daniel@53
|
1355 phrase(data_form(Pairs), Data).
|
daniel@53
|
1356 key_values_data(Pairs, Data) :-
|
daniel@53
|
1357 phrase(gen_data_form(Pairs), Data).
|
daniel@53
|
1358
|
daniel@53
|
1359 data_form([Key-Value|Pairs]) -->
|
daniel@53
|
1360 utf8_string(KeyCodes), ":", utf8_string(ValueCodes), "\n", !,
|
daniel@53
|
1361 { atom_codes(Key, KeyCodes),
|
daniel@53
|
1362 atom_codes(Value, ValueCodes)
|
daniel@53
|
1363 },
|
daniel@53
|
1364 data_form(Pairs).
|
daniel@53
|
1365 data_form([]) -->
|
daniel@53
|
1366 ws.
|
daniel@53
|
1367
|
daniel@53
|
1368 %% utf8_string(-Codes)// is nondet.
|
daniel@53
|
1369 %
|
daniel@53
|
1370 % Take a short UTF-8 code-list from input. Extend on backtracking.
|
daniel@53
|
1371
|
daniel@53
|
1372 utf8_string([]) -->
|
daniel@53
|
1373 [].
|
daniel@53
|
1374 utf8_string([H|T]) -->
|
daniel@53
|
1375 utf8_codes([H]),
|
daniel@53
|
1376 utf8_string(T).
|
daniel@53
|
1377
|
daniel@53
|
1378 ws -->
|
daniel@53
|
1379 [C],
|
daniel@53
|
1380 { C =< 32 }, !,
|
daniel@53
|
1381 ws.
|
daniel@53
|
1382 ws -->
|
daniel@53
|
1383 [].
|
daniel@53
|
1384
|
daniel@53
|
1385
|
daniel@53
|
1386 gen_data_form([]) -->
|
daniel@53
|
1387 [].
|
daniel@53
|
1388 gen_data_form([Key-Value|T]) -->
|
daniel@53
|
1389 field(Key), ":", field(Value), "\n",
|
daniel@53
|
1390 gen_data_form(T).
|
daniel@53
|
1391
|
daniel@53
|
1392 field(Field) -->
|
daniel@53
|
1393 { to_codes(Field, Codes)
|
daniel@53
|
1394 },
|
daniel@53
|
1395 utf8_codes(Codes).
|
daniel@53
|
1396
|
daniel@53
|
1397 to_codes(Codes, Codes) :-
|
daniel@53
|
1398 is_list(Codes), !.
|
daniel@53
|
1399 to_codes(Atomic, Codes) :-
|
daniel@53
|
1400 atom_codes(Atomic, Codes).
|
daniel@53
|
1401
|
daniel@53
|
1402 %% base64_btwoc(+Int, -Base64:list(code)) is det.
|
daniel@53
|
1403 %% base64_btwoc(-Int, +Base64:list(code)) is det.
|
daniel@53
|
1404 %% base64_btwoc(-Int, +Base64:atom) is det.
|
daniel@53
|
1405
|
daniel@53
|
1406 base64_btwoc(Int, Base64) :-
|
daniel@53
|
1407 integer(Int), !,
|
daniel@53
|
1408 btwoc(Int, Bytes),
|
daniel@53
|
1409 phrase(base64(Bytes), Base64).
|
daniel@53
|
1410 base64_btwoc(Int, Base64) :-
|
daniel@53
|
1411 atom(Base64), !,
|
daniel@53
|
1412 atom_codes(Base64, Codes),
|
daniel@53
|
1413 phrase(base64(Bytes), Codes),
|
daniel@53
|
1414 btwoc(Int, Bytes).
|
daniel@53
|
1415 base64_btwoc(Int, Base64) :-
|
daniel@53
|
1416 phrase(base64(Bytes), Base64),
|
daniel@53
|
1417 btwoc(Int, Bytes).
|
daniel@53
|
1418
|
daniel@53
|
1419
|
daniel@53
|
1420 %% btwoc(+Integer, -Bytes) is det.
|
daniel@53
|
1421 %% btwoc(-Integer, +Bytes) is det.
|
daniel@53
|
1422 %
|
daniel@53
|
1423 % Translate between a big integer and and its representation in
|
daniel@53
|
1424 % bytes. The first bit is always 0, as Integer is nonneg.
|
daniel@53
|
1425
|
daniel@53
|
1426 btwoc(Int, Bytes) :-
|
daniel@53
|
1427 integer(Int), !,
|
daniel@53
|
1428 int_to_bytes(Int, Bytes).
|
daniel@53
|
1429 btwoc(Int, Bytes) :-
|
daniel@53
|
1430 is_list(Bytes),
|
daniel@53
|
1431 bytes_to_int(Bytes, Int).
|
daniel@53
|
1432
|
daniel@53
|
1433 int_to_bytes(Int, Bytes) :-
|
daniel@53
|
1434 int_to_bytes(Int, [], Bytes).
|
daniel@53
|
1435
|
daniel@53
|
1436 int_to_bytes(Int, Bytes0, [Int|Bytes0]) :-
|
daniel@53
|
1437 Int < 128, !.
|
daniel@53
|
1438 int_to_bytes(Int, Bytes0, Bytes) :-
|
daniel@53
|
1439 Last is Int /\ 0xff,
|
daniel@53
|
1440 Int1 is Int >> 8,
|
daniel@53
|
1441 int_to_bytes(Int1, [Last|Bytes0], Bytes).
|
daniel@53
|
1442
|
daniel@53
|
1443
|
daniel@53
|
1444 bytes_to_int([B|T], Int) :-
|
daniel@53
|
1445 bytes_to_int(T, B, Int).
|
daniel@53
|
1446
|
daniel@53
|
1447 bytes_to_int([], Int, Int).
|
daniel@53
|
1448 bytes_to_int([B|T], Int0, Int) :-
|
daniel@53
|
1449 Int1 is (Int0<<8)+B,
|
daniel@53
|
1450 bytes_to_int(T, Int1, Int).
|
daniel@53
|
1451
|
daniel@53
|
1452
|
daniel@53
|
1453 %% xor_codes(+C1:list(int), +C2:list(int), -XOR:list(int)) is det.
|
daniel@53
|
1454 %
|
daniel@53
|
1455 % Compute xor of two strings.
|
daniel@53
|
1456 %
|
daniel@53
|
1457 % @error length_mismatch(L1, L2) if the two lists do not have equal
|
daniel@53
|
1458 % length.
|
daniel@53
|
1459
|
daniel@53
|
1460 xor_codes([], [], []) :- !.
|
daniel@53
|
1461 xor_codes([H1|T1], [H2|T2], [H|T]) :- !,
|
daniel@53
|
1462 H is H1 xor H2, !,
|
daniel@53
|
1463 xor_codes(T1, T2, T).
|
daniel@53
|
1464 xor_codes(L1, L2, _) :-
|
daniel@53
|
1465 throw(error(length_mismatch(L1, L2), _)).
|
daniel@53
|
1466
|
daniel@53
|
1467
|
daniel@53
|
1468 /*******************************
|
daniel@53
|
1469 * HTTP ATTRIBUTES *
|
daniel@53
|
1470 *******************************/
|
daniel@53
|
1471
|
daniel@53
|
1472 openid_attribute('openid.mode',
|
daniel@53
|
1473 [ oneof([ associate,
|
daniel@53
|
1474 checkid_setup,
|
daniel@53
|
1475 cancel,
|
daniel@53
|
1476 id_res
|
daniel@53
|
1477 ])
|
daniel@53
|
1478 ]).
|
daniel@53
|
1479 openid_attribute('openid.assoc_type',
|
daniel@53
|
1480 [ oneof(['HMAC-SHA1'])
|
daniel@53
|
1481 ]).
|
daniel@53
|
1482 openid_attribute('openid.session_type',
|
daniel@53
|
1483 [ oneof([ 'DH-SHA1',
|
daniel@53
|
1484 'DH-SHA256'
|
daniel@53
|
1485 ])
|
daniel@53
|
1486 ]).
|
daniel@53
|
1487 openid_attribute('openid.dh_modulus', [length > 1]).
|
daniel@53
|
1488 openid_attribute('openid.dh_gen', [length > 1]).
|
daniel@53
|
1489 openid_attribute('openid.dh_consumer_public', [length > 1]).
|
daniel@53
|
1490 openid_attribute('openid.assoc_handle', [length > 1]).
|
daniel@53
|
1491 openid_attribute('openid.return_to', [length > 1]).
|
daniel@53
|
1492 openid_attribute('openid.trust_root', [length > 1]).
|
daniel@53
|
1493 openid_attribute('openid.identity', [length > 1]).
|
daniel@53
|
1494 openid_attribute('openid.password', [length > 1]).
|
daniel@53
|
1495 openid_attribute('openid.grant', [oneof([yes,no])]).
|