View source with formatted comments or as raw
    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
   45:- use_module(jwt).   46
   47/** <module> Sign in with Google OpenID Connect
   48
   49This  module  deals   with   the    Google   OpenID   Connect  federated
   50authentication method.  An HTTP handler that wishes to establish a login
   51using Google uses the following flow of control.
   52
   53  - Call oauth_authenticate/3. This predicates redirects to Google,
   54    which in turn redirects to oath2(auth_redirect), implemented by
   55    oauth_handle_redirect/1.
   56
   57  - The predicate oauth_handle_redirect/1 establishes the Google unique
   58    user identification (a string holding large integer) and email.  It
   59    calls the multifile hook google_client:login_existing_user/1, which
   60    logs in the user (e.g., by starting an HTTP session and associating
   61    the user with the session) and replies with a web page (or
   62    redirect).
   63
   64  - If google_client:login_existing_user/1 *fails*, this library fetches
   65    user profile information from Google and calls the hook
   66    google_client:create_user/1.  The create_user hook is passed the
   67    basic Google profile information.  Its task is to create a new user.
   68
   69@see https://developers.google.com/accounts/docs/OpenIDConnect
   70*/
   71
   72:- multifile
   73	login_existing_user/1,		% +Claim
   74	create_user/1,			% +Profile
   75	key/2.				% +Name, -Value
   76
   77http:location(oath2, root(oauth2), [priority(-100)]).
   78
   79:- http_handler(oath2(auth_redirect), oauth_handle_redirect, []).   80
   81:- dynamic
   82	forgery_state/5.		% State, Site, Redirect, ClientData, Time
   83
   84%%	oauth_authenticate(+Request, +Site, +Options)
   85%
   86%	Step 2: redirect to Google for  obtaining an authorization code.
   87%	Google redirects back to oauth_handle_response/1.  Options:
   88%
   89%	  - realm(+Realm)
   90%	  Value for `openid.realm`.  Normally, this is the site's
   91%	  root URL.  By default, it is not sent.
   92%	  - login_hint(+Hint)
   93%	  Hint to select the right account.  Typically an email
   94%	  address.  By default, it is not sent.
   95%	  - client_data(+Data)
   96%	  Add the given Data (any Prolog term) to the dict that is
   97%	  passed to the login hooks.
   98
   99oauth_authenticate(Request, Site, Options) :-
  100	oauth_options(Options, Params),
  101	openid_connect_discover(Site, DiscDoc),
  102	key(client_id, ClientId),
  103	http_link_to_id(oauth_handle_redirect, [], LocalRedirect),
  104	public_url(Request, LocalRedirect, Redirect),
  105	option(client_data(ClientData), Options, _),
  106	anti_forgery_state(AntiForgery),
  107	get_time(Now),
  108	asserta(forgery_state(AntiForgery, Site, Redirect, ClientData, Now)),
  109	url_extend(search([ client_id(ClientId),
  110			    response_type(code),
  111			    scope('openid email profile'),
  112			    state(AntiForgery),
  113			    redirect_uri(Redirect)
  114			  | Params
  115			  ]),
  116		   DiscDoc.authorization_endpoint,
  117		   URL),
  118	http_redirect(moved_temporary, URL, Request).
  119
  120oauth_options([], []).
  121oauth_options([H0|T0], [H|T]) :-
  122	name_value(H0, Name, Value),
  123	oauth_option(Name, NameTo), !,
  124	H =.. [NameTo,Value],
  125	oauth_options(T0, T).
  126oauth_options([_|T0], T) :-
  127	oauth_options(T0, T).
  128
  129oauth_option(realm,      'openid.realm').
  130oauth_option(login_hint, login_hint).
  131
  132name_value(Name = Value, Name, Value) :- !.
  133name_value(Term, Name, Value) :-
  134	Term =.. [Name,Value].
  135
  136
  137%%	oauth_handle_redirect(Request)
  138%
  139%	HTTP handler that deals with the  redirect back from Google that
  140%	provides us the authorization code. This  Implements steps 3 and
  141%	4 of the OpenID Connect process:
  142%
  143%	  - Confirm anti-forgery state token
  144%	  - Exchange code for access token and ID token
  145
  146oauth_handle_redirect(Request) :-
  147	http_parameters(Request,
  148			[ state(State, []),
  149			  code(Code, [])
  150			],
  151			[ %form_data(Form)
  152			]),
  153	validate_forgery_state(State, Site, Redirect, ClientData),
  154	openid_connect_discover(Site, DiscDoc),
  155	key(client_id, ClientId),
  156	key(client_secret, ClientSecret),
  157	http_open(DiscDoc.token_endpoint,
  158		  In,
  159		  [ cert_verify_hook(cert_verify),
  160		    post(form([ code(Code),
  161				client_id(ClientId),
  162				client_secret(ClientSecret),
  163				redirect_uri(Redirect),
  164				grant_type(authorization_code)
  165			      ]))
  166		  ]),
  167	call_cleanup(json_read_dict(In, Response),
  168		     close(In)),
  169	jwt(Response.id_token, Claim),
  170	oauth_login(Claim, Response, DiscDoc, ClientData).
  171
  172%%	oauth_login(+Claim, +Response, +DiscDoc, +ClientData)
  173%
  174%	Handle the oauth claim. At least from Google, the claim contains
  175%	the following interesting fields:
  176%
  177%	  - sub:   (long) integer representing the id in Google
  178%	  - email: The user's email
  179%	  - email_verified: boolean
  180%
  181%	We now have two tasks. If `sub` is   known, we are done. If not,
  182%	we must make a new account. To  do   so,  we can prefill info by
  183%	extracting the Google  _user  profile   information_  using  the
  184%	_OpenID Connect_ method.
  185%
  186%	@see https://developers.google.com/accounts/docs/OpenIDConnect#obtaininguserprofileinformation
  187
  188oauth_login(Claim, _, _, ClientData) :-
  189	add_client_data(ClientData, Claim, Claim1),
  190	login_existing_user(Claim1), !.
  191oauth_login(_Claim, Response, DiscDoc, ClientData) :-
  192	key(client_id, ClientId),
  193	key(client_secret, ClientSecret),
  194	url_extend(search([ access_token(Response.access_token),
  195			    client_id(ClientId),
  196			    client_secret(ClientSecret)
  197			  ]),
  198		   DiscDoc.userinfo_endpoint,
  199		   URL),
  200	http_open(URL,
  201		  In,
  202		  [ cert_verify_hook(cert_verify)
  203		  ]),
  204	call_cleanup(json_read_dict(In, Profile),
  205		     close(In)),
  206	add_client_data(ClientData, Profile, Profile1),
  207	create_user(Profile1).
  208
  209add_client_data(ClientData, Dict, Dict) :- var(ClientData), !.
  210add_client_data(ClientData, Dict, Dict.put(client_data, ClientData)).
  211
  212validate_forgery_state(State, Site, Redirect, ClientData) :-
  213	(   forgery_state(State, Site, Redirect, ClientData, Stamp)
  214	->  retractall(forgery_state(State, Site, Redirect, ClientData, Stamp))
  215	;   throw(http_reply(not_acceptable('Invalid state parameter')))
  216	).
  217
  218anti_forgery_state(State) :-
  219	Rand is random(1<<100),
  220	variant_sha1(Rand, State).
  221
  222%%	openid_connect_discover(+Site, -Dict) is det.
  223%
  224%	True when Dicr represents _The Discovery document_.
  225
  226:- dynamic
  227	discovered_data/3.		% URL, Time, Data
  228
  229openid_connect_discover(Site, Dict) :-
  230	openid_connect_discover_url(Site, URL),
  231	(   discovered_data(URL, Dict0)
  232	->  Dict = Dict0
  233	;   discover_data(URL, Expires, Dict0),
  234	    cache_data(URL, Expires, Dict0),
  235	    Dict = Dict0
  236	).
  237
  238discover_data(URL, Expires, Dict) :-
  239	http_open(URL, In,
  240                  [ cert_verify_hook(cert_verify),
  241		    header(expires, Expires)
  242		  ]),
  243	json_read_dict(In, Dict),
  244	close(In).
  245
  246discovered_data(URL, Data) :-
  247	discovered_data(URL, Expires, Data0),
  248	get_time(Now),
  249	(   Now =< Expires
  250	->  Data = Data0
  251	;   retractall(discovered_data(URL, Expires, _)),
  252	    fail
  253	).
  254
  255cache_data(URL, Expires, Data) :-
  256	parse_time(Expires, _Format, Stamp), !,
  257	asserta(discovered_data(URL, Stamp, Data)).
  258cache_data(_, _, _).
  259
  260:- multifile
  261	openid_connect_discover_url/2.  262
  263openid_connect_discover_url(
  264    'google.com',
  265    'https://accounts.google.com/.well-known/openid-configuration').
  266
  267
  268		 /*******************************
  269		 *	      HOOKS		*
  270		 *******************************/
  271
  272%%	key(+Which, -Key) is det.
  273%
  274%	This hook must provide the Google API   keys.  Key is one of the
  275%	values below. The keys are obtained  from Google as explained in
  276%	https://developers.google.com/+/web/signin/add-button
  277%
  278%	  - client_id
  279%	  - client_secret
  280
  281%%	login_existing_user(+Claim) is semidet.
  282%
  283%	Called after establishing the identify of the logged in user.
  284%	Claim is a dict containing
  285%
  286%	  - sub:string
  287%	  String that uniquely indentifies the user inside Google.
  288%	  - email:string
  289%	  Email address of the user.
  290%	  - client_data:Term
  291%	  Present if oauth_authenticate/3 was called with the option
  292%	  client_data(Term).  Note that the term passed is a copy.
  293%
  294%	This call must return an HTML  document indicating that the user
  295%	logged in successfully or redirect  to   the  URL  supplied with
  296%	return to using http_redirect/3.
  297
  298%%	create_user(+Profile) is det.
  299%
  300%	Called after login_existing_user/1 fails and  the Google profile
  301%	for the user has been fetched. Contains  the same info as passed
  302%	to  login_existing_user/1  as   well    as   additional  profile
  303%	information  such  as  `family_name`,   `gender`,  `given_name`,
  304%	`locale`, `name`, `picture` and `profile`. Check the Google docs
  305%	for details.
  306%
  307%	This call creates a new user, typically after verifying that the
  308%	user   is   human    and    completing     the    profile.    As
  309%	login_existing_user/1, it must return a web page or redirect.
  310
  311
  312		 /*******************************
  313		 *	    SSL SUPPORT		*
  314		 *******************************/
  315
  316%%	cert_verify(SSL, ProblemCert, AllCerts, FirstCert, Error) is det.
  317%
  318%	Used by SSL to verify the certificate.
  319
  320:- public cert_verify/5.  321
  322cert_verify(_SSL, _ProblemCert, _AllCerts, _FirstCert, _Error) :-
  323        debug(ssl(cert_verify),'~s', ['Accepting certificate']).
  324
  325
  326		 /*******************************
  327		 *	    URI GOODIES		*
  328		 *******************************/
  329
  330%%	url_extend(+Extend, +URL0, -URL)
  331%
  332%	Extend a URL, typically by adding parameters to it.
  333
  334url_extend(search(Params), URL0, URL) :-
  335	uri_components(URL0, Components0),
  336	uri_data(search, Components0, Search0),
  337	extend_search(Search0, Params, Search),
  338	uri_data(search, Components0, Search, Components),
  339	uri_components(URL, Components).
  340
  341extend_search(Var, Params, String) :-
  342	var(Var), !,
  343	uri_query_components(String, Params).
  344extend_search(String0, Params, String) :-
  345	uri_query_components(String0, Params0),
  346	append(Params0, Params, AllParams),
  347	uri_query_components(String, AllParams).
  348
  349
  350%%	public_url(+Request, +Path, -URL) is det.
  351%
  352%	True when URL is a publically useable  URL that leads to Path on
  353%	the current server. Needed for  the   redirect  URL that we must
  354%	present with the authentication request.
  355
  356public_url(Request, Path, URL) :-
  357	http_current_host(Request, Host, Port,
  358			  [ global(true)
  359			  ]),
  360	setting(http:public_scheme, Scheme),
  361	set_port(Scheme, Port, AuthC),
  362	uri_authority_data(host, AuthC, Host),
  363	uri_authority_components(Auth, AuthC),
  364	uri_data(scheme, Components, Scheme),
  365	uri_data(authority, Components, Auth),
  366	uri_data(path, Components, Path),
  367	uri_components(URL, Components).
  368
  369set_port(Scheme, Port, _) :-
  370	scheme_port(Scheme, Port), !.
  371set_port(_, Port, AuthC) :-
  372	uri_authority_data(port, AuthC, Port).
  373
  374scheme_port(http, 80).
  375scheme_port(https, 443)