• VIP0909: VibeCore Improvement Proposal [term_singletons]

    From Mild Shock@janburse@fastmail.fm to comp.lang.prolog on Mon Aug 11 11:38:08 2025
    From Newsgroup: comp.lang.prolog

    Hi,

    Functional requirement:

    ?- Y = g(_,_), X = f(Y,C,D,Y), term_singletons(X, L),
    L == [C,D].

    ?- Y = g(A,X,B), X = f(Y,C,D), term_singletons(X, L),
    L == [A,B,C,D].

    Non-Functional requirement:

    ?- member(N,[5,10,15]), time(singletons(N)), fail; true.
    % Zeit 1 ms, GC 0 ms, Lips 4046000, Uhr 11.08.2025 01:36
    % Zeit 3 ms, GC 0 ms, Lips 1352000, Uhr 11.08.2025 01:36
    % Zeit 3 ms, GC 0 ms, Lips 1355333, Uhr 11.08.2025 01:36
    true.

    Can your Prolog system do that?

    P.S.: Benchmark was:

    singletons(N) :-
    hydra2(N,Y),
    between(1,1000,_), term_singletons(Y,_), fail; true.

    hydra2(0, _) :- !.
    hydra2(N, s(X,X)) :-
    M is N-1,
    hydra2(M, X).

    Bye
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Mild Shock@janburse@fastmail.fm to comp.lang.prolog on Mon Aug 11 14:31:14 2025
    From Newsgroup: comp.lang.prolog

    Hi,

    While the rep() approach leads automatically
    to total orders. As was already seen in MerciorCOs
    Algorithm where rep(A) = ArCO. We can also arrange
    that it leads to natural orders that are

    conservative, using the DushnikrCo
    Miller theorem:

    DushnikrCoMiller theorem
    Countable linear orders have non-identity order self-embeddings. https://en.wikipedia.org/wiki/Dushnik%E2%80%93Miller_theorem

    I guess the theorem can be proved
    with a Hilbert Hotel argument?

    Here are some examples, works for terms that
    donrCOt use '$VAR'/1 with a negative index, using
    in fact an identity self-embedding on acyclic terms:

    ?- X = f(f(f(X))), naish(X,A).
    X = f(f(f(X))),
    A = f(f(f(S_3))).

    ?- X = s(Y,0), Y = s(X,1), naish(X,A), naish(Y,B).
    X = s(s(X, 1), 0),
    Y = s(X, 1),
    A = s(s(S_2, 1), 0),
    B = s(s(S_2, 0), 1).

    naish/2 is named after Lee Naish, we use a
    variant with deBruijn indexes:

    naish(X, Y) :-
    naish([], X, Y).

    naish(_, X, X) :- var(X), !.
    naish(S, X, Z) :- compound(X),
    nth1(N, S, Y), same_term(X, Y), !,
    M is -N,
    Z = '$VAR'(M).
    naish(S, X, Y) :- compound(X), !,
    X =.. [F|L],
    maplist(naish([X|S]), L, R),
    Y =.. [F|R].
    naish(_, X, X).

    Bye

    Mild Shock schrieb:
    Hi,

    Functional requirement:

    ?- Y = g(_,_), X = f(Y,C,D,Y), term_singletons(X, L),
    -a-a L == [C,D].

    ?- Y = g(A,X,B), X = f(Y,C,D), term_singletons(X, L),
    -a-a L == [A,B,C,D].

    Non-Functional requirement:

    ?- member(N,[5,10,15]), time(singletons(N)), fail; true.
    % Zeit 1 ms, GC 0 ms, Lips 4046000, Uhr 11.08.2025 01:36
    % Zeit 3 ms, GC 0 ms, Lips 1352000, Uhr 11.08.2025 01:36
    % Zeit 3 ms, GC 0 ms, Lips 1355333, Uhr 11.08.2025 01:36
    true.

    Can your Prolog system do that?

    P.S.: Benchmark was:

    singletons(N) :-
    -a-a hydra2(N,Y),
    -a-a between(1,1000,_), term_singletons(Y,_), fail; true.

    hydra2(0, _) :- !.
    hydra2(N, s(X,X)) :-
    -a-a M is N-1,
    -a-a hydra2(M, X).

    Bye

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Mild Shock@janburse@fastmail.fm to comp.lang.prolog on Mon Aug 11 14:44:42 2025
    From Newsgroup: comp.lang.prolog

    Hi,

    Now we can procceed an define:

    structure_compare(C, X, Y) :-
    naish(X, A),
    naish(Y, B),
    compare(C, A, B),

    canonical_compare(C, X, Y) :-
    moore(X, A),
    moore(Y, B),
    structure_compare(C, A, B).

    The predicate structural_compare/3 does
    not respect (==)/2 on cyclic terms. While
    the predicate canonical_compare/3 does

    respect (==)/2 on cyclic terms. Here some
    example queries, showing the (==)/2 behaviour:

    ?- X = f(f(f(X))), Y = f(f(Y)), structure_compare(C, X, Y).
    C = (>).

    ?- X = f(f(f(X))), Y = f(f(Y)), canonical_compare(C, X, Y).
    C = (=).

    And the Mats Carlson pair for demonstration:

    ?- X = s(Y,0), Y = s(X,1), stucture_compare(C, X, Y).
    C = (>).

    ?- X = s(Y,0), Y = s(X,1), canonical_compare(C, X, Y).
    C = (>).

    Bye

    Mild Shock schrieb:
    Hi,

    While the rep() approach leads automatically
    to total orders. As was already seen in MerciorCOs
    Algorithm where rep(A) = ArCO. We can also arrange
    that it leads to natural orders that are

    conservative, using the DushnikrCo
    Miller theorem:

    DushnikrCoMiller theorem
    Countable linear orders have non-identity order self-embeddings. https://en.wikipedia.org/wiki/Dushnik%E2%80%93Miller_theorem

    I guess the theorem can be proved
    with a Hilbert Hotel argument?

    Here are some examples, works for terms that
    donrCOt use '$VAR'/1 with a negative index, using
    in fact an identity self-embedding on acyclic terms:

    ?- X = f(f(f(X))), naish(X,A).
    X = f(f(f(X))),
    A = f(f(f(S_3))).

    ?- X = s(Y,0), Y = s(X,1), naish(X,A), naish(Y,B).
    X = s(s(X, 1), 0),
    Y = s(X, 1),
    A = s(s(S_2, 1), 0),
    B = s(s(S_2, 0), 1).

    naish/2 is named after Lee Naish, we use a
    variant with deBruijn indexes:

    naish(X, Y) :-
    -a-a naish([], X, Y).

    naish(_, X, X) :- var(X), !.
    naish(S, X, Z) :- compound(X),
    -a-a nth1(N, S, Y), same_term(X, Y), !,
    -a-a M is -N,
    -a-a Z = '$VAR'(M).
    naish(S, X, Y) :- compound(X), !,
    -a-a X =.. [F|L],
    -a-a maplist(naish([X|S]), L, R),
    -a-a Y =.. [F|R].
    naish(_, X, X).

    Bye

    Mild Shock schrieb:
    Hi,

    Functional requirement:

    ?- Y = g(_,_), X = f(Y,C,D,Y), term_singletons(X, L),
    -a-a-a L == [C,D].

    ?- Y = g(A,X,B), X = f(Y,C,D), term_singletons(X, L),
    -a-a-a L == [A,B,C,D].

    Non-Functional requirement:

    ?- member(N,[5,10,15]), time(singletons(N)), fail; true.
    % Zeit 1 ms, GC 0 ms, Lips 4046000, Uhr 11.08.2025 01:36
    % Zeit 3 ms, GC 0 ms, Lips 1352000, Uhr 11.08.2025 01:36
    % Zeit 3 ms, GC 0 ms, Lips 1355333, Uhr 11.08.2025 01:36
    true.

    Can your Prolog system do that?

    P.S.: Benchmark was:

    singletons(N) :-
    -a-a-a hydra2(N,Y),
    -a-a-a between(1,1000,_), term_singletons(Y,_), fail; true.

    hydra2(0, _) :- !.
    hydra2(N, s(X,X)) :-
    -a-a-a M is N-1,
    -a-a-a hydra2(M, X).

    Bye


    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Mild Shock@janburse@fastmail.fm to comp.lang.prolog on Mon Aug 11 14:50:39 2025
    From Newsgroup: comp.lang.prolog

    Hi,

    How make it bleeding fast? Here is the
    source code. moore/2 is named after Edward
    Moore from DFA minimization.

    Maybe @kuniaki.mukai has the matrix thing
    from Seiiti Huzita, no matrices were harmed
    here, is it correct?

    moore(X, Y) :-
    moore([], X, Y).

    moore(_, X, X) :- var(X), !.
    moore(S, X, Z) :- compound(X),
    member(Y-Z, S), X == Y, !.
    moore(S, X, Y) :- compound(X), !,
    X =.. [F|L],
    maplist(moore([X-Y|S]), L, R),
    Y =.. [F|R].
    moore(_, X, X).

    Seiiti Huzita published this. Two years after Moore
    in 1956. The paper concludes with:

    ON SOME SEQUENTIAL MACHINES AND EXPERIMENTS
    Seiiti HUZINO - 1958
    "As any reversible machine is identified to one
    strongly connected machine by the decomposition
    theorem, when its initial state is given, the
    proof of this proposition is the same as in
    Moore's theorem 3 ([1])." https://www.jstage.jst.go.jp/article/kyushumfs/12/2/12_2_136/_pdf/-char/en

    The reversibility thing is a funny ode to
    certain physics, and also gives an funny spin
    on constructor / deconstructor duality.

    But I am afraid, I didn't study the paper,
    so just some speculative bla bla on my side.

    Mild Shock schrieb:
    Hi,

    Now we can procceed an define:

    structure_compare(C, X, Y) :-
    -a-a-a naish(X, A),
    -a-a-a naish(Y, B),
    -a-a-a compare(C, A, B),

    canonical_compare(C, X, Y) :-
    -a-a-a moore(X, A),
    -a-a-a moore(Y, B),
    -a-a-a structure_compare(C, A, B).

    The predicate structural_compare/3 does
    not respect (==)/2 on cyclic terms. While
    the predicate canonical_compare/3 does

    respect (==)/2 on cyclic terms. Here some
    example queries, showing the (==)/2 behaviour:

    ?- X = f(f(f(X))), Y = f(f(Y)), structure_compare(C, X, Y).
    C = (>).

    ?- X = f(f(f(X))), Y = f(f(Y)), canonical_compare(C, X, Y).
    C = (=).

    And the Mats Carlson pair for demonstration:

    ?- X = s(Y,0), Y = s(X,1), stucture_compare(C, X, Y).
    C = (>).

    ?- X = s(Y,0), Y = s(X,1), canonical_compare(C, X, Y).
    C = (>).

    Bye

    Mild Shock schrieb:
    Hi,

    While the rep() approach leads automatically
    to total orders. As was already seen in MerciorCOs
    Algorithm where rep(A) = ArCO. We can also arrange
    that it leads to natural orders that are

    conservative, using the DushnikrCo
    Miller theorem:

    DushnikrCoMiller theorem
    Countable linear orders have non-identity order self-embeddings.
    https://en.wikipedia.org/wiki/Dushnik%E2%80%93Miller_theorem

    I guess the theorem can be proved
    with a Hilbert Hotel argument?

    Here are some examples, works for terms that
    donrCOt use '$VAR'/1 with a negative index, using
    in fact an identity self-embedding on acyclic terms:

    ?- X = f(f(f(X))), naish(X,A).
    X = f(f(f(X))),
    A = f(f(f(S_3))).

    ?- X = s(Y,0), Y = s(X,1), naish(X,A), naish(Y,B).
    X = s(s(X, 1), 0),
    Y = s(X, 1),
    A = s(s(S_2, 1), 0),
    B = s(s(S_2, 0), 1).

    naish/2 is named after Lee Naish, we use a
    variant with deBruijn indexes:

    naish(X, Y) :-
    -a-a-a naish([], X, Y).

    naish(_, X, X) :- var(X), !.
    naish(S, X, Z) :- compound(X),
    -a-a-a nth1(N, S, Y), same_term(X, Y), !,
    -a-a-a M is -N,
    -a-a-a Z = '$VAR'(M).
    naish(S, X, Y) :- compound(X), !,
    -a-a-a X =.. [F|L],
    -a-a-a maplist(naish([X|S]), L, R),
    -a-a-a Y =.. [F|R].
    naish(_, X, X).

    Bye

    Mild Shock schrieb:
    Hi,

    Functional requirement:

    ?- Y = g(_,_), X = f(Y,C,D,Y), term_singletons(X, L),
    -a-a-a L == [C,D].

    ?- Y = g(A,X,B), X = f(Y,C,D), term_singletons(X, L),
    -a-a-a L == [A,B,C,D].

    Non-Functional requirement:

    ?- member(N,[5,10,15]), time(singletons(N)), fail; true.
    % Zeit 1 ms, GC 0 ms, Lips 4046000, Uhr 11.08.2025 01:36
    % Zeit 3 ms, GC 0 ms, Lips 1352000, Uhr 11.08.2025 01:36
    % Zeit 3 ms, GC 0 ms, Lips 1355333, Uhr 11.08.2025 01:36
    true.

    Can your Prolog system do that?

    P.S.: Benchmark was:

    singletons(N) :-
    -a-a-a hydra2(N,Y),
    -a-a-a between(1,1000,_), term_singletons(Y,_), fail; true.

    hydra2(0, _) :- !.
    hydra2(N, s(X,X)) :-
    -a-a-a M is N-1,
    -a-a-a hydra2(M, X).

    Bye



    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Mild Shock@janburse@fastmail.fm to comp.lang.prolog on Sat Sep 27 19:26:53 2025
    From Newsgroup: comp.lang.prolog

    Hi,

    So VIP0909 will contain all things related to
    Cyclic terms. Especially gather what is known
    concerning space and time complexity.

    So that non-functional requirements are
    documented. One could make non-functional
    requiremets even mandatory. This is for

    example found in JavaScript when they write:

    "The specification requires maps to be
    implemented "that, on average, provide access
    times that are sublinear on the number of
    elements in the collection". Therefore, it
    could be represented internally as a hash
    table (with O(1) lookup), a search tree
    (with O(log(N)) lookup), or any other data
    structure, as long as the complexity
    is better than O(N)." https://developer.mozilla.org/en-US/docs/Web/JavaScript/Reference/Global_Objects/Map

    This would catapult standards from "correctness"
    pamphlets into the new age of "performance"
    pamphlets. My research shows that some

    unary algorithms in conncetion with cyclic
    terms and some binary algorithms in connection
    with cyclic terms have obvious linear or

    quasi linear bounds.

    Bye


    Mild Shock schrieb:
    Hi,

    Functional requirement:

    ?- Y = g(_,_), X = f(Y,C,D,Y), term_singletons(X, L),
    -a-a L == [C,D].

    ?- Y = g(A,X,B), X = f(Y,C,D), term_singletons(X, L),
    -a-a L == [A,B,C,D].

    Non-Functional requirement:

    ?- member(N,[5,10,15]), time(singletons(N)), fail; true.
    % Zeit 1 ms, GC 0 ms, Lips 4046000, Uhr 11.08.2025 01:36
    % Zeit 3 ms, GC 0 ms, Lips 1352000, Uhr 11.08.2025 01:36
    % Zeit 3 ms, GC 0 ms, Lips 1355333, Uhr 11.08.2025 01:36
    true.

    Can your Prolog system do that?

    P.S.: Benchmark was:

    singletons(N) :-
    -a-a hydra2(N,Y),
    -a-a between(1,1000,_), term_singletons(Y,_), fail; true.

    hydra2(0, _) :- !.
    hydra2(N, s(X,X)) :-
    -a-a M is N-1,
    -a-a hydra2(M, X).

    Bye

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Mild Shock@janburse@fastmail.fm to comp.lang.prolog on Sat Sep 27 19:28:41 2025
    From Newsgroup: comp.lang.prolog

    It,

    It turns out that Jaffar's Unification is ultra fast,
    we even beat Scryer Prolog with our JavaScript target.
    Nevertheless we rejected it, since it intrudes frozen

    Prolog terms. We then speculated that we need a hybrid
    algorithm, that combines intrusion and non-intrusion,
    possibly by braching into non-intrusion, from intrusion.

    But a possible solution is simpler, we could change
    Jaffar's Unification, exemplified by union_find():

    public static Compound union_find2(Compound obj) {
    while (is_compound(obj.functor))
    obj = (Compound)obj.functor;
    return obj;
    }

    Into this here making it hybrid, union_add() and
    log_add() would receive similar changes:

    public static Compound union_find2(Compound obj) {
    if (is_frozen(obj)
    return obj;
    while (is_compound(obj.functor))
    obj = (Compound)obj.functor;
    return obj;
    }

    Let's see how it turns out...

    Bye

    Mild Shock schrieb:
    Hi,

    So VIP0909 will contain all things related to
    Cyclic terms. Especially gather what is known
    concerning space and time complexity.

    So that non-functional requirements are
    documented. One could make non-functional
    requiremets even mandatory. This is for

    example found in JavaScript when they write:

    "The specification requires maps to be
    implemented "that, on average, provide access
    times that are sublinear on the number of
    elements in the collection". Therefore, it
    could be represented internally as a hash
    table (with O(1) lookup), a search tree
    (with O(log(N)) lookup), or any other data
    structure, as long as the complexity
    is better than O(N)." https://developer.mozilla.org/en-US/docs/Web/JavaScript/Reference/Global_Objects/Map


    This would catapult standards from "correctness"
    pamphlets into the new age of "performance"
    pamphlets. My research shows that some

    unary algorithms in conncetion with cyclic
    terms and some binary algorithms in connection
    with cyclic terms have obvious linear or

    quasi linear bounds.

    Bye


    Mild Shock schrieb:
    Hi,

    Functional requirement:

    ?- Y = g(_,_), X = f(Y,C,D,Y), term_singletons(X, L),
    -a-a-a L == [C,D].

    ?- Y = g(A,X,B), X = f(Y,C,D), term_singletons(X, L),
    -a-a-a L == [A,B,C,D].

    Non-Functional requirement:

    ?- member(N,[5,10,15]), time(singletons(N)), fail; true.
    % Zeit 1 ms, GC 0 ms, Lips 4046000, Uhr 11.08.2025 01:36
    % Zeit 3 ms, GC 0 ms, Lips 1352000, Uhr 11.08.2025 01:36
    % Zeit 3 ms, GC 0 ms, Lips 1355333, Uhr 11.08.2025 01:36
    true.

    Can your Prolog system do that?

    P.S.: Benchmark was:

    singletons(N) :-
    -a-a-a hydra2(N,Y),
    -a-a-a between(1,1000,_), term_singletons(Y,_), fail; true.

    hydra2(0, _) :- !.
    hydra2(N, s(X,X)) :-
    -a-a-a M is N-1,
    -a-a-a hydra2(M, X).

    Bye


    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Mild Shock@janburse@fastmail.fm to comp.lang.prolog on Sat Sep 27 19:34:47 2025
    From Newsgroup: comp.lang.prolog

    Hi,

    The Union Find modification proposed below,
    not only assumes that we don't need full
    Union Find for frozen terms, the same terms

    we use in program sharing, because they currently
    don't have cycles. What we should highlight here,
    they also don't have sharing. So both motivations

    for Union Find fall short, we will not find
    frozen Hydras as program sharing. At least currently
    there is this invariant. It might change though,

    but it is worth exploring it while it stands.
    Just imaging a program shared long list:

    data([0,1,2,3,4,5,6,7,8,9,
    0,1,2,3,4,5,6,7,8,9,
    0,1,2,3,4,5,6,7,8,9]).

    A Union Find will create a Union Find linkage,
    of the size N = 30 times, if we for example issue
    the following Prolog query:

    ?- length(X,30), data(X).

    Then on the other hand the cheap hybrid trick will
    not create any Union Find linkage, and mostlikely
    allow to regain some speed.

    Bye

    Mild Shock schrieb:
    It,

    It turns out that Jaffar's Unification is ultra fast,
    we even beat Scryer Prolog with our JavaScript target.
    Nevertheless we rejected it, since it intrudes frozen

    Prolog terms. We then speculated that we need a hybrid
    algorithm, that combines intrusion and non-intrusion,
    possibly by braching into non-intrusion, from intrusion.

    But a possible solution is simpler, we could change
    Jaffar's Unification, exemplified by union_find():

    -a-a-a public static Compound union_find2(Compound obj) {
    -a-a-a-a-a-a-a while (is_compound(obj.functor))
    -a-a-a-a-a-a-a-a-a-a-a obj = (Compound)obj.functor;
    -a-a-a-a-a-a-a return obj;
    -a-a-a }

    Into this here making it hybrid, union_add() and
    log_add() would receive similar changes:

    -a-a-a public static Compound union_find2(Compound obj) {
    -a-a-a-a-a-a-a-a if (is_frozen(obj)
    -a-a-a-a-a-a-a-a-a-a-a-a return obj;
    -a-a-a-a-a-a-a while (is_compound(obj.functor))
    -a-a-a-a-a-a-a-a-a-a-a obj = (Compound)obj.functor;
    -a-a-a-a-a-a-a return obj;
    -a-a-a }

    Let's see how it turns out...

    Bye

    Mild Shock schrieb:
    Hi,

    So VIP0909 will contain all things related to
    Cyclic terms. Especially gather what is known
    concerning space and time complexity.

    So that non-functional requirements are
    documented. One could make non-functional
    requiremets even mandatory. This is for

    example found in JavaScript when they write:

    "The specification requires maps to be
    implemented "that, on average, provide access
    times that are sublinear on the number of
    elements in the collection". Therefore, it
    could be represented internally as a hash
    table (with O(1) lookup), a search tree
    (with O(log(N)) lookup), or any other data
    structure, as long as the complexity
    is better than O(N)."
    https://developer.mozilla.org/en-US/docs/Web/JavaScript/Reference/Global_Objects/Map


    This would catapult standards from "correctness"
    pamphlets into the new age of "performance"
    pamphlets. My research shows that some

    unary algorithms in conncetion with cyclic
    terms and some binary algorithms in connection
    with cyclic terms have obvious linear or

    quasi linear bounds.

    Bye


    Mild Shock schrieb:
    Hi,

    Functional requirement:

    ?- Y = g(_,_), X = f(Y,C,D,Y), term_singletons(X, L),
    -a-a-a L == [C,D].

    ?- Y = g(A,X,B), X = f(Y,C,D), term_singletons(X, L),
    -a-a-a L == [A,B,C,D].

    Non-Functional requirement:

    ?- member(N,[5,10,15]), time(singletons(N)), fail; true.
    % Zeit 1 ms, GC 0 ms, Lips 4046000, Uhr 11.08.2025 01:36
    % Zeit 3 ms, GC 0 ms, Lips 1352000, Uhr 11.08.2025 01:36
    % Zeit 3 ms, GC 0 ms, Lips 1355333, Uhr 11.08.2025 01:36
    true.

    Can your Prolog system do that?

    P.S.: Benchmark was:

    singletons(N) :-
    -a-a-a hydra2(N,Y),
    -a-a-a between(1,1000,_), term_singletons(Y,_), fail; true.

    hydra2(0, _) :- !.
    hydra2(N, s(X,X)) :-
    -a-a-a M is N-1,
    -a-a-a hydra2(M, X).

    Bye



    --- Synchronet 3.21a-Linux NewsLink 1.2