1/*  File:    swi/memfilesio.pl
    2    Author:  Roy Ratcliffe
    3    Created: Feb 26 2022
    4    Purpose: I/O on Memory Files
    5
    6Copyright (c) 2022, Roy Ratcliffe, Northumberland, United Kingdom
    7
    8Permission is hereby granted, free of charge,  to any person obtaining a
    9copy  of  this  software  and    associated   documentation  files  (the
   10"Software"), to deal in  the   Software  without  restriction, including
   11without limitation the rights to  use,   copy,  modify,  merge, publish,
   12distribute, sublicense, and/or sell  copies  of   the  Software,  and to
   13permit persons to whom the Software is   furnished  to do so, subject to
   14the following conditions:
   15
   16    The above copyright notice and this permission notice shall be
   17    included in all copies or substantial portions of the Software.
   18
   19THE SOFTWARE IS PROVIDED "AS IS", WITHOUT  WARRANTY OF ANY KIND, EXPRESS
   20OR  IMPLIED,  INCLUDING  BUT  NOT   LIMITED    TO   THE   WARRANTIES  OF
   21MERCHANTABILITY, FITNESS FOR A PARTICULAR   PURPOSE AND NONINFRINGEMENT.
   22IN NO EVENT SHALL THE AUTHORS  OR   COPYRIGHT  HOLDERS BE LIABLE FOR ANY
   23CLAIM, DAMAGES OR OTHER LIABILITY,  WHETHER   IN  AN ACTION OF CONTRACT,
   24TORT OR OTHERWISE, ARISING FROM,  OUT  OF   OR  IN  CONNECTION  WITH THE
   25SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE.
   26
   27*/
   28
   29:- module(swi_memfilesio,
   30          [ with_output_to_memory_file/3,       % :Goal,+MemoryFile,+Options
   31            memory_file_bytes/2,                % ?MemoryFile,?Bytes:list
   32            put_bytes/1,                        % +Bytes:list
   33            same_memory_file/2                  % +MemoryFile1,+MemoryFile2
   34          ]).   35:- meta_predicate
   36    with_output_to_memory_file(0, +, +).   37:- predicate_options(with_output_to_memory_file/3, 3,
   38                     [ pass_to(open_memory_file/4, 4)
   39                     ]).

I/O on Memory Files

Bytes and octets

Both terms apply herein. Variable names reflect the subtle but essential distinction. All octets are bytes but not all bytes are octets. Byte is merely eight bits, nothing more implied, whereas octet implies important inter-byte ordering according to some big- or little-endian convention.

author
- Roy Ratcliffe */
 with_output_to_memory_file(:Goal, +MemoryFile, +Options) is det
Opens MemoryFile for writing. Calls Goal using once/1, writing to current_output collected in MemoryFile according to the encoding within Options. Defaults to UTF-8 encoding.
   60with_output_to_memory_file(Goal, MemoryFile, Options) :-
   61    setup_call_cleanup(
   62        open_memory_file(MemoryFile, write, Stream, Options),
   63        with_output_to(Stream, Goal),
   64        close(Stream)
   65    ).
 memory_file_bytes(?MemoryFile, ?Bytes:list) is det
Unifies MemoryFile with Bytes.
   71memory_file_bytes(MemoryFile, Bytes), var(MemoryFile) =>
   72    new_memory_file(MemoryFile),
   73    with_output_to_memory_file(put_bytes(Bytes), MemoryFile,
   74                               [ encoding(octet)
   75                               ]).
   76memory_file_bytes(MemoryFile, Bytes) =>
   77    memory_file_to_codes(MemoryFile, Bytes, octet).
 put_bytes(+Bytes:list) is det
Puts zero or more Bytes to current output.

A good reason exists for putting bytes rather than writing codes. The put_byte/1 predicate throws with permission error when writing to a text stream. Bytes are not Unicode text; they have an entirely different ontology.

See also
- Character representation manual section at https://www.swi-prolog.org/pldoc/man?section=chars for more details about the difference between codes, characters and bytes.
   92put_bytes([]) => true.
   93put_bytes([Byte|Bytes]) => put_byte(Byte), put_bytes(Bytes).
 same_memory_file(+MemoryFile1, +MemoryFile2) is semidet
Succeeds if, and only if, two memory files compare equal by content. Comparison operates byte-by-byte and so ignores any underlying encoding.
  101same_memory_file(MemoryFile1, MemoryFile2) :-
  102    setup_call_cleanup(
  103        open_memory_file(MemoryFile1, read, In1, [encoding(octet)]),
  104        setup_call_cleanup(
  105            open_memory_file(MemoryFile2, read, In2, [encoding(octet)]),
  106            same_bytes(In1, In2),
  107            close(In2)
  108        ),
  109        close(In1)
  110    ).
  111
  112same_bytes(In1, In2) :-
  113    get_byte(In1, Byte),
  114    get_byte(In2, Byte),
  115    (   Byte == -1
  116    ->  true
  117    ;   same_bytes(In1, In2)
  118    )