Google Groups no longer supports new Usenet posts or subscriptions. Historical content remains viewable.
Dismiss

Request for comments, Novacore the sequel to ISO modules

281 views
Skip to first unread message

Mostowski Collapse

unread,
Aug 17, 2022, 8:18:25 AM8/17/22
to
Now I have an idea for a novell Prolog core, called Novacore.
What should it be able to do? A few features from JavaScript:

a) Renaming Module Import
The have even renaming module import. For example one
can do in JavaScript:

const emitter = require('events');

But is there a Prolog system that has a renaming module import?
Like for example this here:

:- use_module(events as emitter).

b) Polyfills
In JavaScript new functionality can be added to old versions
via so called polyfills. On the module/class level, this requires
that you can do code injections, later mixins.

Although Prolog would be in a good position here, since for
example it has multifile predicates. But does this work for a
module system of a Prolog system? And how would a polyfill

exactly be done?

I tried this in Ciao Prolog playground, but there seems a couple
of other problems:

:- use_module(library(lists)).

lists:subtract([], _, R) :- !,
R = [].
lists:subtract([E|T], D, R) :- !,
( memberchk(E, D)
-> lists:subtract(T, D, R)
; R = [E|R1],
lists:subtract(T, D, R1)
).

I get quite a funny bouquet of errors:

ERROR: (lns 6-11) Predicate memberchk/2 undefined in source
ERROR: (lns 6-11) Bad module qualification of subtract/3,
predicate not imported from module lists
ERROR: (lns 6-11) Bad module qualification of subtract/3,
predicate not imported from module lists
ERROR: Aborted module compilation

If I am not totally mistaken the subtract/3 mixing works in SWI-Prolog
and in Jekejeke Prolog. Have to try again. But there could be issues
with reconsult, in general it makes a few things more complicated

concerning the Prolog system tooling. But frankly I didn’t use it so
often, there were a few use cases though.

Mostowski Collapse

unread,
Aug 17, 2022, 9:37:18 AM8/17/22
to
So what would be the benefit of Novacore? It would solve
some of the bottlenecks in Prolog systems. Somebody wrote:

"Surely if SWI-Prolog is the outlier I’m happy to change that,
considering that the impact is most likely low."

How can you do **widescale change** and semantic confluence
without waiting for every Prolog system, even without waiting
for SWI-Prolog? Thats what Polyfills do in JavaScript. But I don’t

know how popular they are right now. In the past there
was Babel, and it is still there:

Babel is a JavaScript compiler
Use next generation JavaScript, today.
https://babeljs.io/

Logtalk is kind of the Prolog Babel, with the difference that
Logtalk doesn’t do existing Prolog system module system
injection. But the Bable toolchain consists of more than only

Polyfills, some are similar to Logtalk again (codemods):

- Transform syntax
- Polyfill features that are missing in your target environment
(through a third-party polyfill such as core-js)
^- Source code transformations (codemods)
- And more!

To some extend there is also a third option besides the alternative
of if-then-else conditional Prolog compilation. You could also
use goal_expansion/2 to do some things.

Mostowski Collapse

unread,
Aug 17, 2022, 10:00:44 AM8/17/22
to
In as far the pure modules by Ciao Prolog are a good exercise.
Now imagine a pure+common module, which uses totally different
library than Ciao does currently have as a status quo. No changes

needed to the libraries that Ciao Prolog has, only a common context,
where the name space looks different and some common libraries
are provided. So the Ciao Prolog system would see the current

status quo of Ciao, and the user would see the common. Would this
be possible, such a Chimera Prolog? Or can Ciao Prolog remove
built-ins (for pure) but not add built-ins (for pure+common)?

Mostowski Collapse

unread,
Aug 17, 2022, 4:28:58 PM8/17/22
to
Since I have already a prototype running, but it needs a little
bit more preparation, here is a new term coined. We have
already the new term Novacore, and now comes the following:

One could pursue a new approach, based on a Novacore
with what could be coined Liblets. A Liblet would be kind of package,
that would switch in what is normally more cohesively connected

inside a Prolog system. But the Prolog systems that would aim at
supporting Novacore and Liblets, would need some refactoring
and deossification. So that the Prolog system specific Liblet

becomes switchable. One way to do it, is to have the Prolog
system depend on an internal Liblet not visible to the outside, so
that the switchable Liblets become possible. One could then

experiment with a least common multiple (LCM) Liblet in
each Prolog system that has a Novacore. The LCM Liblet
would be the fusion of various Liblets or even a totally different

setup concerning the name space of this LCM Liblet and the
content of this LCM Liblet. LCM Liblet would be the new name
for Common Prolog. Why is a Novacore needed, and not the

ISO core standard suitable. Various reasons, a) intollerant syntax of
some ISO core implementations, b) other intollerant features of some
ISO core implementations, that prohibit Liblets modelled after or

directly loaded from existing more tollerant Prolog systems.

Mostowski Collapse

unread,
Aug 31, 2022, 5:59:37 AM8/31/22
to
Was refactoring Dogelog Player. It has now a couple
of libraries, making use of the new system_url to fetch them.

- library(compat): New idea of a library, has things like tab/1.
- library(sequence): Reduced library(adanced/sequence) from formerly Jekejeke Prolog.
- library(aggregate): Reduced library(adanced/aggregate) from formerly Jekejeke Prolog.
- library(lists): Like library(basic/lists) from formerly Jekejeke Prolog.

library(sequence) and library(aggregate) are implemented via
the new change_arg/3 in Dogelog Player, unlike Jekejeke Prolog
which uses some Java pivot datastructure.

The new system_url to fetch does not change Dogelog Player
performance. Dogelog Player is still not an extremly fast
Prolog system, it might beat Tau Prolog but otherwise it has

rather modest performance. But change_arg/3 gives nice
performance. Its the better solution than bb_put/2 and bb_get/2,
which is module local, and BTW will not work in multi-threading,

if it has SICStus semantics it is for "blackboard" communication
between multiple threads. The bb_ stands for "blackboard". So its
not thread-local. What is Scryer Prolog thinking?

Anyway, here some performance:

/* Scryer Prolog "v0.9.0-175-g6b8e6204" */
?- use_module(library(iso_ext)).
true.
?- time((call_nth((between(1,1000,_),call_nth(between(1,1000,_),_)),_), fail; true)).
% CPU time: 4.719s
true.

/* Dogelog Player 1.0.2, nodejs */
?- ensure_loaded(library(sequence)).
true.
?- time((call_nth((between(1,1000,_),call_nth(between(1,1000,_),_)),_), fail; true)).
% Wall 1763 ms, gc 4 ms, 6250971 lips
true.

/* SWI-Prolog, 8.5.14 */
?- time((call_nth((between(1,1000,_),call_nth(between(1,1000,_),_)),_), fail; true)).
% 5,002,004 inferences, 0.484 CPU in 0.473 seconds (102% CPU, 10326718 Lips)
true.

Mostowski Collapse

unread,
Aug 31, 2022, 6:04:36 AM8/31/22
to
The implementation goes:

bb_put(Key, Value) :-
( atom(Key) ->
'$store_global_var'(Key, Value)
; type_error(atom, Key, bb_put/2)
).

And then bb_put/2 is used in Scryer Prologs call_nth/2.
How do you want to use this in a multi-threaded Prolog system?

LMAO!

Mostowski Collapse

unread,
Aug 31, 2022, 6:10:30 AM8/31/22
to
I guess the SWI-Prolog implementation of call_nth/2 can
be used with multi-threading. So does the formerly Jekejeke
Prolog implementation, can be used with multi-threading

as well. Performance for formerly Jekejeke Prolog with
JDK 1.8, even bettern than that for SWI-Prolog:

?- time((call_nth((between(1,1000,_),call_nth(between(1,1000,_),_)),_), fail; true)).
% Threads 359 ms, GC 6 ms, Up 372 ms (Current 08/31/22 12:07:16)
true.

Cannot test Ciao Prolog since it doesn't have call_nth/2.
Same for ECLiPSe Prolog, I don't find a predicate that goes
exactly by the name call_nth/2,

maybe there is a substitute?

Mostowski Collapse

unread,
Aug 31, 2022, 1:18:28 PM8/31/22
to
End-users have really problems with embeding
Prolog into HTML pages by themself. For example
an simple advice as follows from Tau Prolog:

get_by_id(writeme, WriteMe),
open(WriteMe, write, Stream),
set_output(Stream),
...
write(Formula)

