View source with raw 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)).

Add reCAPTCHA functionality to a form

This module is a plugin for the SWI-Prolog HTTP/HTML framework to add reCAPTCHA functionality to a form. It works as follows:

  1. Load library(http/recaptcha) and define the reCAPTCHA keys as described in key/2.
  2. Create a form, typically using method('POST') and include, in addition to the data you request from the human user, the reCAPTCHA widget using e.g.,
    \recaptcha([theme(red)])
  3. In the handler of the form, you must ask for the recaptcha parameters and pass them to recaptcha_verify/2. You can do that as follows:
    process_recaptcha_form(Request) :-
           recaptcha_parameters(RecapthaParams),
           http_parameters(Recaptha,
                           [ name(Name, []),
                             age(Age, []),
                             ...
                           | RecapthaParams
                           ]),
           (   recaptcha_verify(Request, RecapthaParams)
           ->  <process normal user fields>
           ;   <you are not human>
           ).
See also
- examples/demo.pl contains a fully functional demo.
Compatibility
- This library is compliant with Google recaptcha v2. */
   78:- multifile
   79	key/2.   80
   81test_key(public,  '6LeIxAcTAAAAAJcZVRqyHh71UMIEGNQ_MXjiZKhI').
   82test_key(private, '6LeIxAcTAAAAAGG-vFI1TnRWxMZNFuojJ4WifJWe').
 recaptcha(+Options)// is det
Display the reCAPTCHA widget. Defined options are:
theme(+Theme)
Set the theme. The default theme is clean.
See also
- https://developers.google.com/recaptcha/docs/customization describes the available themes
   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		 ], [])).
 recaptcha_parameters(-List) is det
List is a list of parameters for http_parameters/3 that is needed for recaptcha_verify/2.
  116recaptcha_parameters(
  117    [ 'g-recaptcha-response'(_Response, [])
  118    ]).
 recaptcha_verify(+Request, +Parameters) is semidet
Is true if the user solved the captcha correctly. Fails if the user did not solve the captcha correctly but there was no error processing the request.
Errors
- recaptcha_error(Error) is raised if there was an error processing the captcha.
See also
- https://developers.google.com/recaptcha/docs/verify lists the errors.
  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).
 key(+Which, -Key) is det
This hook must unify Key to the reCAPTCHA public key if Which us public and to the reCAPTCHA private key if Which is private.

We leave the key handling to a hook to accomodate different ways for storing and transferring the keys. A simple implementation is:

:- use_module(library(http/recaptcha)).

:- multifile recaptcha:key/2.

recaptcha:key(public,  'Public key goes here').
recaptcha:key(private, 'Private key goes here').

When missing, a reserved test key pair is used.