Skip to content

Commit 41a82a4

Browse files
committed
Add jwtks support
1 parent 3a5a20a commit 41a82a4

File tree

2 files changed

+57
-1
lines changed

2 files changed

+57
-1
lines changed

prolog/jwt_io.pl

Lines changed: 51 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -26,7 +26,7 @@
2626
OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
2727
*/
2828

29-
:- module(jwt_io, [jwt_encode/3, jwt_decode/3, jwt_decode_head/2]).
29+
:- module(jwt_io, [jwt_encode/3, jwt_decode/3, jwt_decode_head/2, setup_jwks/1]).
3030
/** <module> Json Web Tokens implementation
3131
3232
Generates and verifies Json Web Tokens.
@@ -70,6 +70,8 @@
7070
:- use_foreign_library(foreign(jwt_io)).
7171

7272
:- use_module(library(http/json)).
73+
:- use_module(library(http/http_client)).
74+
:- use_module(library(http/http_json)).
7375
:- use_module(library(settings)).
7476

7577
:- setting(keys, list(dict), [], 'Signing keys').
@@ -292,3 +294,51 @@
292294
get_key_file(File, Key) :-
293295
read_file_to_string(File, KeyStr, []),
294296
atom_string(Key, KeyStr).
297+
298+
299+
wrap_key(PubKeyString, PadStart, PadWidth, StrLength, Acc, Output) :-
300+
NewPadStart is PadStart + PadWidth,
301+
( NewPadStart < StrLength
302+
-> sub_string(PubKeyString, PadStart, PadWidth, _, SubString),
303+
format(string(NewAcc), "~s~s~n", [Acc, SubString]),
304+
wrap_key(PubKeyString, NewPadStart, PadWidth, StrLength, NewAcc, Output)
305+
; Output = Acc
306+
).
307+
308+
/* convert_jwt_to_key(+Key, -SettingsKey) is semidet.
309+
*
310+
* Converts a key from a JWKS endpoint to a key that is usable in the settings
311+
*/
312+
convert_jwk_to_key(Key, SettingsKey) :-
313+
Key.use = "sig", % key should be skipped if it is not sig
314+
Key.kty = "RSA", % only support RSA for the time being
315+
memberchk(PubKeyString, Key.x5c),
316+
string_length(PubKeyString, StrLength),
317+
wrap_key(PubKeyString, 0, 64, StrLength, "", WrappedKey),
318+
format(string(PubKeyFormatted),
319+
"-----BEGIN PUBLIC KEY-----~n~s-----END PUBLIC KEY-----",
320+
[WrappedKey]),
321+
tmp_file_stream(text, File, Stream),
322+
write(Stream, PubKeyFormatted),
323+
close(Stream),
324+
SettingsKey = _{kid: Key.kid,
325+
type: "RSA",
326+
algorithm: Key.alg,
327+
public_key: File}.
328+
329+
/* setup_jwks(+Endpoint) is nondet.
330+
*
331+
* Sets up a JWKS endpoint to use and set the key settings accordingly.
332+
* Only supports RSA for now and be wary that it overwrites the existing
333+
* configuration.
334+
*
335+
* Another limitation so far is that this is quite inefficient, as the pubkey
336+
* is being written to a temporary file and then read again by the kid
337+
* predicate. This module should probably be refactored entirely.
338+
*
339+
* It also assumes the auth0 JWKS structure.
340+
*/
341+
setup_jwks(Endpoint) :-
342+
http_get(Endpoint, Data, [json_object(dict)]),
343+
maplist(convert_jwk_to_key, Data.keys, Keys),
344+
set_setting(jwt_io:keys, Keys).

tests/jwt_io_jwt.plt

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -81,4 +81,10 @@ test(jti) :- jwt_encode('hmac256', _{sub: 'a'}, X), jwt_decode(X, _, []).
8181
test(jti, fail) :- jwt_encode('hmac256', _{sub: 'a'}, X), jwt_decode(X, Y, []), jwt_decode(X, Y, []).
8282
test(jti, fail) :- jwt_encode('hmac256', _{sub: 'a'}, X), jwt_decode(X, Y, []), not(jwt_decode(X, Y, [])), jwt_decode(X, Y, []).
8383

84+
test(jwks_endpoint) :-
85+
jwt_io:setup_jwks('https://terminushub.eu.auth0.com/.well-known/jwks.json'),
86+
setting(jwt_io:keys, Keys),
87+
Keys = [_{algorithm:"RS256",kid:"Njk1Rjk4RjdBRkJBNDI5RUU4RDhGQTlGQ0YzNDAwQTBDNzAyMDA2Mg",public_key: _,type:"RSA"},
88+
_{algorithm:"RS256",kid:"H2GzHR5oDAnl1QSsgnwgw",public_key:_,type:"RSA"}].
89+
8490
:- end_tests(jwt_io).

0 commit comments

Comments
 (0)