View source with formatted comments or as raw
    1/*  Part of SWI-Prolog
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        J.Wielemaker@vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (C): 2013-2018, VU University Amsterdam
    7			      CWI, Amsterdam
    8
    9    This program is free software; you can redistribute it and/or
   10    modify it under the terms of the GNU General Public License
   11    as published by the Free Software Foundation; either version 2
   12    of the License, or (at your option) any later version.
   13
   14    This program is distributed in the hope that it will be useful,
   15    but WITHOUT ANY WARRANTY; without even the implied warranty of
   16    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
   17    GNU General Public License for more details.
   18
   19    You should have received a copy of the GNU General Public
   20    License along with this library; if not, write to the Free Software
   21    Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
   22
   23    As a special exception, if you link this library with other files,
   24    compiled with a Free Software compiler, to produce an executable, this
   25    library does not by itself cause the resulting executable to be covered
   26    by the GNU General Public License. This exception does not however
   27    invalidate any other reasons why the executable file might be covered by
   28    the GNU General Public License.
   29*/
   30
   31:- module(recaptcha,
   32	  [ recaptcha//1,		% +Options
   33	    recaptcha_parameters/1,	% -HTTP parameter list
   34	    recaptcha_verify/2		% +Request, +HTTPParamList
   35	  ]).   36:- use_module(library(http/html_write)).   37:- use_module(library(http/http_open)).   38:- use_module(library(option)).   39:- use_module(library(debug)).   40:- use_module(library(http/json)).   41
   42/** <module> Add reCAPTCHA functionality to a form
   43
   44This module is a plugin for the   SWI-Prolog  HTTP/HTML framework to add
   45reCAPTCHA functionality to a form.  It works as follows:
   46
   47  1. Load library(http/recaptcha) and define the reCAPTCHA keys
   48     as described in key/2.
   49
   50  2. Create a form, typically using method('POST') and include,
   51     in addition to the data you request from the human user,
   52     the reCAPTCHA widget using e.g.,
   53
   54         \recaptcha([theme(red)])
   55
   56  3. In the handler of the form, you must ask for the recaptcha
   57     parameters and pass them to recaptcha_verify/2.  You can do
   58     that as follows:
   59
   60         process_recaptcha_form(Request) :-
   61		recaptcha_parameters(RecapthaParams),
   62		http_parameters(Recaptha,
   63				[ name(Name, []),
   64				  age(Age, []),
   65				  ...
   66				| RecapthaParams
   67				]),
   68		(   recaptcha_verify(Request, RecapthaParams)
   69		->  <process normal user fields>
   70		;   <you are not human>
   71		).
   72
   73@see examples/demo.pl contains a fully functional demo.
   74@compat This library is compliant with Google recaptcha v2.
   75*/
   76
   77
   78:- multifile
   79	key/2.   80
   81test_key(public,  '6LeIxAcTAAAAAJcZVRqyHh71UMIEGNQ_MXjiZKhI').
   82test_key(private, '6LeIxAcTAAAAAGG-vFI1TnRWxMZNFuojJ4WifJWe').
   83
   84
   85%%	recaptcha(+Options)// is det.
   86%
   87%	Display the reCAPTCHA widget.  Defined options are:
   88%
   89%	  * theme(+Theme)
   90%	  Set the theme.  The default theme is =clean=.
   91%
   92%	@see	https://developers.google.com/recaptcha/docs/customization
   93%		describes the available themes
   94
   95recaptcha(Options) -->
   96	{ (   key(public, PublicKey)
   97	  ->  true
   98	  ;   test_key(public, PublicKey)
   99	  ),
  100	  option(theme(Theme), Options, clean)
  101	},
  102	html_post(head, script([src('https://www.google.com/recaptcha/api.js'),
  103				async(async),
  104				defer(defer)
  105			       ], [])),
  106	html(div([ class('g-recaptcha'),
  107		   'data-theme'(Theme),
  108		   'data-sitekey'(PublicKey)
  109		 ], [])).
  110
  111%%	recaptcha_parameters(-List) is det.
  112%
  113%	List is a list  of  parameters   for  http_parameters/3  that is
  114%	needed for recaptcha_verify/2.
  115
  116recaptcha_parameters(
  117    [ 'g-recaptcha-response'(_Response, [])
  118    ]).
  119
  120
  121%%	recaptcha_verify(+Request, +Parameters) is semidet.
  122%
  123%	Is true if the user solved the   captcha correctly. Fails if the
  124%	user did not solve the captcha correctly  but there was no error
  125%	processing the request.
  126%
  127%	@error	recaptcha_error(Error) is raised if there was an error
  128%		processing the captcha.
  129%	@see	https://developers.google.com/recaptcha/docs/verify
  130%		lists the errors.
  131
  132recaptcha_verify(Request, Parameters) :-
  133	memberchk('g-recaptcha-response'(Response, _), Parameters),
  134	remote_IP(Request, Peer),
  135	(   key(private, PrivateKey)
  136	->  true
  137	;   test_key(private, PrivateKey)
  138	),
  139	debug(recaptcha, 'Verify: response ~p for IP ~p', [Response, Peer]),
  140	setup_call_cleanup(
  141	    http_open('https://www.google.com/recaptcha/api/siteverify',
  142		      In,
  143		      [ post(form([ secret(PrivateKey),
  144				    remoteip(Peer),
  145				    response(Response)
  146				  ]))
  147		      ]),
  148	    json_read_dict(In, Dict),
  149	    close(In)),
  150	debug(recaptcha, 'Recaptcha verify: ~p', [Dict]),
  151	(   is_dict(Dict, _),
  152	    Dict.get(success) == true
  153	->  true
  154	;   is_dict(Dict, _),
  155	    Dict.get(success) == false
  156	->  fail
  157	;   throw(error(recaptcha_error(Dict), _))
  158	).
  159
  160
  161remote_IP(Request, IP) :-
  162        memberchk(x_forwarded_for(IP0), Request), !,
  163	atomic_list_concat(Parts, ', ', IP0),
  164	last(Parts, IP).
  165remote_IP(Request, IP) :-
  166        memberchk(peer(Peer), Request), !,
  167        peer_to_ip(Peer, IP).
  168remote_IP(_, -).
  169
  170
  171peer_to_ip(ip(A,B,C,D), IP) :-
  172        atomic_list_concat([A,B,C,D], '.', IP).
  173
  174%%	key(+Which, -Key) is det.
  175%
  176%	This hook must unify Key to the reCAPTCHA public key if Which us
  177%	=public= and to the reCAPTCHA private key if Which is =private=.
  178%
  179%	We leave the key handling to a hook to accomodate different ways
  180%	for storing and transferring the   keys. A simple implementation
  181%	is:
  182%
  183%	  ==
  184%	  :- use_module(library(http/recaptcha)).
  185%
  186%	  :- multifile recaptcha:key/2.
  187%
  188%	  recaptcha:key(public,  'Public key goes here').
  189%	  recaptcha:key(private, 'Private key goes here').
  190%	  ==
  191%
  192%	When missing, a reserved test key pair is used.