doesn't work, when the stream does a
innerHTML += for the writeme element. What
would then be needed is:

get_by_id(writeme, WriteMe),
open(WriteMe, write, Stream),
set_output(Stream),
...
term_atom(Formula, FormulaAtom),
xml_ecape(FormulaAtom, FormulaEscaped),
write(FormulaEscaped)

I guess xml_escape/2 exists already since
1990's when the world's first web server, was
developed and implemented by Berners-Lee

on a NeXTcube computer. But its even
worse, does Tau Prolog have a term_atom/2?

Mostowski Collapse

unread,
Aug 31, 2022, 1:22:32 PM8/31/22
to
So a Code Playground where you can
simply do the following, as currently
available from dogelog.js:

<script type="application/x-dogelog">
... Dogelog Player code goes here ...
</script>

Is much simpler. Thanks to the Novacore,
if I have time, I will maybe provide also:

<script type="application/x-swi">
... SWI-Prolog code goes here ...
</script>
<script type="application/x-ciao">
... Ciao Prolog code goes here ...
</script>

And if in 100 years from now, the stubborn
Prolog community has decided on some PEPs,
could maybe even do:

<script type="application/x-prolog">
... Prolog code goes here ...
</script>

Mostowski Collapse

unread,
Oct 9, 2022, 7:06:09 PM10/9/22
to
I would like to have nice test cases for Novacore.
For sure floats would be part of Novacore. SWI-Prolog
publish its new release 8.5.18. And it says it does now

do to_nearest rouding more consequently. What does
that mean? Wiki tells me there are at least two “to nearest”:

- Round to nearest, ties to even – rounds to the nearest value;
if the number falls midway, it is rounded to the nearest value
with an even least significant digit.

- Round to nearest, ties away from zero (or ties to away) – rounds
to the nearest value; if the number falls midway, it is rounded to
the nearest value above (for positive numbers) or below (for negative numbers).

https://en.wikipedia.org/wiki/IEEE_754#Roundings_to_nearest 1

But then in Java BigDecimal there are even 3 “to nearest”,
HALF_EVEN, HALF_UP and HALF_DOWN.





Mostowski Collapse

unread,
Oct 9, 2022, 7:12:39 PM10/9/22
to
I guess the to_nearest should be HALF_EVEN. Was
lazy making manual test cases, so used a fuzzer.
The fuzzer test cases might not be that good, especially

for HALF_EVEN, since they might not pick up the border
cases, but nevertheless its a first start. Might do more
test cases. The test cases are simply:

fuzzer :-
L is -(1<<100),
H is (1<<100)+1,
between(1, 100, N),
random(L, H, X),
Y is float(X),
write(case(N, X, Y)), write('.'), nl,
fail.
fuzzer.

My Prolog systems, formerly Jekejeke Prolog and
Dogelog Player on its various target platforms, all
pass these test cases.

Mostowski Collapse

unread,
Oct 9, 2022, 7:13:46 PM10/9/22
to
Here are some very first results for other Prolog systems:

/* SWI-Prolog 8.5.18 (Windows and WASM) Ok */
?- case(N, X, Y), Y =\= float(X).
false.

/* Trealla Prolog 2.4.3 Ok */
?- case(N, X, Y), Y =\= float(X).
false.

/* Scryer Prolog 0.9.0 Nok */
?- case(N, X, Y), Y =\= float(X).
N = 1, X = -572504891324561953821040518484, Y = -5.7250489132456196e29
; N = 3, X = 884996183305110611102854483978, Y = 8.849961833051106e29
; N = 4, X = 1251939306673717603656775488197, Y = 1.2519393066737177e30
Etc..

So somehow these test cases already do their job!

Mostowski Collapse

unread,
Oct 9, 2022, 7:14:20 PM10/9/22
to
More results:

/* Ciao Prolog 1.22.0 (WSL and WASM) Ok */
?- case(N, X, Y), Y =\= float(X).
no

/* ECLiPSe Prolog 7.0.61 Nok */
?- case(N, X, Y), Y =\= float(X).
N = 1
X = -572504891324561953821040518484
Y = -5.7250489132456196e+29
Etc..

Mostowski Collapse

unread,
Oct 10, 2022, 2:57:43 AM10/10/22
to
Here is a better fuzzer, it has a higher mean lsb/1 value,
and therefore mostlikely tests more HALF_EVEN:

?- aggregate_all(sum(N), (case(_,X,_), N is lsb(abs(X))), S), A is S/100.
S = 94,
A = 0.94.

?- aggregate_all(sum(N), (case2(_,X,_), N is lsb(abs(X))), S), A is S/100.
S = 5050,
A = 50.5.

The fiuzzer reads as follows:

fuzzer2 :-
between(1, 100, N),
L is -(1<<N),
H is (1<<N)+1,
random(L, H, X),
Z is X<<(100-N),
Y is float(Z),
write(case2(N, Z, Y)), write('.'), nl,
fail.
fuzzer2.

Mostowski Collapse

unread,
Oct 10, 2022, 2:59:43 AM10/10/22
to
It indeed trip wires the newest SWI-Prolog:

/* SWI-Prolog 8.5.18 Nok */
?- case2(N, X, Y), Z is float(X), Y =\= Z.
N = 56,
X = -1190359501396335678156200476672,
Y = -1.1903595013963357e+30,
Z = -1.1903595013963356e+30 ;
false.

The test case is ok in all my systems, like formerly
Jekejeke Prolog and Dogelog Player. The test
case is also ok here:

/* Trealla Prolog 2.4.3 Ok */
?- case2(N, X, Y), Y =\= float(X).
false.

/* Ciao Prolog 1.22.0 Ok */
?- case2(N, X, Y), Y =\= float(X).
no

Mostowski Collapse

unread,
Oct 12, 2022, 8:11:16 AM10/12/22
to
There are much more tripwires, and its not
related to negative bigints per se:

/* SWI-Prolog 8.5.18 */
?- case3(N, X, Y), Y =\= float(X).
N = 12,
X = 548500250785140154065267720192,
Y = 5.485002507851401e+29 ;
N = 37,
X = 503487689179869862254742601728,
Y = 5.034876891798698e+29 ;
N = 44,
X = -828141981914306499269539921920,
Y = -8.281419819143066e+29 ;
N = 69,
X = -124851129191269336172294307840,
Y = -1.2485112919126934e+29 ;
N = 95,
X = 594779305038924597107611402240,
Y = 5.9477930503892456e+29 ;
false.

Interesting? Thats probably some material fur
further analysis. Need to reactivate my SWI-Prolog
based float_half_even/2. If you analyse the

float_half_even/2 you could find the execution
paths that these examples are using and whether
there is something in common. But this only works

if your system uses fast path float/1, if it uses
a rational number based bigint to float conversion,
the analysis possibly not so helpful. Although a

rational number based float conversion might
show some denominator in the form 2^k, for
some k, and yet all its logic could be translated

to getbit/1, lsb/1, etc..

Mostowski Collapse

unread,
Oct 12, 2022, 1:46:58 PM10/12/22
to
Some suspicion about the random number skewing.
Mostlikely #define MAX_URANDOMM_ITER is too low. See
here what GMP does. And it then falls back to low quality result:

if (count == 0)
/* Too many iterations; return result mod n == result - n */
mpn_sub_n (rp, rp, np, size);
https://salsa.debian.org/science-team/gmp/-/blob/master/mpz/urandomm.c

Note that the example interval [0…2^n+1) is a very nasty non power
of 2 interval. That I was using a nasty interval was rather not planned,
when writing the fuzzer, just some accident.

In my implementation I have no MAX_URANDOMM_ITER limit.
My suspiciion, therefore it generates a better probability shaping
on my side, which can be even measured,

already for 100 bits? Is this the reason? Or its some other bug
in mpz_urandomm() caused by the last limb cmp juggling?

Mostowski Collapse

unread,
Oct 12, 2022, 1:48:05 PM10/12/22
to
I didn’t test the random/1 evaluable function in Trealla and Cliao yet.
Cannot run the same test case in Trealla Prolog or Ciao Prolog,
too much stuff missing:

- Trealla Prolog: Didn’t find bigint random.

- Ciao Prolog: Found some random, with an incompatible
protocol to SWI-Prolog, different meaning of the parameters,
but there is so much other stuff missing, like
msb/1, aggregate_all/3, etc…

Mostowski Collapse

unread,
Oct 12, 2022, 4:22:29 PM10/12/22
to
On Ciao Prolog its:
random(0,M,...)

