1:- module(pluuid, [random_uuid/1, uuid_atom/2, uuid/1, uuid/2]).    2:- use_module(library(crypto), [crypto_n_random_bytes/2, hex_bytes/2]).    3:- use_module(library(list_util), [split/3]).    4
    5:- predicate_options(uuid/2, 2,
    6                     [ version(integer),
    7                       format(atom) ]).    8
    9% given a list of bytes in big-endian form, convert them to an integer
   10bytes_integer(Bs, N) :-
   11    foldl([B, N0, N1]>>(N1 is N0<<8 + B), Bs, 0, N).
   12
   13unsigned64_signed64(Un, Si) :-
   14    integer(Un),
   15    Un >= 0x8000_0000_0000_0000,
   16    !,
   17    Inv is 0xffff_ffff_ffff_ffff - Un,
   18    Si is -Inv - 1.
   19unsigned64_signed64(Un, Si) :-
   20    integer(Si),
   21    Si < 0,
   22    !,
   23    Inv is -Si - 1,
   24    Un is 0xffff_ffff_ffff_ffff - Inv.
   25unsigned64_signed64(Un, Un).
 random_uuid(-UUID) is det
UUID is a random version-4 UUID, represented as uuid(High64, Low64).
   29random_uuid(uuid(Hi, Lo)) :-
   30    crypto_n_random_bytes(8, HiBytes),
   31    bytes_integer(HiBytes, Hi64),
   32    % Set version in 4 sig bits of time_hi_and_version
   33    Hi_ is Hi64 /\ \ (0b1111 << 12 ),
   34    HiUn is Hi_ \/ (4 << 12),
   35    unsigned64_signed64(HiUn, Hi),
   36
   37    crypto_n_random_bytes(8, LoBytes),
   38    bytes_integer(LoBytes, Lo64),
   39    % Set 2 sig bits of clock_seq_hi_res to 0 & 1
   40    Lo_ is Lo64 /\ \ (1 << (64-6)),
   41    LoUn is Lo_ \/ (1 << (64-7)),
   42    unsigned64_signed64(LoUn, Lo).
 uuid_atom(-UUID, +Atom) is semidet
uuid_atom(+UUID, -Atom) is det
Atom is equal to the hexadecimal representation of the version-4 UUID
   47uuid_atom(uuid(Hi_, Lo_), A) :-
   48    integer(Hi_), integer(Lo_), !,
   49    unsigned64_signed64(Hi, Hi_),
   50    unsigned64_signed64(Lo, Lo_),
   51    TimeLow is (Hi >> 32),
   52    TimeMid is (Hi >> 16) /\ 0xffff,
   53    TimeHi is Hi /\ 0xffff,
   54    ClockSeq is (Lo >> 48) /\ 0xffff,
   55    Node is Lo /\ 0xffff_ffff_ffff,
   56    format(atom(TL), '~`0t~16r~8|', [TimeLow]),
   57    format(atom(TM), '~`0t~16r~4|', [TimeMid]),
   58    format(atom(TH), '~`0t~16r~4|', [TimeHi]),
   59    format(atom(CS), '~`0t~16r~4|', [ClockSeq]),
   60    format(atom(N), '~`0t~16r~12|', [Node]),
   61    atomic_list_concat([TL, TM, TH, CS, N], '-', A).
   62uuid_atom(uuid(Hi, Lo), A) :-
   63    atom(A), !,
   64    atom_chars(A, Chars),
   65    split(Chars, '-', CharParts),
   66    maplist(atom_chars, AtomParts, CharParts),
   67    maplist(hex_bytes, AtomParts, Bytes),
   68    maplist(bytes_integer, Bytes, Nums),
   69    [TimeLow, TimeMid, TimeHi, ClockSeq, Node] = Nums,
   70    Hi_ is TimeLow << 32 + TimeMid << 16 + TimeHi,
   71    Lo_ is ClockSeq << 48 + Node,
   72    unsigned64_signed64(Hi_, Hi),
   73    unsigned64_signed64(Lo_, Lo).
 uuid(-UUID) is det
Create a new, random v4 UUID as the atom representation. Copying the API of the built-in library(uuid)
   78uuid(UUID) :-
   79    random_uuid(U),
   80    uuid_atom(U, UUID).
 uuid(-UUID, +Options) is det
Copying the API of the built-in library(uuid)
   84uuid(_UUID, Options) :-
   85    member(version(V), Options),
   86    V \= 4, !,
   87    throw(error(domain_error(4, V),
   88                context(uuid/2, 'Only version 4 UUIDs supported'))).
   89uuid(UUID, Options) :-
   90    memberchk(format(integer), Options), !,
   91    random_uuid(uuid(SHi, SLo)),
   92    unsigned64_signed64(Hi, SHi),
   93    unsigned64_signed64(Lo, SLo),
   94    UUID is Hi << 64 + Lo.
   95uuid(UUID, _Options) :-
   96    uuid(UUID)