1/* Part of SWI-Prolog 2 3 Author: Jan Wielemaker 4 E-mail: J.Wielemaker@cs.vu.nl 5 WWW: http://www.swi-prolog.org 6 Copyright (C): 2015, VU University Amsterdam 7 8 This program is free software; you can redistribute it and/or 9 modify it under the terms of the GNU General Public License 10 as published by the Free Software Foundation; either version 2 11 of the License, or (at your option) any later version. 12 13 This program is distributed in the hope that it will be useful, 14 but WITHOUT ANY WARRANTY; without even the implied warranty of 15 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the 16 GNU General Public License for more details. 17 18 You should have received a copy of the GNU General Public 19 License along with this library; if not, write to the Free Software 20 Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA 21 22 As a special exception, if you link this library with other files, 23 compiled with a Free Software compiler, to produce an executable, this 24 library does not by itself cause the resulting executable to be covered 25 by the GNU General Public License. This exception does not however 26 invalidate any other reasons why the executable file might be covered by 27 the GNU General Public License. 28*/ 29 30:- module(google_client, 31 [ oauth_authenticate/3, % +Request, +Site, +Options 32 openid_connect_discover/2 % +Site, -DiscoveryDict 33 ]). 34:- use_module(library(http/http_open)). 35:- use_module(library(http/http_dispatch)). 36:- use_module(library(http/http_host)). 37:- use_module(library(http/http_parameters)). 38:- use_module(library(http/http_path), []). 39:- use_module(library(http/http_ssl_plugin)). 40:- use_module(library(http/json)). 41:- use_module(library(uri)). 42:- use_module(library(lists)). 43:- use_module(library(debug)). 44:- use_module(library(settings)). 45 46:- use_module(jwt).
73:- multifile 74 login_existing_user/1, % +Claim 75 create_user/1, % +Profile 76 key/2. % +Name, -Value 77 78httplocation(oath2, root(oauth2), [priority(-100)]). 79 80:- http_handler(oath2(auth_redirect), oauth_handle_redirect, []). 81 82:- dynamic 83 forgery_state/5. % State, Site, Redirect, ClientData, Time
openid.realm
. Normally, this is the site's
root URL. By default, it is not sent.100oauth_authenticate(Request, Site, Options) :- 101 oauth_options(Options, Params), 102 openid_connect_discover(Site, DiscDoc), 103 key(client_id, ClientId), 104 http_link_to_id(oauth_handle_redirect, [], LocalRedirect), 105 public_url(Request, LocalRedirect, Redirect), 106 option(client_data(ClientData), Options, _), 107 anti_forgery_state(AntiForgery), 108 get_time(Now), 109 asserta(forgery_state(AntiForgery, Site, Redirect, ClientData, Now)), 110 url_extend(search([ client_id(ClientId), 111 response_type(code), 112 scope('openid email profile'), 113 state(AntiForgery), 114 redirect_uri(Redirect) 115 | Params 116 ]), 117 DiscDoc.authorization_endpoint, 118 URL), 119 http_redirect(moved_temporary, URL, Request). 120 121oauth_options([], []). 122oauth_options([H0|T0], [H|T]) :- 123 name_value(H0, Name, Value), 124 oauth_option(Name, NameTo), !, 125 H =.. [NameTo,Value], 126 oauth_options(T0, T). 127oauth_options([_|T0], T) :- 128 oauth_options(T0, T). 129 130oauth_option(realm, 'openid.realm'). 131oauth_option(login_hint, login_hint). 132 133name_value(Name = Value, Name, Value) :- !. 134name_value(Term, Name, Value) :- 135 Term =.. [Name,Value].
147oauth_handle_redirect(Request) :-
148 http_parameters(Request,
149 [ state(State, []),
150 code(Code, [])
151 ],
152 [ %form_data(Form)
153 ]),
154 validate_forgery_state(State, Site, Redirect, ClientData),
155 openid_connect_discover(Site, DiscDoc),
156 key(client_id, ClientId),
157 key(client_secret, ClientSecret),
158 http_open(DiscDoc.token_endpoint,
159 In,
160 [ cert_verify_hook(cert_verify),
161 post(form([ code(Code),
162 client_id(ClientId),
163 client_secret(ClientSecret),
164 redirect_uri(Redirect),
165 grant_type(authorization_code)
166 ]))
167 ]),
168 call_cleanup(json_read_dict(In, Response),
169 close(In)),
170 jwt(Response.id_token, Claim),
171 oauth_login(Claim, Response, DiscDoc, ClientData).
We now have two tasks. If sub
is known, we are done. If not,
we must make a new account. To do so, we can prefill info by
extracting the Google user profile information using the
OpenID Connect method.
189oauth_login(Claim, _, _, ClientData) :- 190 add_client_data(ClientData, Claim, Claim1), 191 login_existing_user(Claim1), !. 192oauth_login(_Claim, Response, DiscDoc, ClientData) :- 193 key(client_id, ClientId), 194 key(client_secret, ClientSecret), 195 url_extend(search([ access_token(Response.access_token), 196 client_id(ClientId), 197 client_secret(ClientSecret) 198 ]), 199 DiscDoc.userinfo_endpoint, 200 URL), 201 http_open(URL, 202 In, 203 [ cert_verify_hook(cert_verify) 204 ]), 205 call_cleanup(json_read_dict(In, Profile), 206 close(In)), 207 add_client_data(ClientData, Profile, Profile1), 208 create_user(Profile1). 209 210add_client_data(ClientData, Dict, Dict) :- var(ClientData), !. 211add_client_data(ClientData, Dict, Dict.put(client_data, ClientData)). 212 213validate_forgery_state(State, Site, Redirect, ClientData) :- 214 ( forgery_state(State, Site, Redirect, ClientData, Stamp) 215 -> retractall(forgery_state(State, Site, Redirect, ClientData, Stamp)) 216 ; throw(http_reply(not_acceptable('Invalid state parameter'))) 217 ). 218 219anti_forgery_state(State) :- 220 Rand is random(1<<100), 221 variant_sha1(Rand, State).
227:- dynamic 228 discovered_data/3. % URL, Time, Data 229 230openid_connect_discover(Site, Dict) :- 231 openid_connect_discover_url(Site, URL), 232 ( discovered_data(URL, Dict0) 233 -> Dict = Dict0 234 ; discover_data(URL, Expires, Dict0), 235 cache_data(URL, Expires, Dict0), 236 Dict = Dict0 237 ). 238 239discover_data(URL, Expires, Dict) :- 240 http_open(URL, In, 241 [ cert_verify_hook(cert_verify), 242 header(expires, Expires) 243 ]), 244 json_read_dict(In, Dict), 245 close(In). 246 247discovered_data(URL, Data) :- 248 discovered_data(URL, Expires, Data0), 249 get_time(Now), 250 ( Now =< Expires 251 -> Data = Data0 252 ; retractall(discovered_data(URL, Expires, _)), 253 fail 254 ). 255 256cache_data(URL, Expires, Data) :- 257 parse_time(Expires, _Format, Stamp), !, 258 asserta(discovered_data(URL, Stamp, Data)). 259cache_data(_, _, _). 260 261:- multifile 262 openid_connect_discover_url/2. 263 264openid_connect_discover_url( 265 'google.com', 266 'https://accounts.google.com/.well-known/openid-configuration'). 267 268 269 /******************************* 270 * HOOKS * 271 *******************************/
client_data(Term)
. Note that the term passed is a copy.This call must return an HTML document indicating that the user logged in successfully or redirect to the URL supplied with return to using http_redirect/3.
family_name
, gender
, given_name
,
locale
, name
, picture
and profile
. Check the Google docs
for details.
This call creates a new user, typically after verifying that the user is human and completing the profile. As login_existing_user/1, it must return a web page or redirect.
313 /******************************* 314 * SSL SUPPORT * 315 *******************************/
321:- public cert_verify/5. 322 323cert_verify(_SSL, _ProblemCert, _AllCerts, _FirstCert, _Error) :- 324 debug(ssl(cert_verify),'~s', ['Accepting certificate']). 325 326 327 /******************************* 328 * URI GOODIES * 329 *******************************/
335url_extend(search(Params), URL0, URL) :- 336 uri_components(URL0, Components0), 337 uri_data(search, Components0, Search0), 338 extend_search(Search0, Params, Search), 339 uri_data(search, Components0, Search, Components), 340 uri_components(URL, Components). 341 342extend_search(Var, Params, String) :- 343 var(Var), !, 344 uri_query_components(String, Params). 345extend_search(String0, Params, String) :- 346 uri_query_components(String0, Params0), 347 append(Params0, Params, AllParams), 348 uri_query_components(String, AllParams).
357public_url(Request, Path, URL) :- 358 http_current_host(Request, Host, Port, 359 [ global(true) 360 ]), 361 setting(http:public_scheme, Scheme), 362 set_port(Scheme, Port, AuthC), 363 uri_authority_data(host, AuthC, Host), 364 uri_authority_components(Auth, AuthC), 365 uri_data(scheme, Components, Scheme), 366 uri_data(authority, Components, Auth), 367 uri_data(path, Components, Path), 368 uri_components(URL, Components). 369 370set_port(Scheme, Port, _) :- 371 scheme_port(Scheme, Port), !. 372set_port(_, Port, AuthC) :- 373 uri_authority_data(port, AuthC, Port). 374 375scheme_port(http, 80). 376scheme_port(https, 443)
Sign in with Google OpenID Connect
This module deals with the Google OpenID Connect federated authentication method. An HTTP handler that wishes to establish a login using Google uses the following flow of control.
oath2(auth_redirect)
, implemented by oauth_handle_redirect/1.