On SWI-Prolog its:
random(0,M+1,...)

Should there be a discussion about random/3, its protocoll?
I don’t know, what are the plans of Ciao Prolog and SWI-Prolog?
I don’t know? Is there a road map? I don’t know.

Recently SWI-Prolog deprecated random/3 and introduced
random_between/3 with a different protocoll. Maybe this can
point the way forward? I am more interested about the

skewness here, and not the protcoll of some random API.
Skewed shouldn’t mean screwed. Its quite possible that a
skewed random generator can be fixed.

Mostowski Collapse

unread,
Oct 13, 2022, 8:53:46 AM10/13/22
to
So maybe the requirement is eclectic? A non skewed
random ganerator for bigints. Often power of 2 is only
required or smallint is enough.

Ha Ha, a Casino website could be interested that their
random generators are not skewed. Or maybe they even
go for a particular skewed random generator?

What if the users of the Casino website figure out the
skewing and play accordingly? I am thinking of games
like roulette or card games. So its in their own interest?

Legitimacy & Regulation of the RNG
There are a number of independent companies which specialise in iGaming testing.
https://www.casinoguardian.co.uk/casino-guide/random-number-generator/

Mostowski Collapse

unread,
Oct 13, 2022, 10:32:09 AM10/13/22
to
2 out of 3 Prolog system cannot generate uniform random
bigints? Don't know yet, have to dig deeper. Strange that
the below result has always 100.0:

The error in Ciao Prolog is much larger than in SWI-Prolog,
i.e. the distance to the expected value. Was using this query,
taking into account the different random/3 protocoll, and

manually compensating for the missing aggregate_all/3
and msb/1 evaluable function:

$ ciaosh
Ciao 1.22.0 (2022-09-28 21:20:35 +0200) [LINUXx86_64]
?- use_module(library(between)).

?- ['aggregate.p'].

?- E is (1<<100), M is (1<<101), K is (1<<20),
between(1,10,_), aggregate_all(sum(X),
(between(1,K,_), random(0,M,X)), S),
H is abs(S-E*K), msb(H,J), N is J-20, write(N), nl, fail; true.
100.0
100.0
100.0
100.0
100.0
100.0
100.0
100.0
100.0
100.0

And this helper code (file aggregate.p):

:- use_module(library(numlists)).
:- use_module(library(random)).

aggregate_all(sum(X), G, S) :-
findall(X, G, L),
sum_list(L, S).

msb(X, Y) :- Y is log(X)/log(2).

Mostowski Collapse

unread,
Oct 13, 2022, 2:16:02 PM10/13/22
to
Does the C floating point API have HALF_EVEN default?
Maybe, maybe not. Is there a test case to figure out
what rounding a system, Prolog or not, does, for its

floating point numbers, independent of some bigint
conversion issues? Was trying the folllowing test and got
some surprise. There was first quite some agreement:

/* SWI-Prolog 8.5.18 */
?- X is 665723957508124892951320985600.0+26388279066624.0.
X = 6.65723957508125e+29.

/* Ciao Prolog 1.22.0 */
?- X is 665723957508124892951320985600.0+26388279066624.0.
X = 6.65723957508125e29 ?

/* Trealla Prolog 2.4.3 */
?- X is 665723957508124892951320985600.0+26388279066624.0.
X = 6.65723957508125e+29.

/* Jekejeke Prolog 1.5.5 */
?- X is 665723957508124892951320985600.0+26388279066624.0.
X = 6.65723957508125E29.

Mostowski Collapse

unread,
Oct 13, 2022, 2:18:04 PM10/13/22
to
But then suddently:

/* Scryer Prolog 0.9.0 */
?- X is 665723957508124892951320985600.0+26388279066624.0.
X = 6.657239575081248e29.

/* ECLiPSe Prolog 7.0.61 */
?- X is 665723957508124892951320985600.0+26388279066624.0.
X = 6.6572395750812482e+29

?- X is 6.6572395750812482e+29-6.65723957508125E29.
X = -140737488355328.0.

Maybe this also explains the divergence in bigint to float conversion.
Maybe they have by accident a misconfigured FPU? Some init call
to the runtime system missing? Or a cheap floating point library?

But one is WSL2 and the other Windows!

Mostowski Collapse

unread,
Oct 13, 2022, 2:36:51 PM10/13/22
to
Have to dig deeper, could be a parsing problem.
For the first summand, I get:

/* SWI-Prolog */
?- X is 665723957508124892951320985600.0.
X = 6.65723957508125e+29.

/* ECLiPSe Prolog */
X is 665723957508124892951320985600.0.
X = 6.6572395750812482e+29

I am not yet at a test case, which would give me
some information about rounding.

Mostowski Collapse

unread,
Oct 13, 2022, 4:28:53 PM10/13/22
to
Looks like my system belongs to the 2 system that
cannot generate good random numbers? I guess the
system with a smaller value is possible the less good

random generator, because some periodicity was hit.
Java uses a Lehmer algorithm which has a very short
period and uses very few bits in its state. On the other

hand the Twister uses quite some bits I guess, and has
a much larger periodicity. Twister would be therefore the
better randum number generator.

Mostowski Collapse

unread,
Oct 14, 2022, 4:41:45 AM10/14/22
to
Now turning my attention to (/)/2. SWI-Prolog wants me
to use set_prolog_flag(iso, true), to get the semantics
of the ISO core standard, page 116.

But the fuzzer still finds the needle in the haystack.
Using more bits to the numerator, and I find:

/* Jekejeke Prolog 1.5.5 */
?- X is -15915286457581575168 / -238455449856.
X = 6.674322800000001E7.

/* SWI-Prolog 8.5.18 */
?- current_prolog_flag(iso, X).
X = true.

?- X is -15915286457581575168 / -238455449856.
X = 66743227.99999999.

Mostowski Collapse

unread,
Oct 14, 2022, 4:43:32 AM10/14/22
to
Now I have test cases so nasty, even Ciao Prolog and
SICStus Prolog are stumbling. Interestingly Ciao Prolog
and SICStus Prolog stumble at the exact same test cases.

/* Ciao Prolog 1.22.0 */
?- case4(N, P, Q, Y), Z is P/Q, Y =\= Z.
N = 3,
P = -138732791312937296168,
Q = 70775453,
Y = -1960182315087.9346,
Z = -1960182315087.9343 ? ;
no

/* SICStus Prolog 4.7.1 */
?- case4(N, P, Q, Y), Z is P/Q, Y =\= Z.
N = 3,
P = -138732791312937296168,
Q = 70775453,
Y = -1960182315087.9346,
Z = -1960182315087.9343 ? ;
no

Mostowski Collapse

unread,
Oct 14, 2022, 10:41:42 AM10/14/22
to
Last chapter of the testing campaign. Testing (**)/2 now.

BTW, this is a little cringe what the fuzzer found for Dogelog
Player on Python. One can try Python 3.11 and will get:

Python 3.11.0rc1 (main, Aug 8 2022, 11:30:54)
>>> 396** -1
0.002525252525252525
>>> 1/396
0.0025252525252525255

Same test case that makes SICStus Prolog tumbling. Such
surprises lower the pain of testing, make it rather addictive.

Mostowski Collapse

unread,
Oct 15, 2022, 8:30:29 AM10/15/22
to
Next challenge, how to keep my comparison matrice
small. There are so many JavaScript platforms, nodeJS,
browsers, and WTF they differ:

/* Chrome Windows Nok */
?- X is 1889**29.
X = 1.0250068783051206E95.

/* FireFox Windows Ok */
?- X is 1889**29.
X = 1.0250068783051207E95.

Mostowski Collapse

unread,
Oct 19, 2022, 10:42:37 AM10/19/22
to
Whats the Novacore bigint versus float mantra? The difference
between the two notions “less precise and more speed” versus
“more precise and less speed” can be maybe capture as follows:

- Less Precise and More Speed: Even if the arguments are bigint, and
have potentially more than 52 bit mantissa, they are always first
converted to float. So that the operation is only performed with 52
bit arguments, allow for faster processing.

- More Precise and Less Speed: If the arguments are bigint or if
the arguments are rational numbers or arbitrary floats, all bits are
taken into account. So that the operation is performed with more bits
than only 52 bits, resulting in slower processing.

Mostowski Collapse

unread,
Oct 19, 2022, 10:50:24 AM10/19/22
to
Theoretically in the intersection, when the arguments are already
52 bit mantissa, there should be no difference in speed and also
no difference in accuracy, except if the second mode is

