Write IEEE 754 floats in binary stream

Hi,

is there a way how to write a float in IEEE 754 binary format into atom or binary stream?
Such like
“Open(‘myfile.dat’, write,[type(binary)]),
format(BinaryStream,’~f’, [3.14156]).”

I’ve tried it but the number was written as character string “3.14156”, so the type binary was ignored?

Cheers

Hans

library(protobufs) has code that reads and writes “wire format” floats (and other types). These currently aren’t exported, but could easily be; and can be accessed even though they aren’t exported, e.g. protobufs:float64_codes/2
https://www.swi-prolog.org/pldoc/man?section=protobufs-wire-types

1 Like

write/1 and read/1 are (I think) the oldest IO primitives made available in Prolog, meant to handle persistent storage of terms in Prolog source code, with all the complexity that such task implies.

Fast binary term I/O could be what you are looking for, but in the following example, the output file size is 12 bytes, accounting (probably) for the term tag. So, if you need to adhere to some external protocol, the suggestion by @peter.ludemann is what you should try first.

:- module(binserialize,
          [serialize/0
          ,unserialize/0
          ]).

:- use_module(library(macros)).

#define(filename, 'binserialize.bin').

serialize :-
    setup_call_cleanup(
        open(#filename, write, Stream, [encoding(octet)]),
        fast_write(Stream, 3.14156),
        close(Stream)).

unserialize :-
    setup_call_cleanup(
        open(#filename, read, Stream, [encoding(octet)]),
        fast_read(Stream, Float),
        close(Stream)),
    writeln(Float).

PS: I wrote this silly snippet mainly because I was curious about the new library(macros).

Thanks for your answers! If I understand the docs correctly, neither the protobufs nor the fast_write allows a full control over the bit/Byte pattern written out as for example Erlang provides (In protobuf there is no way around the wire format, in fast_write I could not say “write single precession float in little endian”).
Context is to write binary files for GLTF, where for example I have to write 3 16bit integers (vertex indices) followed by 9 floats 32bit in 754 format (vertex coordinates), all in little endian.

Or do I missed something?

Cheers

Hans

Setting a stream to binary merely turns of newline and character encoding (e.g., UTF-8), turning the stream into a stream of raw bytes. There is a flag that causes this to raise an error if you use binary streams for text, but for historical reasons this is off by default.

format/2,3 are for text. I don’t really see much point in writing numbers as binary as there are many ways wire protocols exchange numbers. They can be fixed width, in which case they can be big or little endian, they can be width followed by bits, they can use the currently popular zigzag encoding and probably a bunch more. For floats we at least have 4/8 bytes and little/big endian. IEEE754 is surely dominant these days, but other formats exist.

Prolog itself is too high level to expose details such as integer and float formats to the user. Normally, I’d write at least the low level of a wire protocol interface in C(++). Often it is also worthwhile dealing with a bit larger chunks from C because Prolog stream access is relatively slow. Sometimes you find the stuff you need in e.g., the protobufs binding. The ffi pack can also be used. Its memory access facilities allow access to byte level representations of e.g., floats.

What is #define ? I tested the same lines on the latest SWIPL, but it just said “ERROR: Unknown procedure: (#)/1 (DWIM could not correct goal)”. Could you point where to read this new feature ?

The code for protobufs wire format is pretty straightforward, so you could use that as a starting point – probably it’s easiest to do in C; you could use float32_codes/2 as a starting point. Or you could use the result of float32_codes/2 and manipulate the resulting list of codes.

?- protobufs:float32_codes(1.5, C).
C = [0,0,192,63].

?- protobufs:float32_codes(-10.0, C).
C = [0,0,32,193].

?- protobufs:float32_codes(F, [0,0,160,191]).
F = -1.25.

I just grab from the example there.

Thanks. There seems many chances to use it, though I’m still unsuccessful to do, which I myself try to find what is missing.
(Maybe conflict with something on my term_expansion)

:- use_module(library(macros)).

#define(max_width, 100).

% ?-     100 < #max_width.
%@ ERROR: Arithmetic: `max_width/0' is not a function
%@ ERROR: In:
%@ ERROR:   [12] 100<#(..)

Indeed, that seems to be the curse of operators overloading in Prolog, given the reduced availability of scoping WRT other languages.

Macro expansion is realized using term_expansion/2, which is not used for the toplevel. So, macrs do not work at the toplevel. That could surely be added, but I’m not sure that adds anything useful.

Nope.

I see well, thanks. As for me, it would be surely useful also at toplevel because of my frequent use of macros there.

:- use_module(library(macros)).
#define(maxval, 100).

test:- 10 < #maxval.
% ?- listing(test).
%@ test :-
%@     10<100.
%@ 
%@ true.
% ?- test.
%@ true.

Note that you can misuse answer reuse at the toplevel :slight_smile:

6 ?- MaxVal = 100.
MaxVal = 100.

7 ?- 10 < $MaxVal.
MaxVal = 100.

I seldom use $ convention at toplevel. Anyway I don’t insist to use # also at toplevel. The current decision seems appropriate enough.