1/*
    2  BSD 2-Clause License
    3
    4  Copyright (c) 2018, Can Bican
    5  All rights reserved.
    6
    7  Redistribution and use in source and binary forms, with or without
    8  modification, are permitted provided that the following conditions are met:
    9
   10  * Redistributions of source code must retain the above copyright notice, this
   11    list of conditions and the following disclaimer.
   12
   13  * Redistributions in binary form must reproduce the above copyright notice,
   14    this list of conditions and the following disclaimer in the documentation
   15    and/or other materials provided with the distribution.
   16
   17  THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS"
   18  AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
   19  IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE
   20  DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT HOLDER OR CONTRIBUTORS BE LIABLE
   21  FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
   22  DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR
   23  SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   24  CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY,
   25  OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE
   26  OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
   27*/
   28
   29:- module(jwt_io, [jwt_encode/3, jwt_decode/3, jwt_decode_head/2]).

Json Web Tokens implementation

Generates and verifies Json Web Tokens.

The module requires libjwt to compile.

In addition to jwt_encode/3 and jwt_decode/3, the following settings are required for proper functionality:

RSA keys can be generated by:

ssh-keygen -t rsa -b 4096 -f sample.key
openssl rsa -in sample.key -pubout -outform PEM -out sample.key.pub

ECDSA keys can be generated by:

openssl ecparam -genkey -name secp256k1 -noout -out sample-private.pem
openssl ec -in sample-private.pem -pubout -out sample-public.pem
author
- Can Bican
See also
- https://jwt.io/
- https://github.com/benmcollins/libjwt
license
- BSD */
   70:- use_foreign_library(jwt_io).   71
   72:- use_module(library(http/json)).   73:- use_module(library(settings)).   74
   75:- setting(keys,            list(dict), [],   'Signing keys').   76:- setting(clock_tolerance, integer,    60,   'clock tolerance in seconds').   77:- setting(audience,        string,     "",   'audience of the jwt').   78
   79:- setting(blacklist_check, atom,       check_blacklist_default,  "predicate of arity 1 to check if a JTI is blacklisted").   80:- setting(blacklist_add,   atom,       add_to_blacklist_default, "predicate of arity 2 to add a JTI to blacklist with expiration").   81:- setting(jti_generator,   atom,       uuid,                     "predicate of arity 1 to generate a unique JTI").
 jwt_encode(+KeyId:atom, +Claims:dict, -Token:string) is semidet
Generates a JWT token.
Arguments:
KeyId- the key to use for signing the token
Claims- contents of the key
Token- resulting token
   97jwt_encode(Kid, Claims, Token) :-
   98  must_be(atom, Kid),
   99  must_be(dict, Claims),
  100  get_key_from_settings(Kid, Key),
  101  get_jti(Jti),
  102  claims_with_aud(Claims, ClaimsWithAud),
  103  claims_with_iat(ClaimsWithAud, ClaimsWithIat),
  104  claims_with_iss(ClaimsWithIat, Key, ClaimsWithIss),
  105  ClaimsNew = ClaimsWithIss.put(_{jti: Jti}),
  106  atom_json_dict(Data,ClaimsNew,[as(atom)]),
  107  jwt_encode_from_string(Data, Token, Key.key, Key.algorithm, Kid).
 jwt_decode(+Data:atom, -Payload:dict, +Options:options) is semidet
Decodes a generated JWT token.

The following options are recognized:

