1:- module(bc_hex, [
    2    bc_atom_hex/2, % +Atom, -HexAtom
    3    bc_hex_atom/2  % +HexAtom, -Atom
    4]).    5
    6:- use_module(library(memfile)).    7:- use_module(library(readutil)).
 bc_atom_hex(+Atom, -HexAtom) is det
Converts given atom into UTF-8-encoded hex atom.
   14bc_atom_hex(Atom, Hex):-
   15    atom_chars(Atom, InChars),
   16    setup_call_cleanup(
   17        new_memory_file(Handle),
   18        chars_to_hex(Handle, InChars, OutChars),
   19        free_memory_file(Handle)),
   20    atom_chars(Hex, OutChars).
 bc_hex_atom(+HexAtom, -Atom) is det
Converts given hex atom into UTF-8-encoded atom. Throws error(cannot_convert_hex(Up, Low)) when the hex atom cannot be converted.
   28bc_hex_atom(Hex, Atom):-
   29    atom_chars(Hex, InChars),
   30    setup_call_cleanup(
   31        new_memory_file(Handle),
   32        hex_to_chars(Handle, InChars, OutChars),
   33        free_memory_file(Handle)),
   34    atom_chars(Atom, OutChars).
   35
   36% Runs conversion through the
   37% memory file.
   38
   39hex_to_chars(Memfile, InChars, OutChars):-
   40    hex_to_memfile(InChars, Memfile),
   41    memfile_to_chars(Memfile, OutChars).
   42
   43% Runs conversion through the
   44% memory file.
   45
   46chars_to_hex(Memfile, InChars, OutChars):-
   47    chars_to_memfile(InChars, Memfile),
   48    memfile_to_hex(Memfile, OutChars).
   49
   50% Writes the list of characters
   51% into the memory file.
   52
   53chars_to_memfile(Chars, Memfile):-
   54    setup_call_cleanup(
   55        open_memory_file(Memfile, write, Stream, [ encoding(utf8) ]),
   56        chars_to_stream(Chars, Stream),
   57        close(Stream)).
   58
   59% Writes the list of characters
   60% into the stream.
   61
   62chars_to_stream([], _).
   63
   64chars_to_stream([Char|Chars], Stream):-
   65    put_char(Stream, Char),
   66    chars_to_stream(Chars, Stream).
   67
   68% Reads memfile into the list
   69% of characters.
   70
   71memfile_to_chars(Memfile, Chars):-
   72    setup_call_cleanup(
   73        open_memory_file(Memfile, read, Stream, [ encoding(utf8) ]),
   74        stream_to_chars(Stream, Chars),
   75        close(Stream)).
   76
   77% Reads stream into the list
   78% of characters.
   79
   80stream_to_chars(Stream, Chars):-
   81    get_char(Stream, Char),
   82    (   Char = end_of_file
   83    ->  Chars = []
   84    ;   Chars = [Char|Rest],
   85        stream_to_chars(Stream, Rest)).
   86
   87% Reads memfile into the list
   88% of hex characters.
   89
   90memfile_to_hex(Memfile, Out):-
   91    setup_call_cleanup(
   92        open_memory_file(Memfile, read, Stream, [ encoding(octet) ]),
   93        stream_to_hex(Stream, Out),
   94        close(Stream)).
   95
   96% Writes the list of hex characters
   97% into the memfile.
   98
   99hex_to_memfile(Chars, Memfile):-
  100    setup_call_cleanup(
  101        open_memory_file(Memfile, write, Stream, [ encoding(octet) ]),
  102        hex_to_stream(Chars, Stream),
  103        close(Stream)).
  104
  105% Writes the list of hex characters
  106% into the stream.
  107
  108hex_to_stream([], _).
  109
  110hex_to_stream([_], _).
  111
  112hex_to_stream([Up, Low|Chars], Stream):-
  113    hex(Hex),
  114    (   nth0(Upper, Hex, Up),
  115        nth0(Lower, Hex, Low)
  116    ->  Byte is Upper << 4 + Lower,
  117        put_byte(Stream, Byte)
  118    ;   throw(error(cannot_convert_hex(Up, Low)))),
  119    hex_to_stream(Chars, Stream).
  120
  121% Reads stream into the list
  122% of hex characters.
  123
  124stream_to_hex(Stream, Out):-
  125    get_byte(Stream, Byte),
  126    (   Byte = -1
  127    ->  Out = []
  128    ;   hex(Hex),
  129        Upper is Byte >> 4,
  130        Lower is Byte /\ 15,
  131        nth0(Upper, Hex, Up),
  132        nth0(Lower, Hex, Low),
  133        Out = [Up,Low|Rest],
  134        stream_to_hex(Stream, Rest)).
  135
  136% FIXME could have better representation?
  137
  138hex(['0', '1', '2', '3', '4', '5', '6', '7', '8', '9', 'a', 'b', 'c', 'd', 'e', 'f'])