• 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
  • From Mild Shock@janburse@fastmail.fm to comp.lang.prolog on Mon Oct 27 14:40:30 2025
    From Newsgroup: comp.lang.prolog

    Hi,

    Now I wish I had a Prolog system at hand that
    could do what one could see in an old version of
    LPA Prolog, and even going beyond. Namely:

    print(X | Y) :- write(X), maplist(write, Y).

    So basically the list head and tail matching for
    Prolog compounds. It has an additional challenge,
    how does the Prolog predicate catalogue look

    like. There is now a variadic predicate. But on
    2nd though and looking at Java Script, which has
    a prefix operator (...)/1 which can be used for:

    - **Rest Patterns:**
    One can define function print(X, ...Y) which
    is pretty much the same as the above.

    - **Spread Replacement:**
    But one can also invoke print(Z, ...V, ...W) which
    goes beyond a head tail inside a unify read.

    What would be a benefit? For example call/n could
    be the variadic definition, showing a further feature,
    namely Prolog variables at functor positions:

    call(F(...A), ...B) :- F(...A, ...B).

    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 Oct 27 14:57:07 2025
    From Newsgroup: comp.lang.prolog

    Hi,

    Currently I have a dozen solutions on a back
    of a envelope but cannot decide what to implement.
    I am also examing my native call/n implementation,

    which is in Java to learn what was used and whether
    we can abstract some new code instructions, and
    marveling at the C# Span struct:

    - Prolog compound creation:
    The call/n implementation differes from
    other Prolog compound creations in that
    new Object[] is called with a computed arity.
    The arity formula for spread replacement is:

    arity(F(...A, ...B)) = arity(A) + arity(B)

    - Prolog compound population
    The call/n implementation differs from
    other Prolog compound creations in that
    System.arraycopy() is called with computed
    destination indexes:

    dst(...A) = 0
    dst(...B) = arity(A)

    - Prolog compound matching
    The call/n implementation doesn't do much.
    It it knows that ...A is from the compound
    F(...) and that ...B is from the compound
    call(...), so a rest pattern is a pair of compound
    and source indexes, the used in System.arraycopy().

    src(...A) = 0
    src(...B) = 1

    Interstingly C# has institutionalized a lightweight
    struct Span, according All About Span: Exploring a
    New .NET Mainstay By Stephen Toub | January 2018.

    So I was thinking of converting a span ...X into
    two Prolog variables X1 and X2, where X1 points to
    the parent compound and X2 is the offset.

    But if we only allow a single rest pattern, in the spirit
    of LPA Prolog, X2 will be a constant that the Prolog
    compiler knows from the given rest pattern.

    So its still only one Prolog logical variable!

    Bye

    Mild Shock schrieb:
    Hi,

    Now I wish I had a Prolog system at hand that
    could do what one could see in an old version of
    LPA Prolog, and even going beyond. Namely:

    print(X | Y) :- write(X), maplist(write, Y).

    So basically the list head and tail matching for
    Prolog compounds. It has an additional challenge,
    how does the Prolog predicate catalogue look

    like. There is now a variadic predicate. But on
    2nd though and looking at Java Script, which has
    a prefix operator (...)/1 which can be used for:

    - **Rest Patterns:**
    -a One can define function print(X, ...Y) which
    -a is pretty much the same as the above.

    - **Spread Replacement:**
    -a But one can also invoke print(Z, ...V, ...W) which
    -a goes beyond a head tail inside a unify read.

    What would be a benefit? For example call/n could
    be the variadic definition, showing a further feature,
    namely Prolog variables at functor positions:

    call(F(...A), ...B) :- F(...A, ...B).

    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 Oct 27 15:16:17 2025
    From Newsgroup: comp.lang.prolog

    Hi,

    I see the following benefit of superintelligence
    as a pair programming model over some internet
    community. This is based of my experience

    over the last weeks:

    - Benefit of Superintelligence:
    The superintelligence might not be the design
    lead that carries the main idea and makes the
    important decisions. Still ChatGPT, DeepSeek, etc..
    are exceptionally useful as RTFM slaves.

    - Drawback I of Community:
    Human communities are execeptionally bad at RTFM,
    as the case of Julio the Nazi Retard shows.
    He was even not able to organize a copy of the
    ISO core standard document.

    - Dawback II of Community:
    Human communities tend to become vanity churches,
    where everybody can leave a mark, even when its
    a little pile of poo. An excellent example is golangs
    short function literals. Miles and miles since 2022,
    but no implementation yet:

    proposal: spec: short function literals #21498 https://github.com/golang/go/issues/21498#issuecomment-1132271548

    Drawback II is used by many big companies, such
    as Google, Apple, etc.. The goal of this use of
    social media is to act as magnet, and to tweek
    SEO, search engine optimization.

    Thats the same goal behind SWI-Prolog discourse,
    just produce miles and miles of tapestry of
    poo pile, doesn't matter. The most important thing
    is to attract more and more cows (and flies),

    to fill the common land (Almend in German):

    Das Wort Allmende stammt aus dem altnordischen Wort
    rCRalmenningrrCL, was so viel wie rCRwas jedem geh||rtrCL bedeutet https://de.wikipedia.org/wiki/Allmende

    Bye

    Mild Shock schrieb:
    Hi,

    Currently I have a dozen solutions on a back
    of a envelope but cannot decide what to implement.
    I am also examing my native call/n implementation,

    which is in Java to learn what was used and whether
    we can abstract some new code instructions, and
    marveling at the C# Span struct:

    - Prolog compound creation:
    -a The call/n implementation differes from
    -a other Prolog compound creations in that
    -a new Object[] is called with a computed arity.
    -a The arity formula for spread replacement is:

    arity(F(...A, ...B)) = arity(A) + arity(B)

    - Prolog compound population
    -a The call/n implementation differs from
    -a other Prolog compound creations in that
    -a System.arraycopy() is called with computed
    -a destination indexes:

    dst(...A) = 0
    dst(...B) = arity(A)

    - Prolog compound matching
    -a The call/n implementation doesn't do much.
    -a It it knows that ...A is from the compound
    -a F(...) and that ...B is from the compound
    -a call(...), so a rest pattern is a pair of compound
    -a and source indexes, the used in System.arraycopy().

    src(...A) = 0
    src(...B) = 1

    Interstingly C# has institutionalized a lightweight
    struct Span, according All About Span: Exploring a
    New .NET Mainstay By Stephen Toub | January 2018.

    So I was thinking of converting a span ...X into
    two Prolog variables X1 and X2, where X1 points to
    the parent compound and X2 is the offset.

    But if we only allow a single rest pattern, in the spirit
    of LPA Prolog, X2 will be a constant that the Prolog
    compiler knows from the given rest pattern.

    So its still only one Prolog logical variable!

    Bye

    Mild Shock schrieb:
    Hi,

    Now I wish I had a Prolog system at hand that
    could do what one could see in an old version of
    LPA Prolog, and even going beyond. Namely:

    print(X | Y) :- write(X), maplist(write, Y).

    So basically the list head and tail matching for
    Prolog compounds. It has an additional challenge,
    how does the Prolog predicate catalogue look

    like. There is now a variadic predicate. But on
    2nd though and looking at Java Script, which has
    a prefix operator (...)/1 which can be used for:

    - **Rest Patterns:**
    -a-a One can define function print(X, ...Y) which
    -a-a is pretty much the same as the above.

    - **Spread Replacement:**
    -a-a But one can also invoke print(Z, ...V, ...W) which
    -a-a goes beyond a head tail inside a unify read.

    What would be a benefit? For example call/n could
    be the variadic definition, showing a further feature,
    namely Prolog variables at functor positions:

    call(F(...A), ...B) :- F(...A, ...B).

    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 Tue Oct 28 13:54:48 2025
    From Newsgroup: comp.lang.prolog

    Hi,

    China tightens the screws: Influencers now
    need degrees to speak on finance, health, law

    "China has rolled out a new law requiring
    influencers to prove their qualifications before
    posting about topics like finance, health or law.
    While officials call it a fight against misinformation,
    critics see it as a blow to online freedom." https://www.livemint.com/news/world/china-tightens-the-screws-influencers-now-need-degrees-to-speak-on-finance-health-law-11761619952479.html

    Maybe this will motivate the turkish woman,
    I am asking her already for long to attend

    some classes and make a few course certificates.

    Bye

    Mild Shock schrieb:
    Hi,

    I see the following benefit of superintelligence
    as a pair programming model over some internet
    community. This is based of my experience

    over the last weeks:

    - Benefit of Superintelligence:
    -a The superintelligence might not be the design
    -a lead that carries the main idea and makes the
    -a important decisions. Still ChatGPT, DeepSeek, etc..
    -a are exceptionally useful as RTFM slaves.

    - Drawback I of Community:
    -a Human communities are execeptionally bad at RTFM,
    -a as the case of Julio the Nazi Retard shows.
    -a He was even not able to organize a copy of the
    -a ISO core standard document.

    - Dawback II of Community:
    -a Human communities tend to become vanity churches,
    -a where everybody can leave a mark, even when its
    -a a little pile of poo. An excellent example is golangs
    -a short function literals. Miles and miles since 2022,
    -a but no implementation yet:

    proposal: spec: short function literals #21498 https://github.com/golang/go/issues/21498#issuecomment-1132271548

    Drawback II is used by many big companies, such
    as Google, Apple, etc.. The goal of this use of
    social media is to act as magnet, and to tweek
    SEO, search engine optimization.

    Thats the same goal behind SWI-Prolog discourse,
    just produce miles and miles of tapestry of
    poo pile, doesn't matter. The most important thing
    is to attract more and more cows (and flies),

    to fill the common land (Almend in German):

    Das Wort Allmende stammt aus dem altnordischen Wort
    rCRalmenningrrCL, was so viel wie rCRwas jedem geh||rtrCL bedeutet https://de.wikipedia.org/wiki/Allmende

    Bye


    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Mild Shock@janburse@fastmail.fm to comp.lang.prolog on Tue Oct 28 13:57:34 2025
    From Newsgroup: comp.lang.prolog

    Hi,

    China tightens the screws: Influencers now
    need degrees to speak on finance, health, law

    "China has rolled out a new law requiring
    influencers to prove their qualifications before
    posting about topics like finance, health or law.
    While officials call it a fight against misinformation,
    critics see it as a blow to online freedom." https://www.livemint.com/news/world/china-tightens-the-screws-influencers-now-need-degrees-to-speak-on-finance-health-law-11761619952479.html

    Maybe this will motivate Boris the Loris, and
    Julio the Nazi Retard, to take logic more seriously.

    Bye

    Bye

    Mild Shock schrieb:
    Hi,

    I see the following benefit of superintelligence
    as a pair programming model over some internet
    community. This is based of my experience

    over the last weeks:

    - Benefit of Superintelligence:
    -a The superintelligence might not be the design
    -a lead that carries the main idea and makes the
    -a important decisions. Still ChatGPT, DeepSeek, etc..
    -a are exceptionally useful as RTFM slaves.

    - Drawback I of Community:
    -a Human communities are execeptionally bad at RTFM,
    -a as the case of Julio the Nazi Retard shows.
    -a He was even not able to organize a copy of the
    -a ISO core standard document.

    - Dawback II of Community:
    -a Human communities tend to become vanity churches,
    -a where everybody can leave a mark, even when its
    -a a little pile of poo. An excellent example is golangs
    -a short function literals. Miles and miles since 2022,
    -a but no implementation yet:

    proposal: spec: short function literals #21498 https://github.com/golang/go/issues/21498#issuecomment-1132271548

    Drawback II is used by many big companies, such
    as Google, Apple, etc.. The goal of this use of
    social media is to act as magnet, and to tweek
    SEO, search engine optimization.

    Thats the same goal behind SWI-Prolog discourse,
    just produce miles and miles of tapestry of
    poo pile, doesn't matter. The most important thing
    is to attract more and more cows (and flies),

    to fill the common land (Almend in German):

    Das Wort Allmende stammt aus dem altnordischen Wort
    rCRalmenningrrCL, was so viel wie rCRwas jedem geh||rtrCL bedeutet https://de.wikipedia.org/wiki/Allmende

    Bye


    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Mild Shock@janburse@fastmail.fm to comp.lang.prolog on Tue Oct 28 21:06:08 2025
    From Newsgroup: comp.lang.prolog

    Hi,

    Communities were betrayed by GitHub . Everybody
    was lured into endlessly filling GitHub with code,
    enlessly providing tickets and discussions. Just

    for their own vanity. While LaMDA (behind closed
    doors) use this much of data (probably other sources
    than only GitHub, remember there was Google+):

    "The pre-training dataset consists of 2.97B
    documents, 1.12B dialogs, and 13.39B utterances,
    for a total of 1.56T words. The largest LaMDA model
    has 137B non-embedding parameters."
    https://en.wikipedia.org/wiki/LaMDA

    The matrix is now booting. GitHub users rubbing
    their eyes. First there was a helpful chatbot as
    a sidebar for tickets. Not there is a chatbot

    on the front page and asks you, how it can help you.
    I can chose among, but its like in a computer game,
    if I use a credit card you can get more:

    Fast and cost-efficient
    - GPT-5 mini
    - o4-mini

    Versatile and highly intelligent
    - GPT-4.1
    - GPT-40
    - Claude Sonnet 3.5
    - Claude Sonnet 3.7
    - Claude Sonnet 4
    - Gemini 2.5 Pro
    - 03
    - GPT-5

    Most powerful at complex tasks
    - Claude Sonnet 3.7 Thinking
    - Claude Opus 4

    Home dashboard update [Public preview feedback] https://github.com/orgs/community/discussions/177902

    I wouldn't underestimate the possibility of this
    integration to collect more dialog data, and even
    deep software problem solving skill data.

    Welcome to the Matrix!

    Bye

    Mild Shock schrieb:
    Hi,

    China tightens the screws: Influencers now
    need degrees to speak on finance, health, law

    "China has rolled out a new law requiring
    influencers to prove their qualifications before
    posting about topics like finance, health or law.
    While officials call it a fight against misinformation,
    critics see it as a blow to online freedom." https://www.livemint.com/news/world/china-tightens-the-screws-influencers-now-need-degrees-to-speak-on-finance-health-law-11761619952479.html


    Maybe this will motivate Boris the Loris, and
    Julio the Nazi Retard, to take logic more seriously.

    Bye

    Bye

    Mild Shock schrieb:
    Hi,

    I see the following benefit of superintelligence
    as a pair programming model over some internet
    community. This is based of my experience

    over the last weeks:

    - Benefit of Superintelligence:
    -a-a The superintelligence might not be the design
    -a-a lead that carries the main idea and makes the
    -a-a important decisions. Still ChatGPT, DeepSeek, etc..
    -a-a are exceptionally useful as RTFM slaves.

    - Drawback I of Community:
    -a-a Human communities are execeptionally bad at RTFM,
    -a-a as the case of Julio the Nazi Retard shows.
    -a-a He was even not able to organize a copy of the
    -a-a ISO core standard document.

    - Dawback II of Community:
    -a-a Human communities tend to become vanity churches,
    -a-a where everybody can leave a mark, even when its
    -a-a a little pile of poo. An excellent example is golangs
    -a-a short function literals. Miles and miles since 2022,
    -a-a but no implementation yet:

    proposal: spec: short function literals #21498
    https://github.com/golang/go/issues/21498#issuecomment-1132271548

    Drawback II is used by many big companies, such
    as Google, Apple, etc.. The goal of this use of
    social media is to act as magnet, and to tweek
    SEO, search engine optimization.

    Thats the same goal behind SWI-Prolog discourse,
    just produce miles and miles of tapestry of
    poo pile, doesn't matter. The most important thing
    is to attract more and more cows (and flies),

    to fill the common land (Almend in German):

    Das Wort Allmende stammt aus dem altnordischen Wort
    rCRalmenningrrCL, was so viel wie rCRwas jedem geh||rtrCL bedeutet
    https://de.wikipedia.org/wiki/Allmende

    Bye



    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Mild Shock@janburse@fastmail.fm to comp.lang.prolog on Sun Nov 2 15:50:56 2025
    From Newsgroup: comp.lang.prolog

    Hi,

    Here I am not agreeing with John W. Lloyd,
    when in his 2nd monograph Logic for Learning,
    he proposes basic terms to cover

    Logic for Learning
    https://users.cecs.anu.edu.au/~jwl/LogicforLearning/

    certain if-then-else lambda terms. We can also
    do without if-then-else, if we have a complete
    key domain and do not model a default.

    The translation is as follows:

    dict_arrow({D}, (X,Y) => Z) :- dict_arrow(D, X, Y, Z).

    dict_arrow(K:V, X, Y, (X = K, Y = V)).
    dict_arrow((A,B), X, Y, (C;D)) :-
    dict_arrow(A, X, Y, C),
    dict_arrow(B, X, Y, D).

    They work as expected:

    ?- dict_arrow({foo:123,bar:baz}, _X), call(_X, foo, Y).
    Y = 123;
    fail.

    ?- dict_arrow({foo:123,bar:baz}, _X), call(_X, jack, Y).
    fail.

    And these dicts even allow something that Mozilla
    arrow functions currently cannot do. They can yield,
    i.e. act as enumerators. Here an example enumerating keys:

    ?- dict_arrow({foo:123,bar:baz}, _X), call(_X, Y, _).
    Y = foo;
    Y = bar.

    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 Sun Nov 2 15:58:19 2025
    From Newsgroup: comp.lang.prolog

    Hi,

    That Mozilla has no yield in their arrow functions,
    is documented here:

    Arrow functions cannot use yield within their body
    and cannot be created as generator functions.

    https://developer.mozilla.org/en-US/docs/Web/JavaScript/Reference/Functions/Arrow_functions

    So the Dogelog Player arrow functions are the
    next step in short function literals. They offer the
    beauty of unification and backtracking.

    We made the keys example to show backtracking:

    ?- dict_arrow({foo:123,bar:baz}, _X), call(_X, Y, _).
    Y = foo;
    Y = bar.

    But this example suffers from a spurious choice point:

    ?- dict_arrow({foo:123,bar:baz}, _X), call(_X, foo, Y).
    Y = 123;
    fail.

    If we put the arrow function for the dict, into a static
    clause, Dogelog Player will do an ahead of time compilation
    of the arrow functions, and the spurious choice point goes away:

    ?- [user].
    lloyd(((X,Y) => (X = foo, Y = 123; X = bar, Y = baz))).
    ^Z

    ?- lloyd(_D), reference(_D).
    true.

    ?- lloyd(_D), call(_D, foo, X).
    X = 123.

    Bye

    Mild Shock schrieb:
    Hi,

    Here I am not agreeing with John W. Lloyd,
    when in his 2nd monograph Logic for Learning,
    he proposes basic terms to cover

    Logic for Learning
    https://users.cecs.anu.edu.au/~jwl/LogicforLearning/

    certain if-then-else lambda terms. We can also
    do without if-then-else, if we have a complete
    key domain and do not model a default.

    The translation is as follows:

    dict_arrow({D}, (X,Y) => Z) :- dict_arrow(D, X, Y, Z).

    dict_arrow(K:V, X, Y, (X = K, Y = V)).
    dict_arrow((A,B), X, Y, (C;D)) :-
    -a-a dict_arrow(A, X, Y, C),
    -a-a dict_arrow(B, X, Y, D).

    They work as expected:

    ?- dict_arrow({foo:123,bar:baz}, _X), call(_X, foo, Y).
    Y = 123;
    fail.

    ?- dict_arrow({foo:123,bar:baz}, _X), call(_X, jack, Y).
    fail.

    And these dicts even allow something that Mozilla
    arrow functions currently cannot do. They can yield,
    i.e. act as enumerators. Here an example enumerating keys:

    ?- dict_arrow({foo:123,bar:baz}, _X), call(_X, Y, _).
    Y = foo;
    Y = bar.

    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 Sun Nov 2 16:28:49 2025
    From Newsgroup: comp.lang.prolog

    Hi,

    Most higher order theorem provers have dicts
    somewhere. The most common approach is to define
    a declarative mutator:

    Lean:

    def fun_update (f : +# raA +#) (a : +#) (b : +#) : +# raA +# :=
    ++ x => if x = a then b else f x

    But the above sees a dict as a function , if we
    see Super Dicts as relations. We don't need necessarely
    a fun_update that introduces a if-then-else,

    if we construct super dicts. If we know what we
    are doing, we can construct them by disjoint union
    whatever. Even a set theoretical view would allow

    such a if-then-else free construction for functions.
    In Prolog there is no notational advantage of seeing
    them as functions, or have the SWI-Prolog nonsense of

    dot operator. In the examples I use call/n to invoke
    them, and call/n in Prolog comes from the relational world.
    And defining the SWI-Prolog (.)/3 is trivial for Super Dicts:

    .(D, K, V) :- call(D, K, V).

    The only beauty we find in SWI-Prolog, that the dot
    operator allows various modes, but this is bootstrapped
    from the function view, not using the existing

    relations view of clauses. But I guess in practice
    nobody is using certain available modes?

    Bye

    P.S.: Now I am thinking of rewriting library(misc/dict),
    to manipulate dicts as arrow functions. But maybe should
    first work on assert/retract on arrow functions.

    If we don't use John W. Lloyd, we can use PaulsonrCOs HF,
    in case we need some theoretical underpinning and would
    like to reason about them.

    Defining relation extension:

    R[a|->b] := R <| (a,b)

    Or defining "calling" them:

    call(D, K, V) := (K,V) ree R

    See also:

    A Mechanised Proof of G||del's
    Incompleteness Theorems using Nominal Isabelle
    The work follows +Uwierczkowski's detailed
    proof of the theorems using hereditarily
    finite (HF) set theory.
    https://arxiv.org/abs/2104.13792

    Mild Shock schrieb:
    Hi,

    That Mozilla has no yield in their arrow functions,
    is documented here:

    Arrow functions cannot use yield within their body
    and cannot be created as generator functions.

    https://developer.mozilla.org/en-US/docs/Web/JavaScript/Reference/Functions/Arrow_functions


    So the Dogelog Player arrow functions are the
    next step in short function literals. They offer the
    beauty of unification and backtracking.

    We made the keys example to show backtracking:

    ?- dict_arrow({foo:123,bar:baz}, _X), call(_X, Y, _).
    Y = foo;
    Y = bar.

    But this example suffers from a spurious choice point:

    ?- dict_arrow({foo:123,bar:baz}, _X), call(_X, foo, Y).
    Y = 123;
    fail.

    If we put the arrow function for the dict, into a static
    clause, Dogelog Player will do an ahead of time compilation
    of the arrow functions, and the spurious choice point goes away:

    ?- [user].
    lloyd(((X,Y) => (X = foo, Y = 123; X = bar, Y = baz))).
    ^Z

    ?- lloyd(_D), reference(_D).
    true.

    ?- lloyd(_D), call(_D, foo, X).
    X = 123.

    Bye

    Mild Shock schrieb:
    Hi,

    Here I am not agreeing with John W. Lloyd,
    when in his 2nd monograph Logic for Learning,
    he proposes basic terms to cover

    Logic for Learning
    https://users.cecs.anu.edu.au/~jwl/LogicforLearning/

    certain if-then-else lambda terms. We can also
    do without if-then-else, if we have a complete
    key domain and do not model a default.

    The translation is as follows:

    dict_arrow({D}, (X,Y) => Z) :- dict_arrow(D, X, Y, Z).

    dict_arrow(K:V, X, Y, (X = K, Y = V)).
    dict_arrow((A,B), X, Y, (C;D)) :-
    -a-a-a dict_arrow(A, X, Y, C),
    -a-a-a dict_arrow(B, X, Y, D).

    They work as expected:

    ?- dict_arrow({foo:123,bar:baz}, _X), call(_X, foo, Y).
    Y = 123;
    fail.

    ?- dict_arrow({foo:123,bar:baz}, _X), call(_X, jack, Y).
    fail.

    And these dicts even allow something that Mozilla
    arrow functions currently cannot do. They can yield,
    i.e. act as enumerators. Here an example enumerating keys:

    ?- dict_arrow({foo:123,bar:baz}, _X), call(_X, Y, _).
    Y = foo;
    Y = bar.

    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 Sun Nov 2 16:41:52 2025
    From Newsgroup: comp.lang.prolog

    Hi,

    It seems there is a gap between doing certain
    things , like for example prototype-based programming
    where we would store arrow functions in dicts.

    To reasoning about. For eample I find:

    Bryan Ford: Dictionary Abstractions and
    Implementations in Isabelle/HOL
    https://bford.info/isabelle/dict/

    Lars Hupel: Certifying Dictionary Construction
    in Isabelle/HOL
    https://lars.hupel.info/pub/dict.pdf

    The Bryan Ford work is in the level of Logtalk
    value objects. The Lars Hupel work tells me:

    4 Limitations
    "Specifiedness A particularly thorny issue is
    presented by functions that return other
    functions. While currying itself is a common
    idiom in functional programming, manipulation
    of partially-applied functions would require a
    non-trivial data flow analysis."

    So what now? Can we not more broadly ahead
    of time compile them? Will Isabelle/HOL stay in
    limbo, no JavaScript backend, no Go backend.

    Bye


    Mild Shock schrieb:
    Hi,

    That Mozilla has no yield in their arrow functions,
    is documented here:

    Arrow functions cannot use yield within their body
    and cannot be created as generator functions.

    https://developer.mozilla.org/en-US/docs/Web/JavaScript/Reference/Functions/Arrow_functions


    So the Dogelog Player arrow functions are the
    next step in short function literals. They offer the
    beauty of unification and backtracking.

    We made the keys example to show backtracking:

    ?- dict_arrow({foo:123,bar:baz}, _X), call(_X, Y, _).
    Y = foo;
    Y = bar.

    But this example suffers from a spurious choice point:

    ?- dict_arrow({foo:123,bar:baz}, _X), call(_X, foo, Y).
    Y = 123;
    fail.

    If we put the arrow function for the dict, into a static
    clause, Dogelog Player will do an ahead of time compilation
    of the arrow functions, and the spurious choice point goes away:

    ?- [user].
    lloyd(((X,Y) => (X = foo, Y = 123; X = bar, Y = baz))).
    ^Z

    ?- lloyd(_D), reference(_D).
    true.

    ?- lloyd(_D), call(_D, foo, X).
    X = 123.

    Bye

    Mild Shock schrieb:
    Hi,

    Here I am not agreeing with John W. Lloyd,
    when in his 2nd monograph Logic for Learning,
    he proposes basic terms to cover

    Logic for Learning
    https://users.cecs.anu.edu.au/~jwl/LogicforLearning/

    certain if-then-else lambda terms. We can also
    do without if-then-else, if we have a complete
    key domain and do not model a default.

    The translation is as follows:

    dict_arrow({D}, (X,Y) => Z) :- dict_arrow(D, X, Y, Z).

    dict_arrow(K:V, X, Y, (X = K, Y = V)).
    dict_arrow((A,B), X, Y, (C;D)) :-
    -a-a-a dict_arrow(A, X, Y, C),
    -a-a-a dict_arrow(B, X, Y, D).

    They work as expected:

    ?- dict_arrow({foo:123,bar:baz}, _X), call(_X, foo, Y).
    Y = 123;
    fail.

    ?- dict_arrow({foo:123,bar:baz}, _X), call(_X, jack, Y).
    fail.

    And these dicts even allow something that Mozilla
    arrow functions currently cannot do. They can yield,
    i.e. act as enumerators. Here an example enumerating keys:

    ?- dict_arrow({foo:123,bar:baz}, _X), call(_X, Y, _).
    Y = foo;
    Y = bar.

    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 Sun Nov 2 19:47:04 2025
    From Newsgroup: comp.lang.prolog

    Hi,

    Calling Prolog a logic programming language, is as much
    a joke as negation as failure induces non-monotonicity
    by its closed world assumption. Question is are there

    some Prolog++ out in the wild, that do not make the
    idea of object oriented logic programming yet another
    laughing stock? If we understand that Datalog, i.e.

    banning function symbols, already can profit from the
    so called Clark Completion, to understand its semantics.
    It might be a short step to see that a Prolog++ will

    even suffer more and need a similar explanation. Super
    Dicts bootstrapped from Arrow Functions offers such an
    explanation. Take a look at our Super Dict example,

    where (=>)/2 is the arrow function constructor:

    R = (X,Y) => (X = foo, Y = 123; X = bar, Y = baz)

    The logical reading for membership is indeed,
    where (<-)/2 is logical implication:

    (K,V) e R <- (K = foo, V = 123; K = bar, V = baz)

    But we cannot derive negative information, a failure
    of a goal G, is not the same as the derivation of
    a goal ~G. So we can apply Clark Completion and will get:

    (K,V) ree R <- (K rea foo; V rea 123), (K rea bar; V rea baz)

    One can imagine that we use dif/2 for (rea)/2. But the
    translaton is quite different from Ulrich Neumerkels
    indexing dif/2, since we didn't start with John W. Lloyds

    if-then-else, so the logical completion of the dict,
    which is not a if-then-else cascade, is also not directly a
    if-then-else cascade of an improved if-then-else.

    Bye

    BTW: The backtracking through disjunction in the negative
    part can be eliminated. By writing it as follows, using
    some properties of (rea)/2:

    (K,V) ree R <- (K,V) rea (foo, 123), (K,V) rea (bar, baz).

    So negation dict membership becomes a collection of
    dif/2 constraints.

    Mild Shock schrieb:
    Hi,

    It seems there is a gap between doing certain
    things , like for example prototype-based programming
    where we would store arrow functions in dicts.

    To reasoning about. For eample I find:

    Bryan Ford: Dictionary Abstractions and
    Implementations in Isabelle/HOL
    https://bford.info/isabelle/dict/

    Lars Hupel: Certifying Dictionary Construction
    in Isabelle/HOL
    https://lars.hupel.info/pub/dict.pdf

    The Bryan Ford work is in the level of Logtalk
    value objects. The Lars Hupel work tells me:

    4 Limitations
    "Specifiedness A particularly thorny issue is
    presented by functions that return other
    functions. While currying itself is a common
    idiom in functional programming, manipulation
    of partially-applied functions would require a
    non-trivial data flow analysis."

    So what now? Can we not more broadly ahead
    of time compile them? Will Isabelle/HOL stay in
    limbo, no JavaScript backend, no Go backend.

    Bye

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Mild Shock@janburse@fastmail.fm to comp.lang.prolog on Wed Nov 5 20:23:16 2025
    From Newsgroup: comp.lang.prolog

    Hi,

    Now that we managed to conceive nested arrow
    functions, next step on the menu is inner if-then-else
    or disjunction, like inside a findall/3 or inside

    (\+)/1, doing ahead of time compilation (AOT).
    That it leads to problems of rational trees was
    more a psyop easter egg of mine. Although I am not

    yet sure, in the long run the compiler should
    be able to handle rational trees, like copy_term/2
    can handle them. But before tackling inner

    if-then-else, first check the occurence frequency
    of then. Do they happen often? Is it worth AOT-ing
    them. Then also before tackling inner if-then-else,

    does the code use (,)/2, (;)/2 or (->)/2 in
    scenarios where it is used for meta programming
    i.e. _,_, _;_ or _->_ pattern for deconstruction

    or construction. And do these cases fall into
    the new arrow viability check adopte to a if-then-else
    viability check, or fall they through?

    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 Wed Nov 5 21:19:00 2025
    From Newsgroup: comp.lang.prolog

    Hi,

    Credits go to myself (an old Stackoverflow
    post of mine from 2020):

    The algorithm "A" according to Antoni Diller looks fairly simple: https://stackoverflow.com/questions/65066544/bracket-abstraction-in-prolog

    The OrReference aka Anonymous Predicate is just another variant
    of combinatorial logic. You can view OrReference having the same
    logtical status as a closed SKI expression.

    Plus to this guys here also already in 2004:

    Hiord: A Type-Free Higher-Order Logic Programming
    Language with Predicate Abstraction
    Daniel Cabeza, Manuel V. Hermenegildo, Manuel V. Hermenegildo https://www.researchgate.net/publication/221052995

    Only they botched it, since recursion and mutual recursion
    needs still some fixpoint operator construction. But
    the Anonymous Predicate thingy is beautiful, without

    any fixpoint operator construction needed:

    test(Even) :-
    Even = ((X) => Y^(X = n; X = s(Y), call(Odd, Y))),
    Odd = ((X) => Y^(X = s(Y), call(Even, Y))).

    ?- listing(test).
    test(A) :-
    A = 0rReference(B),
    B = 0rReference(A).

    Basically evaluating a rational tree closure:

    ?- test(_X), call(_X, s(s(s(s(n))))).
    true.

    ?- test(_X), call(_X, s(s(s(s(s(n)))))).
    fail.

    ?- test(_X), call(_X, s(s(s(s(s(s(n))))))).
    true.

    Bye

    Mild Shock schrieb:
    Hi,

    Now that we managed to conceive nested arrow
    functions, next step on the menu is inner if-then-else
    or disjunction, like inside a findall/3 or inside

    (\+)/1, doing ahead of time compilation (AOT).
    That it leads to problems of rational trees was
    more a psyop easter egg of mine. Although I am not

    yet sure, in the long run the compiler should
    be able to handle rational trees, like copy_term/2
    can handle them. But before tackling inner

    if-then-else, first check the occurence frequency
    of then. Do they happen often? Is it worth AOT-ing
    them. Then also before tackling inner if-then-else,

    does the code use (,)/2, (;)/2 or (->)/2 in
    scenarios where it is used for meta programming
    i.e. _,_, _;_ or _->_ pattern for deconstruction

    or construction. And do these cases fall into
    the new arrow viability check adopte to a if-then-else
    viability check, or fall they through?

    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