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