1:- module(login_crypto, [
    2              token_uname/2,
    3              make_login_cookie/2,
    4              password_hash/2
    5          ]).

Tools for crypto work on login cookies

I think token_uname and make_login_cookie are

   16:- use_module(library(crypto)).
 password_hash(+Plain:string, -Hash:atom) is det
Hash a password
   21password_hash(Plain, Hash) :-
   22    crypto_password_hash(Plain, Hash).
 token_uname(+Token:string, -Uname:text) is semidet
Succeeds returning the user name if the token is valid or fails if not
   29token_uname(Token, Uname) :-
   30    hex_bytes(Token, TokenList),
   31    length(Nonce, 12),
   32    append(Nonce, CipherTextCodes, TokenList),
   33    string_codes(CipherText, CipherTextCodes),
   34    get_crypto_key(Key),
   35    crypto_data_decrypt(CipherText,
   36                        'chacha20-poly1305',
   37                        Key,
   38                        Nonce,
   39                        RecoveredText,
   40                        []),
   41    split_string(RecoveredText, "/", "", [URLEncodedUName, ExpiresUtimeString]),
   42    number_string(Expires, ExpiresUtimeString),
   43    get_time(Now),
   44    Expires > Now,
   45    www_form_encode(URLEncodedUName, Uname).
   46
   47:- dynamic crypto_key/1.   48
   49get_crypto_key(Key) :-
   50    crypto_key(Key),
   51    !.
   52get_crypto_key(Key) :-
   53    catch(
   54        setup_call_cleanup(
   55            open('secret_identity_key', read, Stream),
   56            read(Stream, Key),
   57            close(Stream)
   58        ),
   59        error(existence_error(source_sink, _), _),
   60        (   create_crypto_key_file, % make sure we really wrote it
   61            get_crypto_key(Key),
   62            asserta(crypto_key(Key))
   63        )
   64    ).
   65
   66create_crypto_key_file :-
   67    crypto_n_random_bytes(32, Key),
   68    setup_call_cleanup(
   69        open('secret_identity_key', write, Stream),
   70        (   writeq(Stream, Key),
   71            write(Stream, '.'),
   72            flush_output(Stream)
   73        ),
   74        close(Stream)
   75    ).
   76
   77
   78make_login_cookie(UName, Cookie) :-
   79      www_form_encode(URLEncodedUName, UName),
   80      get_time(Now),
   81      Expires is floor(Now) + 86400,
   82      get_crypto_key(Key),
   83      atomics_to_string([URLEncodedUName, "/", Expires], PlainText),
   84      crypto_n_random_bytes(12, Nonce),
   85      crypto_data_encrypt(PlainText, 'chacha20-poly1305',
   86                          Key, Nonce, CipherText, []),
   87      string_codes(CipherText, CipherTextCodes),
   88      append(Nonce, CipherTextCodes, TokenList),
   89      hex_bytes(Cookie, TokenList)