also required to return more bits. So we also have for the
first mode the result is **always** required to be only a float.
Then there is mostlikely always a speed difference, and the

first mode is always faster and less accurate.

Mostowski Collapse

unread,
Oct 19, 2022, 10:51:45 AM10/19/22
to
Ok did some performance measurement. Basically used this harness.
Was reusing the test data, that was used for accuracy testing, so its
based on the same cases.p file:

% swi_perf
swi_perf :-
write('case, swi: '), time((between(1,20000,_),
case(_, X, Y), Y =\= float(X), fail; true)),
write('case2, swi: '), time((between(1,20000,_),
case2(_, X, Y), Y =\= float(X), fail; true)),
write('case3, swi: '), time((between(1,20000,_),
case3(_, X, Y), Y =\= float(X), fail; true)),
write('case4, swi: '), time((between(1,20000,_),
case4(_, P, Q, Y), Y =\= P/Q, fail; true)),
write('case5, swi: '), time((between(1,20000,_),
case5(_, P, Q, Y), Y =\= P/Q, fail; true)),
write('case6, swi: '), time((between(1,20000,_),
case6(_, P, Q, Y), Y =\= P**Q, fail; true)).

Mostowski Collapse schrieb am Mittwoch, 19. Oktober 2022 um 16:42:37 UTC+2:

Mostowski Collapse

unread,
Oct 19, 2022, 10:52:41 AM10/19/22
to
Woa! My Jekejeke Prolog (was using JDK 1.8) is quite a number cruncher,
on the other hand Dogelog Player (was using nodeJS) is lacking behind.
Inbetween the result of Prolog systems that I tested, results in milliseconds.

System case case2 case3 case4 case5 case6
jekejeke 270 266 255 305 361 539
ciao 344 343 343 386 386 544
eclipse 414 388 396 518 541 939
trealla 553 547 549 569 565 605
swi 989 941 979 528 532 861
scryer 889 857 872 1177 1188 1147
sicstus 1087 1083 1104 1221 1218 1226
dogelog 1171 1163 1171 1241 1300 1330

Mostowski Collapse

unread,
Oct 19, 2022, 9:55:47 PM10/19/22
to
Code inspection sometimes helps find defects:

/* Jekejeke Prolog Ok */
?- X is (2^53+1)*2^64+1, Y is float(X).
X = 166153499473114502559719956244594689, Y = 1.6615349947311452E35.

/* SWI-Prolog 8.5.20 Ok */
?- X is float(166153499473114502559719956244594689).
X = 1.6615349947311452e+35.

/* Ciao Prolog Nok */
?- X is float(166153499473114502559719956244594689).
X = 1.661534994731145e35 ?

Pitty my fuzzer didn't find it. But I guess I will manually add it.

Mostowski Collapse

unread,
Oct 19, 2022, 9:58:38 PM10/19/22
to
Explanation of the defect:

Mostly based on code from Torbjorn Granlund, Johan Andersson,
and Mats Carlsson (Ref: Knuth vol. 2 sec. 4.3.1)