aud(+Audience)
Audience for the token - if the audiences don't match, decoding fails.
iss(+Issuer)
Issuer for the token - if the issuers don't match, decoding fails.
Arguments:
Data- signed JWT token
Payload- contents of the token
Options- options
  128jwt_decode(Data, Payload, Options) :-
  129  jwt_decode_head(Data, PayloadFirst),
  130  atom_json_dict(PayloadFirst, PayloadHeader, [as(string)]),
  131  atom_string(Kid, PayloadHeader.kid),
  132  get_key_from_settings(Kid, KeyDict),
  133  jwt_decode_from_string(Data, Payload, KeyDict),
  134  atom_json_dict(Payload, PayloadDict, [as(string)]),
  135  jwt_jti_valid(PayloadDict),
  136  jwt_exp_valid(PayloadDict),
  137  jwt_nbf_valid(PayloadDict),
  138  jwt_iss_valid(PayloadDict, Options),
  139  jwt_aud_valid(PayloadDict, Options),
  140  jwt_iat_valid(PayloadDict).
  141
  142jwt_decode_head(Data, Payload) :-
  143  jwt_parse_head(Data, Payload).
  144
  145get_jti(Jti) :-
  146  setting(jti_generator, Generator),
  147  call(Generator, Jti).
  148
  149check_blacklist_default(Jti) :-
  150  retract(blacklisted(Jti,Exp)),
  151  not_before_now(Exp),
  152  assertz(blacklisted(Jti,Exp)).
  153
  154check_blacklist_default(Jti) :-
  155  retract(blacklisted(Jti,Exp)),
  156  assertz(blacklisted(Jti,Exp)).
  157
  158add_to_blacklist_default(Jti, Exp) :-
  159  assertz(blacklisted(Jti,Exp)).
  160
  161jwt_jti_valid(Payload) :-
  162  setting(blacklist_check, BlacklistCheck),
  163  setting(blacklist_add, BlacklistAdd),
  164  current_prolog_flag(max_tagged_integer, MaxInt),
  165  (
  166    get_dict(jti, Payload, JtiPayload)
  167  ->
  168    not(call(BlacklistCheck, JtiPayload)),
  169    (
  170      get_dict(exp, Payload, ExpPayload)
  171    -> call(BlacklistAdd, JtiPayload, ExpPayload)
  172    ; call(BlacklistAdd, JtiPayload, MaxInt)
  173    )
  174  ; !
  175  ).
  176
  177jwt_nbf_valid(Payload) :-
  178  (
  179    get_dict(nbf, Payload, ExpPayload)
  180  -> not_after_now(ExpPayload)
  181  ; !
  182  ).
  183
  184jwt_exp_valid(Payload) :-
  185  (
  186    get_dict(exp, Payload, ExpPayload)
  187  -> not_before_now(ExpPayload)
  188  ; !
  189  ).
  190
  191jwt_aud_valid(Payload, Options) :-
  192  (
  193    option(aud(Aud), Options, ""),
  194    Aud \= ""
  195  -> Aud = Payload.aud
  196  ; !
  197  ).
  198
  199jwt_iss_valid(_, Options) :-
  200  option(iss(""), Options, ""),
  201  !.
  202
  203jwt_iss_valid(Payload, Options) :-
  204  IssPayload = Payload.get(iss),
  205  option(iss(Iss), Options, ""),
  206  Iss = IssPayload.
  207
  208jwt_decode_from_string(Data, Payload, Key) :-
  209  member(Key.type, ['RSA', 'ECDSA']),
  210  !,
  211  jwt_decode_from_string(Data, Payload, Key.algorithm, Key.public_key),
  212  !.
  213
  214jwt_decode_from_string(Data, Payload, Key) :-
  215  jwt_decode_from_string(Data, Payload, Key.algorithm, ''),
  216  !.
  217
  218claims_with_iss(C, K, CNew) :-
  219  (
  220    _ = K.get(iss)
  221  -> CNew = C.put(_{iss: K.get(iss)})
  222  ; CNew = C
  223  ).
  224
  225claims_with_iat(Claims, CNew) :-
  226  (
  227    _ = Claims.get(iat)
  228  -> CNew = Claims
  229  ; get_time(Now),
  230    NowT is floor(Now),
  231    CNew = Claims.put(_{iat: NowT})
  232  ).
  233
  234claims_with_aud(Claims, CNew) :-
  235  (
  236    setting(audience, Audience),
  237    Audience \= ""
  238  -> CNew = Claims.put(_{aud: Audience})
  239  ; CNew = Claims
  240  ).
  241
  242jwt_iat_valid(Payload) :-
  243  Iat = Payload.iat,
  244  Iat > 0,
  245  not_after_now(Iat).
  246
  247not_before_now(Epoch) :-
  248  get_time(Now),
  249  setting(clock_tolerance, Tolerance),
  250  NowTolerated is Now - Tolerance,
  251  NowTolerated =< Epoch.
  252
  253not_after_now(Epoch) :-
  254  get_time(Now),
  255  setting(clock_tolerance, Tolerance),
  256  NowTolerated is Now + Tolerance,
  257  NowTolerated > Epoch.
  258
  259get_key_from_settings(Kid, Key) :-
  260  setting(keys, Keys),
  261  get_kid(Kid, Keys, Key).
  262
  263get_kid(_, [], _) :- fail.
  264get_kid(Kid, [Key|_], KeyResult) :-
  265  Key.kid = Kid,
  266  read_key_file(Key, KeyResult),
  267  !.
  268get_kid(Kid, [_|Keys], KeyDict) :-
  269  get_kid(Kid, Keys, KeyDict).
  270
  271read_key_file(Key, Key) :-
  272  Key.type = 'HMAC',
  273  !.
  274read_key_file(Key,KeyRead) :-
  275  member(Key.type, ['RSA', 'ECDSA']),
  276  get_dict('key', Key, PrivateKeyFile),
  277  !,
  278  read_file_to_string(PrivateKeyFile, KeyStr, []),
  279  read_file_to_string(Key.public_key, PublicKeyStr, []),
  280  atom_string(KeyAtom, KeyStr),
  281  atom_string(PublicKeyAtom, PublicKeyStr),
  282  KeyRead = Key.put(_{key: KeyAtom, public_key: PublicKeyAtom}),
  283  !.
  284read_key_file(Key, KeyRead) :-
  285  member(Key.type, ['RSA', 'ECDSA']),
  286  read_file_to_string(Key.public_key, PublicKeyStr, []),
  287  atom_string(PublicKeyAtom, PublicKeyStr),
  288  KeyRead = Key.put(_{public_key: PublicKeyAtom}),
  289  !.
  290
  291
  292get_key_file(File, Key) :-
  293  read_file_to_string(File, KeyStr, []),
  294  atom_string(Key, KeyStr)