flt64_t bn_to_float(bignum_t *bn) {
while (i > 1) {
f = f*norm2 + u;
https://github.com/ciao -lang/ciao/blob/master/core/engine/eng_bignum.c#L1043

I think a defect could be if HALF_EVEN prematurely
rounds down the value of f, and then later a value of u,
would indicate that this rounding down was not legit,

but float addition cannot help it.

Mostowski Collapse

unread,
Oct 19, 2022, 10:46:49 PM10/19/22
to
I added some hand picked test cases, from the
Ciao Prolog blooper, including some negative bigints.
Interestingly other Prolog systems are also pray to the

same blooper. In total I found that 3 Prolog systems have
this blooper, whereas Trealla only for 50%. Here are now
the number of failures from the new test cases:

% case3, trealla: 5
% case3, ciao: 10
% case3, sicstus: 10

Mostowski Collapse

unread,
Oct 25, 2022, 8:56:11 AM10/25/22
to
Woa! My testing campaign has not yet ended. Now I
found a test case, where the Unix platform also fails.
Was increasing the bits in the case6/3 fuzzer:

pow2(B, E, X) :- E < 0, integer(E), !, X is 1/(B^(-E)).
pow2(B, E, X) :- X is B^E.

?- current_prolog_flag(iso, X).
X = false.

/* SWI-Prolog 8.5.20 WLS2 Nok */
?- repeat, L is -(1<<15), H is (1<<15)+1,
M is -(1<<3), J is (1<<3)+1, random(L, H, P),
random(M, J, Q), pow2(P, Q, A), B is P**Q, A=\=B.
P = -18573,
Q = -7,
A = -1.3116730299820406e-30,
B = -1.3116730299820408e-30 .

Mostowski Collapse

unread,
Oct 25, 2022, 8:59:11 AM10/25/22
to
I have SWIPL on Unix platform only since weekend,
could not do this testing beforehand, so I guess I
need to update case6/3 test cases,

because they showed Unix platform completely
passing, which seems to be wrong. I used in the old
fuzzer 12 bits + 6 bits, the above uses 15 bits + 3 bits,

and new nasty test cases pop up. Its a test case where
JDK 19 non-strict also fails. Cool! I couldn’t believe that
it is that good. It was too good to be true.

So its also not that good!

/* Jekejeke Prolog 1.5.5, JDK 19 non-strict Nok */
?- X is -18573** -7.
X = -1.3116730299820408E-30.

Mostowski Collapse

unread,
Oct 25, 2022, 11:36:46 AM10/25/22
to
Nope the JDK 19 is correct here. Bug in long division?

/* SWI-Prolog 8.5.20 WSL2 */
?- current_prolog_flag(iso, X).
X = false.

?- X is 1/(18573^7).
X = 1.3116730299820406e-30.

?- X is float(1 rdiv (18573^7)).
X = 1.3116730299820408e-30.

Mostowski Collapse

unread,
Oct 25, 2022, 1:53:20 PM10/25/22
to
Enhanced test cases, new viewpoint. Now WASM is
the more accurate platform, both for SWI and Ciao.
JDK 19 is still ultra accurate. But I cant say that it

is always correctly rounded. For non-integer arguments
I found a faulty example for (**)/2, but the below test
cases only test integer arguments of (**)/2:

System (=:=)/2 (/)/2 (**)/2 Total Variant
jekejeke 0 0 0 0 JDK 19
dogelog 0 0 2 2 PyPy
swi 0 0 4 4 WASM
sicstus 10 0 2 12 Windows
trealla 5 0 11 16 WSL2
ciao 10 0 10 20 WASM
scryer 33 46 11 90 WSL2
eclipse 33 45 68 146 Windows

Mostowski Collapse

unread,
Oct 26, 2022, 10:01:01 AM10/26/22
to
Here is a trick to force Python compatibility mode, I guess
works for SWI-Prolog 8.5.20 which has improved rational
number rounding? Thats the incorrectly rounded result:

/* incorrectly rounded of the real number quotient */
?- X is 1267650600228229401496703205376 /
762385119722780192080867194597.
X = 1.662743103759914.
Now do switch on Python compatibility mode, and
watch the result getting correctly rounded:

/* Use this combo for Python compatibility:
prefer_rationals=true,
max_rational_size=0,
max_rational_size_action=float */
?- set_prolog_flag(prefer_rationals, true).
true.

?- set_prolog_flag(max_rational_size, 0).
true.

?- set_prolog_flag(max_rational_size_action, float).
true.

/* Correctly rounded of the real number quotient, via
detour over rational numbers, which are correctly
rounded since release 8.5.20 of SWI-Prolog? */
?- X is 1267650600228229401496703205376 /
762385119722780192080867194597.
X = 1.6627431037599143.

Mostowski Collapse

unread,
Oct 26, 2022, 10:02:15 AM10/26/22
to
BTW the real number quotient is this real number:

1267650600228229401496703205376 /
762385119722780192080867194597 =
1.66274310375991431383116365048...

Was using microsoft calculator desk accessory. But
maybe should do more testing of this new Python
mode trick. Nasty test cases might lure everywhere.

Mostowski Collapse

unread,
Nov 14, 2022, 5:21:11 PM11/14/22
to
My latest take on msb/2, in case a Prolog system
doesn't have this built-in. Some hi lo search:

% msb(+Integer, -Integer)
msb(0, N) :- !, N = -1.
msb(X, N) :-
msb(X, 1, N).

% msb(+Integer, +Integer, -Integer)
msb(X, H, N) :-
X < (1<<H), !,
L is H>>1,
msb(X, L, H, N).
msb(X, H, N) :-
J is H<<1,
msb(X, J, N).

% msb(+Integer, +Integer, +Integer, -Integer)
msb(_, L, H, N) :- L+1 =:= H, !,
N = L.
msb(X, L, H, N) :- M is (L+H) >> 1,
X < (1<<M), !,
msb(X, L, M, N).
msb(X, L, H, N) :- M is (L+H) >> 1,
msb(X, M, H, N).

But it is not a replacement for the real thing.
An msb/1 evaluable function still performs better.

Mostowski Collapse

unread,
Nov 14, 2022, 5:31:28 PM11/14/22
to
So when will all Prolog system have these basic
evaluable functions and predicates?

msb/1: Return most significant bit of an integer
lsb/1: Return least significant bit of an integer
testbit/2: Succeed if bit of integer is set, otherwise fail.
divmod/4: Succeed with div and mod.

Scryer Prolog doesn't have these built-ins. So emulating
them makes it utterly slow. Using the hi lo approach for msb:

/* Scryer Prolog 0.9.1 WSL2 */
?- member((N,K),[(53,2600),(1024,150),(8192,9)]),
time((between(1,K,_), mp_pi(N, _), fail; true)), fail; true.
% CPU time: 4.240s
% CPU time: 5.621s
% CPU time: 7.718s
% true.

But it seems that bigints are not that fast, with ECLiPSe Prolog
which does not have these built-ins the hi lo isn't that bad:

/* ECLiPSe Prolog 7.1.12 Windows */
?- member((N,K),[(53,2600),(1024,150),(8192,9)]),
time_eclipse((between(1,K,_), mp_pi(N, _), fail; true)), fail; true.
0.904113500000676 sec
1.78132879998884 sec
1.56477859998995 sec

The best is always SWI-Prolog. It picks up trends and provides
functionallity so that the end-user can profit:

/* SWI-Prolog 8.5.20 Windows GMP */
?- member((N,K),[(53,2600),(1024,150),(8192,9)]),
time((between(1,K,_), mp_pi(N, _), fail; true)), fail; true.
% 8,699,603 inferences, 0.875 CPU in 0.879 seconds (100% CPU, 9942403 Lips)
% 7,952,250 inferences, 1.047 CPU in 1.064 seconds (98% CPU, 7596179 Lips)
% 3,771,657 inferences, 0.656 CPU in 0.673 seconds (97% CPU, 5747287 Lips)
true.

Whats wrong with the other Prolog systems, such as Scryer
Prolog and ECLiPSe Prolog that don't provide these built-ins?

Are they in a comatose sleeping beauty sleep?

Mostowski Collapse

unread,
Nov 17, 2022, 9:08:51 AM11/17/22
to
The best I can do for Dogelog Player, concerning
msb/1 and the JavaScript platform. Just imagine
the speed if JavaScript would have a real msb/1
or bitlength/1, so that we don't need this nonsense?

function bigint_msb(alpha) {
alpha = alpha.toString(16);
return 31 - Math.clz32(hexvalue(alpha.codePointAt(0))) + (alpha.length - 1)*4;
}

This is a known problem that bigint has no msb/1 or
bitlength/1 in JavaScript as of now. Nevertheless I now
easily beat Scryer Prolog even with Dogelog Player.
Comparing to the hi lo search msb I get these results:

/* Dogelog Player 1.0.3 Windows nodeJS */
?- member((N,K),[(53,2600),(1024,150),(8192,9)]),
time((between(1,K,_), mp_pi(N, _), fail; true)), fail; true.
% Wall 4136 ms, gc 10 ms, 2539128 lips
% Wall 4346 ms, gc 104 ms, 2219962 lips
% Wall 3876 ms, gc 88 ms, 1180529 lips
true.

Also unlike Scryer Prolog, for larger bigints, i.e. 8192
the timing doesn't go up, it rather goes down. Probably some
alternative bigint multiplication methods etc.. kick in for
larger bigints, and they are missing in Scryer Prolog for

the Rust based bigints? They are still in its fancy? Also
Scryer Prolog would fare better if it had a native msb/1.

Mostowski Collapse

unread,
Nov 17, 2022, 9:21:33 AM11/17/22
to
The effect that computation gets faster for larger bigint
is also seen for Python, when I use the PyPy interpreter.
I guess it has also to do with the effort needed to

promote a smallint to a bigint, either before an operation
or after an operation. Another speculation would be, that
the bigint operations slow down the frequency of my

Dogelog Player garbage collection, since this frequency
is not yet adaptive. But the larger bit test case even
beats Scryer Prolog, now beaten by Python/PyPy:

/* Dogelog Player 1.0.3 Windows PyPy */
?- member((N,K),[(53,2600),(1024,150),(8192,9)]),
time((between(1,K,_), mp_pi(N, _), fail; true)), fail; true.
% Wall 18696 ms, gc 799 ms, 561771 lips
% Wall 12737 ms, gc 730 ms, 757550 lips
% Wall 7126 ms, gc 339 ms, 642182 lips
true.

The 7126 ms (Dogelog Player on PyPy) compared to the
7.718s (Scryer Prolog) is ca. 10% faster. I never though
that Dogelog Prolog on the Python platform could do

that, since Python is rather annonyingly slow.

Mostowski Collapse

unread,
Jan 11, 2023, 3:45:30 PM1/11/23
to
I guess its time to talk about DOM APIs inside Prolog,
and making them mature and portable. I am planning
to adopt the Tau Prolog DOM API.

But I have two DOM APIs in mind:

- Stateless DOM API: Basically Tau Prolog is a stateless
DOM API. All API calls have all the necessary parameters,
there is nothing implicit right?

- Statefull DOM API: On the other hand so far, in Dogelog
Player, I have used a statefull DOM API. With a notion
of cursor, you can imagine Turtle graphics, only the Turtle

is not a Turtle with location and orientation, but a node
somewhere in a DOM tree.

My plan is to give the Statefull DOM API a new try, but
bootstrapping it from the a Stateless DOM API. Eh voila
I am already banging my head:

DOM API: How get last child efficiently?
https://github.com/tau-prolog/tau-prolog/issues/340

Mostowski Collapse

unread,
Jan 11, 2023, 3:52:46 PM1/11/23
to
Ha Ha ChatGPT is trolling me. You can search last_child
in Tau Prolog current GitHub, not a single find.

https://github.com/tau-prolog/tau-prolog/search?q=last_child

Or try this:

:- use_module(library(dom)).
?- last_child(foo, bar).
uncaught exception: error(existence_error(procedure,last_child/2),top_level/0)

Nevertheless ChatGPT halucinates something perfectly plausible:

Q: How get DOM last child in Tau Prolog programming language.

A: In Tau Prolog, you can use the built-in predicate
"last_child/2" to get the last child of a DOM element.

The predicate takes two arguments:

The DOM element for which you want to get
the last child (the parent element)
A variable that will be bound to the last child element

Example usage:

Copy code
last_child(parent_element, LastChild),
You have to unify the parent element with a variable
that has been initialized as a DOM element .

Please note that my knowledge cut off on Tau-Prolog is
from 2021 and this predicates could be deprecated or
changed so I recommend to check in the documentation
of the library you're using or check the version of
Tau-Prolog you're working with.

LoL

Mostowski Collapse

unread,
Jan 11, 2023, 5:24:33 PM1/11/23
to

Looks like Ciao Prolog Playground totally
forgot about some library(dom)? Nada?

Is it more harder to make library(dom) for
a WASM based Prolog than a JavaScript based

Prolog? What about SWI-Prolog WASM?

Mostowski Collapse

unread,
Jan 13, 2023, 4:56:46 AM1/13/23
to
An other can of worms format/2, related to DOM generation.
The Prolog community could standardisize it voluntarily
without the need of the ISO body. Just have a common place,

where somebody puts up a kind of specification document.
Something like a format/2 Prolog Enhancement Proposals (PEP).
Why look into format/2 ? Because Tau Prolog suggests funny stuff:

add_item(Item, Count) :-
...
format(Stream, "~a (~d)", [Item, Count]),
...

Web development with Tau Prolog - Riazaa
https://biblioteca.sistedes.es/submissions/descargas/2022/PROLE/2022-PROLE-006.pdf

Mostlikely the above is not a very optimal idea, since
there are so many other issues in DOM text generation,
like XML Escape or URL Encoding. But nevertheless

worth investigating as a means for DOM text generation.

Mostowski Collapse

unread,
Jan 13, 2023, 4:58:12 AM1/13/23
to
A middle ground could be to standardisized only float formatting.
So that there are some primitives that do float formatting,
and various string interpolations and portraying could be

bootstrapped from it. I find some rudimentaries here from ROK:

float_codes(Float, Codes, Format) :-
% like number_codes/2 but only for floats
http://www.cs.otago.ac.nz/staffpriv/ok/pllib.htm

So the standardisation would takle what the ‘%’ operator can
do in Python, when the left argument is a string and the right
argument is a float. But there is much to be demanded, what

if the right argument is an integer, especially a bigint and not
a smallint, a bigint that cannot be converted to float. So ROKs
take is a little outdated, since is not bigint aware.

Mostowski Collapse

unread,
Jan 13, 2023, 4:59:22 AM1/13/23
to
SWI-Prolog is currently bigint aware:

?- format("abc ~2f def", [123123123123123123123]).
abc 123123123123123123123.00 def

?- format("abc ~2f def", [123123123123123123123.0]).
abc 123123123123123126272.00 def

Trealla Prolog doesn’t tolerate integer:

?- format("abc ~2f def", [123123123123123123123]).
error(type_error(float,123123123123123123123),format/2).

Scryer Prolog does sometimes nonsense for float:

?- format("abc ~2f def", [123123123123123123123.0]).
abc 1.23 def true.

Mostowski Collapse

unread,
Jan 13, 2023, 5:01:03 AM1/13/23
to
My conclusion, to reach the level of SWI-Prolog,
a number_codes with a format parameters is needed, and
not a float_codes that is restricted to floats.

With a number_codes that also accepts integers, it will go
smooth to also format integers, as SWI-Prolog does.
On my side I started defining a new built-in:

atom_number(-Atom, +Atom, +Integer, +Number)

The above built-in takes a slightly different turn, not codes
but atom is the currency for number conversion. The
input atom is ‘f’ or ‘e’, and the input integer is the requested

precision. But it is currently too stupid for bigint, working on it.

Mostowski Collapse

unread,
Jan 13, 2023, 7:49:28 AM1/13/23
to
PEPs are probably anyway a dead end. Best would be if Prolog
systems were designed around a Novacore. So atom_number/4
would probably fit into a **Novacore**, but format/[2,3] not.

format/[2,3] would have a pure Prolog implementation, that
can be shared across Prolog systems. Same for locales, a pure
Prolog implementation, or some Semantic Net from ChatGPT.

LoL

Mostowski Collapse

unread,
Jan 16, 2023, 6:03:10 PM1/16/23
to
Thats a defect of Markus Triskas library(format).
The defect is found in Scryer Prolog:

?- format("foo ~w bar ~w baz", [p(A,B),q(B,C)]), nl.
foo p(A,B) bar q(B,C) baz

?- format("foo ~w bar", [p(A,B)]), format(" ~w baz", [q(B,C)]), nl.
foo p(A,B) bar q(A,B) baz

One should be able to chop up format/[2,3]. Other
Prolog systems are able to do that. Either with small
variable gensym or with large variable gensym:

/* Trealla, Jekejeke etc.. --> small variable gensym */
?- format('foo ~w bar ~w baz', [p(A,B),q(B,C)]), nl.
foo p(_0, _1) bar q(_1, _2) baz

?- format('foo ~w bar', [p(A,B)]), format(' ~w baz', [q(B,C)]), nl.
foo p(_0, _1) bar q(_1, _2) baz

/* SWI-Prolog, Dogelog etc.. --> large variable gensym */
?- format('foo ~w bar ~w baz', [p(A,B),q(B,C)]), nl.
foo p(_23041, _23042) bar q(_23042, _23043) baz

?- format('foo ~w bar', [p(A,B)]), format(' ~w baz', [q(B,C)]), nl.
foo p(_25699, _25700) bar q(_25700, _25701) baz

I don't know whether Trealla and Jekejeke use the
same gensym strategy, but phenotype is similar.
Same for the genotype of SWI-Prolog and Dogelog,

mostlikely not the same realization under the hood,
but similar outcome again.

Mostowski Collapse

unread,
Jan 16, 2023, 6:07:06 PM1/16/23
to

It seems that Tau Prolog has a hickup somewhere:

?- format("foo ~w bar ~w baz", [p(A,B),q(B,C)]), nl.
uncaught exception: error(instantiation_error,fabricate_var_name/3)

https://github.com/tau-prolog/tau-prolog/issues/342

Mostowski Collapse

unread,
Jan 17, 2023, 3:49:25 AM1/17/23
to
Interesting find, hooking into Java printf gives:

?- catch(printf('abc %s def', []), error(E,_), true).
Error: Unknown template: representation_error('Format specifier ''%s''')
/* java.util.MissingFormatArgumentException extends IllegalFormatException */
?- catch(printf('abc %s def', [p,q]), error(E,_), true).
abc p def

So too many arguments are tolerated. On the other
hand SWI-Prolog does check too many arguments:

?- catch(format('abc ~w def', []), error(E,_), true).
E = format('not enough arguments').

?- catch(format('abc ~w def', [p,q]), error(E,_), true).
E = format('too many arguments').

Oki Doki

Mostowski Collapse

unread,
Jan 17, 2023, 6:22:57 AM1/17/23
to
Interesting find, Ciao Prologs does sometimes boxing:

/* Ciao Prolog 1.22.0 */
?- format('abc ~w def', [p]). %%% no-boxing exception [_]
abc p def

?- format('abc ~w def', p).
abc p def

I guess this makes the format/2 predicate a little brittle,
when used to print lists. One cannot distinguish [p] and
p in the output, not sure whether is a tolerable flaw?

It is tolerable in as far as there exists a work around. The
work around is to avoid boxing when there is only
one item to print:

?- format('abc ~w def', [[p]]).
abc [p] def

?- format('abc ~w def', [p]).
abc p def

So when you are Pavlov’s dog and have learned to use
and enjoy Ciao Prologs feature, because of some positive
feedback where it works, you have to unlearn this feature

nevertheless, which needs the administration of electric
shocks to the programmer.

Mostowski Collapse

unread,
Feb 27, 2023, 6:08:12 AM2/27/23
to
Could a Novacore also be a Worker Prolog? One coul
imagine a Prolog system where all predicates are by
default thread local, and where threads can only

share information through message passing. You would
more or less get JavaScript Workers. Such a Prolog system
would not anymore need synchronization of predicates,

neither needed for static nor dynamic predicates. I am
currently wondering whether I can build such a Prolog variant
and what the performance would be? But a special form of

thread local would be needed, since the predicate needs not be
visible among multiple workers.

Mostowski Collapse

unread,
Feb 27, 2023, 6:09:01 AM2/27/23
to
A bonus would be if the Prolog system had event
loops in its Workers by default, so that kind of fibers
would be available, and one would still have some benefits

of a multi-threaded Prolog system, just do it async
in the same thread. Maybe a couple service threads besides
the workers threads nevertheless, so that for example

things like call_with_time_limit/2 still work. Maybe such a
Worker Prolog could be bootstrapped from a multi-threaded
Prolog system by changing some defaults, for example

that predicates are by default this new form of thread local.

Mostowski Collapse

unread,
Feb 27, 2023, 1:31:36 PM2/27/23
to
If you have fibers, you also don’t need any locking. At least not for
basic operations like assert/1, retract/1, etc… since they still run single
threaded if you don’t yield during these operations. But on

the other hand try this in the current SWI-Prolog WASM shell:

?- call_with_time_limit(0.5, (repeat, fail)).
ERROR: Unhandled exception: toplevel: Unknown procedure:
call_with_time_limit/2 (DWIM could not correct goal)
https://dev.swi-prolog.org/wasm/shell

Surprisingly, since this weekend, I can do the following
in Dogelog Player for Python, the predicate time_out/2 accepts
milliseconds and has the arguments in different order:

?- time_out((repeat, fail), 500).
Error: system_error(timelimit_exceeded)
user:1
And I didn’t use threads, so how did I do it? BTW: I don’t know
whether Tau Prolog can demonstrate it. They have demonstrated
something else, multiple Prolog threads trying to reach a finish line.

I am not yet there at the Tau Prolog calibre of fibers, step by step
wondering currently how signal handling can be done.

Mostowski Collapse

unread,
Feb 27, 2023, 1:33:05 PM2/27/23
to
Relatively straight forward using Python fibers. Only they are not
called fibers, the are call coroutines. For example the new
built-in to schedule an alarm is implemented as follows in Python:

loop = asyncio.get_running_loop()
res = loop.call_later(delay/1000.0, alarm_abort)

The same works also for JavaScript now, using an API with some
different names, but also based on an event loop I guess. Thats
the magic of fibers, they are inbetween single threaded and

multi-threaded. The alarm_abort callback in the above posts a
signal, which gets taken note by the auto-yielding interpreter. The
behaviour is very similar to a multi-threaded Prolog alarm,

or a single-threaded Prolog alarm that uses some operating
system service for the signalling.

Mostowski Collapse

unread,
Feb 27, 2023, 7:05:12 PM2/27/23
to
Is this Worker Prolog part of Novacore. Well Yes and
No. Novacore is supposed to be a core without any libraries,
reduced to the minimum. So it can be the basis for

a multitude of things, like:

Multi-Threaded Prolog ----\
Single-Threaded Prolog ---+-----> Novacore
Worker Fiber Prolog ------/

Thats why I am currently moving all kind of
libraries out of formerly Jekejeke Prolog Runtime,
to a different place, threads are gone, locks are

gone, pipes are gone, directories are gone, everything
is gone. Maybe Workers will come? Who knows.
Maybe Worker Fibers will come?

I am not 100% sure whether Workers always need
Fibers? Well there is one use case. If a Worker
needs to be abortable, this could be done

by a auto-yielding Prolog system running inside
the Worker. See Prolog of Ciao Playground. So
I guess one has to think as a Worker Prolog not

as a Multi-Threaded Prolog rather as a Multi-Single-
Threaded Prolog, where each Thread is Single in
that it is isolated from the other Threads, doesn't

see their predicates, and the fiber makes an easy
solution to abort such a Thread. In Java its done
differently. There most all Multi-Threaded APIs are

abortable from the outside, but to abort a Prolog
interpreter you still need something else, since
you don't necessarily call Multi-Threaded APIs

all the time. So polling some signal or auto-yielding
is essentially the same.

Mostowski Collapse

unread,
Mar 1, 2023, 12:01:19 PM3/1/23
to
Are lazy streams fibers? Not really.

If you preform engine yield, you just land in the parent
context of the current execution. You don’t temporarily
suspend the current execution. You need an event loop

for that. But all the papers by Tarau, Wielemaker and
Schrijvers never discuss that. You could also imagine a
new Prolog language, with two new operators async/1

and await/1. For example one could write a bankteller
web worker only with fibers, and one could
produce code as follows:

:- async withdraw/2.
withdraw(Amount) :-
await do_something,
retact(account(Current)),
Current2 is Curent-Amount,
assertz(account(Current2)),
await do_something2.

Since the retract/assertz combo is not interleaved with an
await statement, we know that noting will yield while executing
the combo, and the effect is as if it were a critical region. But

locks or atomics are not needed. You have to switch off auto-
yielding for such a code as above, no auto-yielding is also the
default execution mode of JavaScript, and you could apply

the same reasoning to JavaScript.

Mostowski Collapse

unread,
Mar 1, 2023, 12:02:37 PM3/1/23
to
Maybe good name for such a language would be
Fibertalk. It would have a linter with some style checks.
Like if a body goal has an await/1, but the head predicate

doesn’t have async/1, there would be a warning or error.
But you can implement async/1 and await/1 extremly simple.
They are only declarations as a kind of program documentation

and are also useful for the linter, but for execution they do nothing:

async(_).
await(G) :- G.

To implement them as above is possible for a Prolog
system with fibers that can yield anywhere. It might be
as well the case, that for JavaScript the keywords are

also only decoration? Not sure. The decoration goes also
into attributes of objects such as “Function” in JavaScript.

Mostowski Collapse

unread,
Mar 2, 2023, 7:06:55 AM3/2/23
to
So is there really a 3rd category Worker Fiber? Thanks for
challenging me explaning a concept over and over again.

Q: You shouldn’t, but you need between fibers on the same worker?

A: Do you mean shared atom and clause garbage collection is needed?
Yes. But only a single threaded version of it. Its not doing anything
between fibers inside the same worker. You don’t need locking or

atomics for fibers as I see it. With the JavaScript Worker model,
you land in single threaded Prolog system, although you are
multi-threaded. I don’t know how difficult it would be to build a

SWI-Prolog system that has Workers running single-threaded,
but nevertheless supports many of them over threads? You possibly
have to separate the Workers from a Workers monitor. Make the

Workers monitor a separately compiled component, where multi-threading
is enable. And compile the SWI-Prolog Workers Prolog runtime system
single-threaded, i.e. with multi-threading disabled.

Mostowski Collapse

unread,
Mar 2, 2023, 7:08:48 AM3/2/23
to
I don’t know yet how to bake it. In formerly Jekejeke
Prolog I have ultra static but no yield or auto-yield yet,
despite that it has engines!

In Dogelog Player I have yield or auto-yield, but no
cooperative task spawning yet. One Prolog system that
has already fibers is Tau Prolog, but their system

doesn’t perform very well otherwise. SWI-Prolog is
in a good position in that it has already engines with
yield and recently auto-yield!

Mostowski Collapse

unread,
Mar 8, 2023, 4:45:15 AM3/8/23
to
Now I made a new version of my non-fibers and fibers API.
I removed the name “engine” from the API, so as to avoid
confusion. Engines are more lower level than the Python

idea of callbacks and tasks. The API now reads:

Part 1: Callbacks (non-fibers) (Changed)
They are Stackless and run in the <strike>main Engine</strike>
current Task of the Current Thread. In my current take, they run
without Auto-Yield and without Yield-Allowed.

os_call_later(G, D, T):
The predicate succeeds in T with a new timer. As a side effect
it schedules the goal G to be executed after D milliseconds.

os_call_cancel(T):
The predicate succeeds. As a side effect it cancels the timer T.

Part 2: Tasks (1:N fibers) (Changed)
They are Stackful and create their own <strike>Engine</strike> Task
in the Current Thread. In my current take, they run with
Auto-Yield and with Yield-Allowed.

os_task_current(E):
The predicate succeeds in E with the current <strike>engine</strike> task.

os_task_abort(E, M):
The predicate succeeds. As a side effect the <strike>engine</strike>
task E gets the message M signalled.

os_task_create(G, E):
The predicate succeeds in E with a new <strike>engine</strike> task
for the goal G. The task gets immediately scheduled to be executed.

Mostowski Collapse

unread,
Mar 8, 2023, 4:47:34 AM3/8/23
to
Nice addition to the current API spec and already
implemented for JavaScript and Python. A callback
has now the context available of the task that scheduled it.

?- os_task_current(T), write('task='), write(T), nl.
task=main

?- call_later((os_task_current(T), write('task='),
write(T), nl), 100), sleep(500).
task=main

?- create_task((os_task_current(T), write('task='), write(T), nl)), sleep(500).
task=[object Object]

?- create_task(call_later((os_task_current(T), write('task='),
write(T), nl), 100)), sleep(500).
task=[object Object]

And there is a new Prolog flag allow_yield, which can
be illustrated, you can query what the current API says:

?- current_prolog_flag(allow_yield, A), write('allow_yield='), write(A), nl.
allow_yield=on

?- call_later((current_prolog_flag(allow_yield, A), write('allow_yield='),
write(A), nl), 100), sleep(500).
allow_yield=off

Mostowski Collapse

unread,
Mar 18, 2023, 8:55:21 AM3/18/23
to
Inside Novacore we could reinvent Prolog Dicts. JavaScript
has a primitive data type for Symbols, so you can call
Symbol.for(“key”), which will internalize the string, so that

you can use pointer equality on the result:

> Symbol is a built-in object whose constructor returns a symbol primitive
> https://developer.mozilla.org/en-US/docs/Web/JavaScript/Reference/Global_Objects/Symbol

It wouldn’t match JSON usage, since the keys are not supposed
to be Symbols, only Strings. But maybe this is only superficially,
and internally they are Symbols. One could do the same for

Novacore Prolog Dicts. On the surface Novacore Prolog
Dicts would use Strings:

?- X = {"abc" : 123.45, "def": 67}.
But under the hood there would be a transition from String to Atom:

?- X = {"abc" : 123.45, "def": 67}, X =.. L.
L = [C'novacore_dict, abc, 123.45, def, 67]

The rational would be: The keys usually form a limited vocabulary.

Mostowski Collapse

unread,
Mar 18, 2023, 8:56:23 AM3/18/23
to
Interestingly with the above trick, a Prolog parser can
recognize Novacore Prolog Dicts. Since it would see this
production at the head of a Novacore Prolog Dict:

novacore_dict :== "{" string ":" term ... "}"

Which is unlike the ISO core definition of “{}”, since in
ISO core there are no strings, and even a qualified call in
ISO module assumes that we have atom “:” term. So

there would be no collision with this production:

set :== "{" term "}"

Mostowski Collapse

unread,
Mar 18, 2023, 9:01:35 AM3/18/23
to
Currently I get an error when I use string keys:

/* SWI-Prolog 9.1.4 */
?- current_prolog_flag(double_quotes, X).
X = string.

?- X = _{"abc": 123.46, "def": 67}.
ERROR: Syntax error: key_expected
Also there is the annoying need for an underscore functor.

With string keys I could directly embed JSON?
In this case null, false and true could be easily an atom.
Thats kind of solving the constant problem from another angle.

Mostowski Collapse

unread,
Mar 18, 2023, 9:06:36 AM3/18/23
to
But this other angle would only work inside JSON.
There is still a problem with ordinary Prolog code, and
for example the disabled setter. If we want to avoid some

bottle neck of translating structures back and forth.

Mostowski Collapse

unread,
May 13, 2023, 9:36:04 AM5/13/23
to
Now I have already removed the following predicates from
Novacore, they landed in library(compat):

- numbervars/2
- subsumes/2
- subsumes_term/2

Now wonder where variant/2 would land? SWI-Prolog wants to tell me
that variant/2 might need library(compat), because of numbervars/2.
Assuming A and B have already distinct variables I get the following solution:

A =@= B :-
\+ \+ (numbervars(Ac, 0, N),
numbervars(Bc, 0, N),
Ac == Bc).
https://www.swi-prolog.org/pldoc/doc_for?object=%28%3D@%3D%29/2

On the other hand this solution gives me also a library(compat)
dependency, since its based on subsumes_term/2. Again assuming A and
B have already distinct variables I get the following solution:

A =@= B :-
subsumes_term(A, B),
subsumes_term(B, A).
https://www.complang.tuwien.ac.at/ulrich/iso-prolog/built-in_predicates

Isn't there something simpler?

Mostowski Collapse

unread,
May 13, 2023, 9:41:10 AM5/13/23
to
This is cute, has quite some different dependencies,
inspired by the use of term_variables/3 in bagof/3,
again assuming that A and B have already disjoint variables:

A =@= B :-
term_variables(A, L),
term_variables(B, R),
\+ \+ (L=R, A==B).

Can be bootstrapped from a much smaler Novacore.

Mostowski Collapse schrieb am Samstag, 13. Mai 2023 um 15:36:04 UTC+2:
> Now I have already removed the following predicates from
> Novacore, they landed in library(compat):
>
> - numbervars/2
> - subsumes/2
> - subsumes_term/2
>
> Now wonder where variant/2 would land? SWI-Prolog wants to tell me
> that variant/2 might need library(compat), because of numbervars/2.
> Assuming A and B have already distinct variables I get the following solution:
>
> A =@= B :-
> \+ \+ (numbervars(A, 0, N),
> numbervars(B, 0, N),
> A == B).

Mostowski Collapse

unread,
May 21, 2023, 6:54:42 AM5/21/23
to
Now I have implemented the new open/4 options method/1,
headers/1 and body/1 also for Dogelog Player. There is a first
take that works in the browser. More platforms to follow.

Its such a thin extension, API wise, want to have it as part of
Novacore. What do other Prolog systems do? Here is what
SWI-Prolog in their offering.

- method/1: Accepts the method name in lower case,
so far I use the option with an upper case value.
- headers/1: Doesn't use our Key-Value pair format,
instead the format is Key(Value). Has separate option
for auth/1 and inside auth/1 for bearer/1.
- body/1: Not available in SWI-Prolog, must use post/1,
and post/1 accepts quite a bulk of formats.

and then I find that Trealla Prolog does something else
Signature wise:

- offers some convenience like http_post/4, http_delete/3,
bootstrapped from http_get/3.
- http_get/3 has options method/1, post/1 and header/2,
quite amazing, mostly written in 100% Prolog!
- might also support HTTPS, depends on client/5.
- this was checked into GitHub 9 months ago

and Scryer Prolog does again something else
Signature wise:

- http_open/3 had a 100% Prolog solution in 2020,
but became something else 12 months ago.
- http_open/3 has options method/1, data/1 and
request_headers/1, goes into CallHttpOpen instruction,
which then uses hyper_tls.

Mild Shock

unread,
Jul 29, 2023, 7:51:12 AM7/29/23
to
The new multilingual strings are also an exercise in
Novacore. There were a few issues that needed novel
Prolog solutions, to make a Novacore solution.

One problem was I didn't want to use library(format)
and format/3 to format multilingual strings when
generating error messages. This addresses more

the later multilingual strings processing than the
multilingual strings store itself. So how resolve this
paradox? Here is my take, a mini format/3 boostraped

from the Dogelog Player specific atom_split/3:

% sys_inter_polate(+Stream, +Atom, +List)
sys_inter_polate(Stream, Template, Args) :-
atom_split(Template, '~', [Head|Tail]),
put_atom(Stream, Head),
sys_zipper_output(Args, Tail, Stream).

% sys_zipper_output(+List, +List, +Stream)
sys_zipper_output([Arg|Args], [Head|Tail], Stream) :-
writeq(Stream, Arg),
put_atom(Stream, Head),
sys_zipper_output(Args, Tail, Stream).
sys_zipper_output([], [], _).

It only understands format specifier '~', but is sufficient:

/* German Text */
strings('syntax_error.singleton_var', de, 'Alleinstehende Variable(n) ~, anonyme Variable(n) (_) benutzen.').

/* English and Fallback Text */
strings('syntax_error.singleton_var', '', 'Singleton variable(s) ~, use anonymous variable(s) (_).').

LoL

Mild Shock

unread,
Sep 7, 2023, 8:15:22 PM9/7/23
to
Did you know that Novacore has change_arg/3?
Works for Dogelog Player and formerly Jekejeke Prolog.
It is similar like nb_linkarg/3 in SWI-Prolog.

So we can implement countall/3 in a blink:

countall(G, N) :-
functor(Holder, v, 1),
change_arg(1, Holder, 0),
(G,
arg(1, Holder, H),
J is H+1,
change_arg(1, Holder, J),
fail; true),
arg(1, Holder, N).

Works find:

?- countall(between(10,20,_), N).
N = 11.

Mild Shock

unread,
Nov 19, 2023, 1:54:30 PM11/19/23
to
We are now exploring file systems with novacore.
And here and then we have a couple of primitives
and then do some bootstrapping. It currently lands

in library(random) until we find a better place:

% directory_member(+Atom, -Atom)
directory_member(F, N) :-
directory_files(F, L),
member(N, L).

% ensure_directory(+Atom)
ensure_directory(F) :-
file_exists(F),
file_property(F, type(directory)),
!.
ensure_directory(F) :-
make_directory(F).

Guess what, finding semantic and support of
directory_files/2, file_exists/1 and file_property/2
is already non trivial.

Mild Shock

unread,
Nov 19, 2023, 1:56:35 PM11/19/23
to

Mild Shock

unread,
Nov 19, 2023, 1:59:09 PM11/19/23
to

LogNonsenseTalk with its brainwash is totally
useless. This here is already wrong:

file_exists(File) :-
absolute_file_name(File, ExpandedPath),
{exists_file(ExpandedPath)}.

https://github.com/LogtalkDotOrg/logtalk3/blob/master/library/os/os.lgt

Becaue for example exists_file/1 in SWI-Prolog
means exists regular file. But file_exists/1

should mean exists file of any type. Just
lookup what GNU Prolog provides. In OS lingua

file means often regular, directory, etc..

Mild Shock schrieb:

Mild Shock

unread,
Nov 19, 2023, 2:01:51 PM11/19/23
to
You see the OS jargon meaning in directory_member/2
which is bootstrapped from directory_files/2.

directory_files/2 should of course list any files
inside the directory, regular, directory, etc..

not only regular files. So "files" means any
file of type regular, directory, etc..
0 new messages