• DCG is easily affected (Was: The Ghosts in my Cabinet: Indexing)

    From Mild Shock@janburse@fastmail.fm to comp.lang.prolog on Fri Jul 11 09:38:00 2025
    From Newsgroup: comp.lang.prolog


    Interestingly, DCG is also affect. Here a
    DCG take of an append app/3, it has the 2nd
    and 3rd argument swapped:

    ?- [user].
    app([]) --> [].
    app([X|Y]) --> [X], app(Y).
    ^D

    Looks like an append, taking the argument swap
    into account, the A=B is redundant, could
    be optimized away:

    /* SWI-Prolog 9.3.25 */
    ?- listing(app/3).
    app([], A, B) :-
    A=B.
    app([A|B], [A|C], D) :-
    app(B, C, D).

    And works like an append, again taking the
    argument swap into account:

    ?- app([1],X,[2,3]).
    X = [1, 2, 3].

    Now the multi-argument indexing test, still
    taking the argument swap into account;

    /* ECLiPSe Prolog 7.1beta #13 */
    [eclipse 3]: app(X, [1], Y).

    X = []
    Y = [1]
    Yes (0.00s cpu, solution 1, maybe more) ? ;

    X = [1]
    Y = []
    Yes (0.00s cpu, solution 2)

    Versus:

    /* SWI-Prolog 9.3.25 */
    ?- app(X, [1], Y).
    X = [],
    Y = [1] ;
    X = [1],
    Y = [] ;
    false.

    Mild Shock schrieb:
    I am currently doing a re-evaluation of an old
    Prolog system, checking what features I could adopt.
    This is unlike the current trend where people have
    turned their focus on GUIs, like XPCE,

    or a are stuck in an endless loop of parser
    problems, like in Trealla. But I would nevertheless
    share my finding. Take this simple example of
    a list append:

    app([], X, X).
    app([X|Y], Z, [X|T]) :- app(Y, Z, T).

    ECLiPSe Prolog gives me, only one redo question
    in the top-level:

    /* ECLiPSe Prolog 7.1beta #13 */
    [eclipse 2]: app(X,Y,[1]).

    X = []
    Y = [1]
    Yes (0.00s cpu, solution 1, maybe more) ? ;

    X = [1]
    Y = []
    Yes (0.00s cpu, solution 2)

    In SWI-Prolog I find, two redo questions
    in the top.level:

    /* SWI-Prolog 9.3.25 */
    ?- app(X,Y,[1]).
    X = [],
    Y = [1] ;
    X = [1],
    Y = [] ;
    false.

    I know SWI-Prolog handles lists differently
    than other Prolog terms during indexing. Could
    this be the reason? Or maybe that the call is
    not “hot” enough, so it doesn’t get JIT-ed.

    ECLiPSe Prolog does it on the very first call,
    and I assume its due to a kind of index on
    the 3rd argument.


    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Mild Shock@janburse@fastmail.fm to comp.lang.prolog on Tue Jul 15 15:20:02 2025
    From Newsgroup: comp.lang.prolog

    Hi,

    That false/0 and not fail/0 is now all over the place,
    I don't mean in person but for example here:

    ?- X=f(f(X), X), Y=f(Y, f(Y)), X = Y.
    false.

    Is a little didactical nightmare.

    Syntactic unification has mathematical axioms (1978),
    to fully formalize unifcation you would need to
    formalize both (=)/2 and (≠)/2 (sic!), otherwise you
    rely on some negation as failure concept.

    Keith L. Clark, Negation as Failure https://link.springer.com/chapter/10.1007/978-1-4684-3384-5_11

    You can realize a subset of a mixture of (=)/2
    and (≠)/2 in the form of a vanilla unify Prolog
    predicate using some of the meta programming
    facilities of Prolog, like var/1 and having some

    negation as failure reading:

    /* Vanilla Unify */
    unify(V, W) :- var(V), var(W), !, (V \== W -> V = W; true).
    unify(V, T) :- var(V), !, V = T.
    unify(S, W) :- var(W), !, W = S.
    unify(S, T) :- functor(S, F, N), functor(T, F, N),
    S =.. [F|L], T =.. [F|R], maplist(unify, L, R).

    I indeed get:

    ?- X=f(f(X), X), Y=f(Y, f(Y)), unify(X,Y).
    false.

    If the vanilla unify/2 already fails then unify
    with and without subject to occurs check, will also
    fail, and unify with and without ability to
    handle rational terms, will also fail:

    Bye

    Mild Shock schrieb:

    Interestingly, DCG is also affect. Here a
    DCG take of an append app/3, it has the 2nd
    and 3rd argument swapped:

    ?- [user].
    app([]) --> [].
    app([X|Y]) --> [X], app(Y).
    ^D

    Looks like an append, taking the argument swap
    into account, the A=B is redundant, could
    be optimized away:

    /* SWI-Prolog 9.3.25 */
    ?- listing(app/3).
    app([], A, B) :-
        A=B.
    app([A|B], [A|C], D) :-
        app(B, C, D).

    And works like an append, again taking the
    argument swap into account:

    ?- app([1],X,[2,3]).
    X = [1, 2, 3].

    Now the multi-argument indexing test, still
    taking the argument swap into account;

    /* ECLiPSe Prolog 7.1beta #13 */
    [eclipse 3]: app(X, [1], Y).

    X = []
    Y = [1]
    Yes (0.00s cpu, solution 1, maybe more) ? ;

    X = [1]
    Y = []
    Yes (0.00s cpu, solution 2)

    Versus:

    /* SWI-Prolog 9.3.25 */
    ?- app(X, [1], Y).
    X = [],
    Y = [1] ;
    X = [1],
    Y = [] ;
    false.

    Mild Shock schrieb:
    I am currently doing a re-evaluation of an old
    Prolog system, checking what features I could adopt.
    This is unlike the current trend where people have
    turned their focus on GUIs, like XPCE,

    or a are stuck in an endless loop of parser
    problems, like in Trealla. But I would nevertheless
    share my finding. Take this simple example of
    a list append:

    app([], X, X).
    app([X|Y], Z, [X|T]) :- app(Y, Z, T).

    ECLiPSe Prolog gives me, only one redo question
    in the top-level:

    /* ECLiPSe Prolog 7.1beta #13 */
    [eclipse 2]: app(X,Y,[1]).

    X = []
    Y = [1]
    Yes (0.00s cpu, solution 1, maybe more) ? ;

    X = [1]
    Y = []
    Yes (0.00s cpu, solution 2)

    In SWI-Prolog I find, two redo questions
    in the top.level:

    /* SWI-Prolog 9.3.25 */
    ?- app(X,Y,[1]).
    X = [],
    Y = [1] ;
    X = [1],
    Y = [] ;
    false.

    I know SWI-Prolog handles lists differently
    than other Prolog terms during indexing. Could
    this be the reason? Or maybe that the call is
    not “hot” enough, so it doesn’t get JIT-ed.

    ECLiPSe Prolog does it on the very first call,
    and I assume its due to a kind of index on
    the 3rd argument.



    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Mild Shock@janburse@fastmail.fm to comp.lang.prolog on Tue Jul 15 15:24:07 2025
    From Newsgroup: comp.lang.prolog

    Hi,

    Now somebody was so friendly to spear head
    a new Don Quixote attempt in fighting the
    windmills of compare/3. Interestingly my

    favorite counter example still goes through:

    ?- X = X-0-9-7-6-5-4-3-2-1, Y = Y-7-5-8-2-4-1,
    compare_with_stack(C, X, Y).
    X = X-0-9-7-6-5-4-3-2-1,
    Y = Y-7-5-8-2-4-1,
    C = (<).

    ?- H = H-9-7-6-5-4-3-2-1-0, Z = H-9-7-6-5-4-3-2-1, Y = Y-7-5-8-2-4-1,
    compare_with_stack(C, Z, Y).
    H = H-9-7-6-5-4-3-2-1-0,
    Z = H-9-7-6-5-4-3-2-1,
    Y = Y-7-5-8-2-4-1,
    C = (>).

    ?- H = H-9-7-6-5-4-3-2-1-0, Z = H-9-7-6-5-4-3-2-1, X =
    X-0-9-7-6-5-4-3-2-1,
    compare_with_stack(C, Z, X).
    H = H-9-7-6-5-4-3-2-1-0,
    Z = X, X = X-0-9-7-6-5-4-3-2-1,
    C = (=).

    I posted it here in March 2023:

    Careful with compare/3 and Brent algorithm https://swi-prolog.discourse.group/t/careful-with-compare-3-and-brent-algorithm/6413

    Its based that rational terms are indeed in
    some relation to rational numbers. The above
    terms are related to:

    10/81 = 0.(123456790) = 0.12345679(02345679)

    Bye

    Mild Shock schrieb:
    Hi,

    That false/0 and not fail/0 is now all over the place,
    I don't mean in person but for example here:

    ?- X=f(f(X), X), Y=f(Y, f(Y)), X = Y.
    false.

    Is a little didactical nightmare.

    Syntactic unification has mathematical axioms (1978),
    to fully formalize unifcation you would need to
    formalize both (=)/2 and (≠)/2 (sic!), otherwise you
    rely on some negation as failure concept.

    Keith L. Clark, Negation as Failure https://link.springer.com/chapter/10.1007/978-1-4684-3384-5_11

    You can realize a subset of a mixture of (=)/2
    and (≠)/2 in the form of a vanilla unify Prolog
    predicate using some of the meta programming
    facilities of Prolog, like var/1 and having some

    negation as failure reading:

    /* Vanilla Unify */
    unify(V, W) :- var(V), var(W), !, (V \== W -> V = W; true).
    unify(V, T) :- var(V), !, V = T.
    unify(S, W) :- var(W), !, W = S.
    unify(S, T) :- functor(S, F, N), functor(T, F, N),
         S =.. [F|L], T =.. [F|R], maplist(unify, L, R).

    I indeed get:

    ?- X=f(f(X), X), Y=f(Y, f(Y)), unify(X,Y).
    false.

    If the vanilla unify/2 already fails then unify
    with and without subject to occurs check, will also
    fail, and unify with and without ability to
    handle rational terms, will also fail:

    Bye

    Mild Shock schrieb:

    Interestingly, DCG is also affect. Here a
    DCG take of an append app/3, it has the 2nd
    and 3rd argument swapped:

    ?- [user].
    app([]) --> [].
    app([X|Y]) --> [X], app(Y).
    ^D

    Looks like an append, taking the argument swap
    into account, the A=B is redundant, could
    be optimized away:

    /* SWI-Prolog 9.3.25 */
    ?- listing(app/3).
    app([], A, B) :-
         A=B.
    app([A|B], [A|C], D) :-
         app(B, C, D).

    And works like an append, again taking the
    argument swap into account:

    ?- app([1],X,[2,3]).
    X = [1, 2, 3].

    Now the multi-argument indexing test, still
    taking the argument swap into account;

    /* ECLiPSe Prolog 7.1beta #13 */
    [eclipse 3]: app(X, [1], Y).

    X = []
    Y = [1]
    Yes (0.00s cpu, solution 1, maybe more) ? ;

    X = [1]
    Y = []
    Yes (0.00s cpu, solution 2)

    Versus:

    /* SWI-Prolog 9.3.25 */
    ?- app(X, [1], Y).
    X = [],
    Y = [1] ;
    X = [1],
    Y = [] ;
    false.

    Mild Shock schrieb:
    I am currently doing a re-evaluation of an old
    Prolog system, checking what features I could adopt.
    This is unlike the current trend where people have
    turned their focus on GUIs, like XPCE,

    or a are stuck in an endless loop of parser
    problems, like in Trealla. But I would nevertheless
    share my finding. Take this simple example of
    a list append:

    app([], X, X).
    app([X|Y], Z, [X|T]) :- app(Y, Z, T).

    ECLiPSe Prolog gives me, only one redo question
    in the top-level:

    /* ECLiPSe Prolog 7.1beta #13 */
    [eclipse 2]: app(X,Y,[1]).

    X = []
    Y = [1]
    Yes (0.00s cpu, solution 1, maybe more) ? ;

    X = [1]
    Y = []
    Yes (0.00s cpu, solution 2)

    In SWI-Prolog I find, two redo questions
    in the top.level:

    /* SWI-Prolog 9.3.25 */
    ?- app(X,Y,[1]).
    X = [],
    Y = [1] ;
    X = [1],
    Y = [] ;
    false.

    I know SWI-Prolog handles lists differently
    than other Prolog terms during indexing. Could
    this be the reason? Or maybe that the call is
    not “hot” enough, so it doesn’t get JIT-ed.

    ECLiPSe Prolog does it on the very first call,
    and I assume its due to a kind of index on
    the 3rd argument.




    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Mild Shock@janburse@fastmail.fm to comp.lang.prolog on Tue Jul 15 15:28:51 2025
    From Newsgroup: comp.lang.prolog

    Corr.: Small typo in the number
    expansion itself, should read:

    10/81 = 0.(123456790) = 0.12345679(012345679)

    Mild Shock schrieb:
    Hi,

    Now somebody was so friendly to spear head
    a new Don Quixote attempt in fighting the
    windmills of compare/3. Interestingly my

    favorite counter example still goes through:

    ?- X = X-0-9-7-6-5-4-3-2-1, Y = Y-7-5-8-2-4-1,
       compare_with_stack(C, X, Y).
    X = X-0-9-7-6-5-4-3-2-1,
    Y = Y-7-5-8-2-4-1,
    C = (<).

    ?- H = H-9-7-6-5-4-3-2-1-0, Z = H-9-7-6-5-4-3-2-1, Y = Y-7-5-8-2-4-1,
       compare_with_stack(C, Z, Y).
    H = H-9-7-6-5-4-3-2-1-0,
    Z = H-9-7-6-5-4-3-2-1,
    Y = Y-7-5-8-2-4-1,
    C = (>).

    ?- H = H-9-7-6-5-4-3-2-1-0, Z = H-9-7-6-5-4-3-2-1, X = X-0-9-7-6-5-4-3-2-1,
       compare_with_stack(C, Z, X).
    H = H-9-7-6-5-4-3-2-1-0,
    Z = X, X = X-0-9-7-6-5-4-3-2-1,
    C = (=).

    I posted it here in March 2023:

    Careful with compare/3 and Brent algorithm https://swi-prolog.discourse.group/t/careful-with-compare-3-and-brent-algorithm/6413


    Its based that rational terms are indeed in
    some relation to rational numbers. The above
    terms are related to:

    10/81 = 0.(123456790) = 0.12345679(02345679)

    Bye

    Mild Shock schrieb:
    Hi,

    That false/0 and not fail/0 is now all over the place,
    I don't mean in person but for example here:

    ?- X=f(f(X), X), Y=f(Y, f(Y)), X = Y.
    false.

    Is a little didactical nightmare.

    Syntactic unification has mathematical axioms (1978),
    to fully formalize unifcation you would need to
    formalize both (=)/2 and (≠)/2 (sic!), otherwise you
    rely on some negation as failure concept.

    Keith L. Clark, Negation as Failure
    https://link.springer.com/chapter/10.1007/978-1-4684-3384-5_11

    You can realize a subset of a mixture of (=)/2
    and (≠)/2 in the form of a vanilla unify Prolog
    predicate using some of the meta programming
    facilities of Prolog, like var/1 and having some

    negation as failure reading:

    /* Vanilla Unify */
    unify(V, W) :- var(V), var(W), !, (V \== W -> V = W; true).
    unify(V, T) :- var(V), !, V = T.
    unify(S, W) :- var(W), !, W = S.
    unify(S, T) :- functor(S, F, N), functor(T, F, N),
          S =.. [F|L], T =.. [F|R], maplist(unify, L, R).

    I indeed get:

    ?- X=f(f(X), X), Y=f(Y, f(Y)), unify(X,Y).
    false.

    If the vanilla unify/2 already fails then unify
    with and without subject to occurs check, will also
    fail, and unify with and without ability to
    handle rational terms, will also fail:

    Bye

    Mild Shock schrieb:

    Interestingly, DCG is also affect. Here a
    DCG take of an append app/3, it has the 2nd
    and 3rd argument swapped:

    ?- [user].
    app([]) --> [].
    app([X|Y]) --> [X], app(Y).
    ^D

    Looks like an append, taking the argument swap
    into account, the A=B is redundant, could
    be optimized away:

    /* SWI-Prolog 9.3.25 */
    ?- listing(app/3).
    app([], A, B) :-
         A=B.
    app([A|B], [A|C], D) :-
         app(B, C, D).

    And works like an append, again taking the
    argument swap into account:

    ?- app([1],X,[2,3]).
    X = [1, 2, 3].

    Now the multi-argument indexing test, still
    taking the argument swap into account;

    /* ECLiPSe Prolog 7.1beta #13 */
    [eclipse 3]: app(X, [1], Y).

    X = []
    Y = [1]
    Yes (0.00s cpu, solution 1, maybe more) ? ;

    X = [1]
    Y = []
    Yes (0.00s cpu, solution 2)

    Versus:

    /* SWI-Prolog 9.3.25 */
    ?- app(X, [1], Y).
    X = [],
    Y = [1] ;
    X = [1],
    Y = [] ;
    false.

    Mild Shock schrieb:
    I am currently doing a re-evaluation of an old
    Prolog system, checking what features I could adopt.
    This is unlike the current trend where people have
    turned their focus on GUIs, like XPCE,

    or a are stuck in an endless loop of parser
    problems, like in Trealla. But I would nevertheless
    share my finding. Take this simple example of
    a list append:

    app([], X, X).
    app([X|Y], Z, [X|T]) :- app(Y, Z, T).

    ECLiPSe Prolog gives me, only one redo question
    in the top-level:

    /* ECLiPSe Prolog 7.1beta #13 */
    [eclipse 2]: app(X,Y,[1]).

    X = []
    Y = [1]
    Yes (0.00s cpu, solution 1, maybe more) ? ;

    X = [1]
    Y = []
    Yes (0.00s cpu, solution 2)

    In SWI-Prolog I find, two redo questions
    in the top.level:

    /* SWI-Prolog 9.3.25 */
    ?- app(X,Y,[1]).
    X = [],
    Y = [1] ;
    X = [1],
    Y = [] ;
    false.

    I know SWI-Prolog handles lists differently
    than other Prolog terms during indexing. Could
    this be the reason? Or maybe that the call is
    not “hot” enough, so it doesn’t get JIT-ed.

    ECLiPSe Prolog does it on the very first call,
    and I assume its due to a kind of index on
    the 3rd argument.





    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Mild Shock@janburse@fastmail.fm to comp.lang.prolog on Tue Jul 15 18:41:04 2025
    From Newsgroup: comp.lang.prolog

    Hi,

    Maybe AGI should take over proving.
    Just take the humans out of the loop
    of any programming, it leads to nowhere.

    Bye

    Julio Di Egidio schrieb:
    But we must thank MS for the nail in that coffin, too: they can't
    be satisfied with just a Lean broken by design, they must own the
    whole compartment: only poisoned meatballs for the public...

    -Julio

    Mild Shock schrieb:
    Corr.: Small typo in the number
    expansion itself, should read:

    10/81 = 0.(123456790) = 0.12345679(012345679)

    Mild Shock schrieb:
    Hi,

    Now somebody was so friendly to spear head
    a new Don Quixote attempt in fighting the
    windmills of compare/3. Interestingly my

    favorite counter example still goes through:

    ?- X = X-0-9-7-6-5-4-3-2-1, Y = Y-7-5-8-2-4-1,
        compare_with_stack(C, X, Y).
    X = X-0-9-7-6-5-4-3-2-1,
    Y = Y-7-5-8-2-4-1,
    C = (<).

    ?- H = H-9-7-6-5-4-3-2-1-0, Z = H-9-7-6-5-4-3-2-1, Y = Y-7-5-8-2-4-1,
        compare_with_stack(C, Z, Y).
    H = H-9-7-6-5-4-3-2-1-0,
    Z = H-9-7-6-5-4-3-2-1,
    Y = Y-7-5-8-2-4-1,
    C = (>).

    ?- H = H-9-7-6-5-4-3-2-1-0, Z = H-9-7-6-5-4-3-2-1, X =
    X-0-9-7-6-5-4-3-2-1,
        compare_with_stack(C, Z, X).
    H = H-9-7-6-5-4-3-2-1-0,
    Z = X, X = X-0-9-7-6-5-4-3-2-1,
    C = (=).

    I posted it here in March 2023:

    Careful with compare/3 and Brent algorithm
    https://swi-prolog.discourse.group/t/careful-with-compare-3-and-brent-algorithm/6413


    Its based that rational terms are indeed in
    some relation to rational numbers. The above
    terms are related to:

    10/81 = 0.(123456790) = 0.12345679(02345679)

    Bye

    Mild Shock schrieb:
    Hi,

    That false/0 and not fail/0 is now all over the place,
    I don't mean in person but for example here:

    ?- X=f(f(X), X), Y=f(Y, f(Y)), X = Y.
    false.

    Is a little didactical nightmare.

    Syntactic unification has mathematical axioms (1978),
    to fully formalize unifcation you would need to
    formalize both (=)/2 and (≠)/2 (sic!), otherwise you
    rely on some negation as failure concept.

    Keith L. Clark, Negation as Failure
    https://link.springer.com/chapter/10.1007/978-1-4684-3384-5_11

    You can realize a subset of a mixture of (=)/2
    and (≠)/2 in the form of a vanilla unify Prolog
    predicate using some of the meta programming
    facilities of Prolog, like var/1 and having some

    negation as failure reading:

    /* Vanilla Unify */
    unify(V, W) :- var(V), var(W), !, (V \== W -> V = W; true).
    unify(V, T) :- var(V), !, V = T.
    unify(S, W) :- var(W), !, W = S.
    unify(S, T) :- functor(S, F, N), functor(T, F, N),
          S =.. [F|L], T =.. [F|R], maplist(unify, L, R).

    I indeed get:

    ?- X=f(f(X), X), Y=f(Y, f(Y)), unify(X,Y).
    false.

    If the vanilla unify/2 already fails then unify
    with and without subject to occurs check, will also
    fail, and unify with and without ability to
    handle rational terms, will also fail:

    Bye

    Mild Shock schrieb:

    Interestingly, DCG is also affect. Here a
    DCG take of an append app/3, it has the 2nd
    and 3rd argument swapped:

    ?- [user].
    app([]) --> [].
    app([X|Y]) --> [X], app(Y).
    ^D

    Looks like an append, taking the argument swap
    into account, the A=B is redundant, could
    be optimized away:

    /* SWI-Prolog 9.3.25 */
    ?- listing(app/3).
    app([], A, B) :-
         A=B.
    app([A|B], [A|C], D) :-
         app(B, C, D).

    And works like an append, again taking the
    argument swap into account:

    ?- app([1],X,[2,3]).
    X = [1, 2, 3].

    Now the multi-argument indexing test, still
    taking the argument swap into account;

    /* ECLiPSe Prolog 7.1beta #13 */
    [eclipse 3]: app(X, [1], Y).

    X = []
    Y = [1]
    Yes (0.00s cpu, solution 1, maybe more) ? ;

    X = [1]
    Y = []
    Yes (0.00s cpu, solution 2)

    Versus:

    /* SWI-Prolog 9.3.25 */
    ?- app(X, [1], Y).
    X = [],
    Y = [1] ;
    X = [1],
    Y = [] ;
    false.

    Mild Shock schrieb:
    I am currently doing a re-evaluation of an old
    Prolog system, checking what features I could adopt.
    This is unlike the current trend where people have
    turned their focus on GUIs, like XPCE,

    or a are stuck in an endless loop of parser
    problems, like in Trealla. But I would nevertheless
    share my finding. Take this simple example of
    a list append:

    app([], X, X).
    app([X|Y], Z, [X|T]) :- app(Y, Z, T).

    ECLiPSe Prolog gives me, only one redo question
    in the top-level:

    /* ECLiPSe Prolog 7.1beta #13 */
    [eclipse 2]: app(X,Y,[1]).

    X = []
    Y = [1]
    Yes (0.00s cpu, solution 1, maybe more) ? ;

    X = [1]
    Y = []
    Yes (0.00s cpu, solution 2)

    In SWI-Prolog I find, two redo questions
    in the top.level:

    /* SWI-Prolog 9.3.25 */
    ?- app(X,Y,[1]).
    X = [],
    Y = [1] ;
    X = [1],
    Y = [] ;
    false.

    I know SWI-Prolog handles lists differently
    than other Prolog terms during indexing. Could
    this be the reason? Or maybe that the call is
    not “hot” enough, so it doesn’t get JIT-ed.

    ECLiPSe Prolog does it on the very first call,
    and I assume its due to a kind of index on
    the 3rd argument.






    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Mild Shock@janburse@fastmail.fm to comp.lang.prolog on Tue Jul 15 18:41:57 2025
    From Newsgroup: comp.lang.prolog

    Hi,

    Having 2544 issues is probably a bad sign.
    I find this many issues here:

    https://github.com/rocq-prover/rocq/issues

    Mostlikely 90% of the issues can be move to
    the new discussion feature of GitHub.

    LoL

    Bye

    P.S.: Same holds for Scryer Prolog with 406 issues.

    Mild Shock schrieb:
    Hi,

    Maybe AGI should take over proving.
    Just take the humans out of the loop
    of any programming, it leads to nowhere.

    Bye

    Julio Di Egidio schrieb:
    But we must thank MS for the nail in that coffin, too: they can't
    be satisfied with just a Lean broken by design, they must own the
    whole compartment: only poisoned meatballs for the public...

    -Julio

    Mild Shock schrieb:
    Corr.: Small typo in the number
    expansion itself, should read:

    10/81 = 0.(123456790) = 0.12345679(012345679)

    Mild Shock schrieb:
    Hi,

    Now somebody was so friendly to spear head
    a new Don Quixote attempt in fighting the
    windmills of compare/3. Interestingly my

    favorite counter example still goes through:

    ?- X = X-0-9-7-6-5-4-3-2-1, Y = Y-7-5-8-2-4-1,
        compare_with_stack(C, X, Y).
    X = X-0-9-7-6-5-4-3-2-1,
    Y = Y-7-5-8-2-4-1,
    C = (<).

    ?- H = H-9-7-6-5-4-3-2-1-0, Z = H-9-7-6-5-4-3-2-1, Y = Y-7-5-8-2-4-1,
        compare_with_stack(C, Z, Y).
    H = H-9-7-6-5-4-3-2-1-0,
    Z = H-9-7-6-5-4-3-2-1,
    Y = Y-7-5-8-2-4-1,
    C = (>).

    ?- H = H-9-7-6-5-4-3-2-1-0, Z = H-9-7-6-5-4-3-2-1, X =
    X-0-9-7-6-5-4-3-2-1,
        compare_with_stack(C, Z, X).
    H = H-9-7-6-5-4-3-2-1-0,
    Z = X, X = X-0-9-7-6-5-4-3-2-1,
    C = (=).

    I posted it here in March 2023:

    Careful with compare/3 and Brent algorithm
    https://swi-prolog.discourse.group/t/careful-with-compare-3-and-brent-algorithm/6413


    Its based that rational terms are indeed in
    some relation to rational numbers. The above
    terms are related to:

    10/81 = 0.(123456790) = 0.12345679(02345679)

    Bye

    Mild Shock schrieb:
    Hi,

    That false/0 and not fail/0 is now all over the place,
    I don't mean in person but for example here:

    ?- X=f(f(X), X), Y=f(Y, f(Y)), X = Y.
    false.

    Is a little didactical nightmare.

    Syntactic unification has mathematical axioms (1978),
    to fully formalize unifcation you would need to
    formalize both (=)/2 and (≠)/2 (sic!), otherwise you
    rely on some negation as failure concept.

    Keith L. Clark, Negation as Failure
    https://link.springer.com/chapter/10.1007/978-1-4684-3384-5_11

    You can realize a subset of a mixture of (=)/2
    and (≠)/2 in the form of a vanilla unify Prolog
    predicate using some of the meta programming
    facilities of Prolog, like var/1 and having some

    negation as failure reading:

    /* Vanilla Unify */
    unify(V, W) :- var(V), var(W), !, (V \== W -> V = W; true).
    unify(V, T) :- var(V), !, V = T.
    unify(S, W) :- var(W), !, W = S.
    unify(S, T) :- functor(S, F, N), functor(T, F, N),
          S =.. [F|L], T =.. [F|R], maplist(unify, L, R).

    I indeed get:

    ?- X=f(f(X), X), Y=f(Y, f(Y)), unify(X,Y).
    false.

    If the vanilla unify/2 already fails then unify
    with and without subject to occurs check, will also
    fail, and unify with and without ability to
    handle rational terms, will also fail:

    Bye

    Mild Shock schrieb:

    Interestingly, DCG is also affect. Here a
    DCG take of an append app/3, it has the 2nd
    and 3rd argument swapped:

    ?- [user].
    app([]) --> [].
    app([X|Y]) --> [X], app(Y).
    ^D

    Looks like an append, taking the argument swap
    into account, the A=B is redundant, could
    be optimized away:

    /* SWI-Prolog 9.3.25 */
    ?- listing(app/3).
    app([], A, B) :-
         A=B.
    app([A|B], [A|C], D) :-
         app(B, C, D).

    And works like an append, again taking the
    argument swap into account:

    ?- app([1],X,[2,3]).
    X = [1, 2, 3].

    Now the multi-argument indexing test, still
    taking the argument swap into account;

    /* ECLiPSe Prolog 7.1beta #13 */
    [eclipse 3]: app(X, [1], Y).

    X = []
    Y = [1]
    Yes (0.00s cpu, solution 1, maybe more) ? ;

    X = [1]
    Y = []
    Yes (0.00s cpu, solution 2)

    Versus:

    /* SWI-Prolog 9.3.25 */
    ?- app(X, [1], Y).
    X = [],
    Y = [1] ;
    X = [1],
    Y = [] ;
    false.

    Mild Shock schrieb:
    I am currently doing a re-evaluation of an old
    Prolog system, checking what features I could adopt.
    This is unlike the current trend where people have
    turned their focus on GUIs, like XPCE,

    or a are stuck in an endless loop of parser
    problems, like in Trealla. But I would nevertheless
    share my finding. Take this simple example of
    a list append:

    app([], X, X).
    app([X|Y], Z, [X|T]) :- app(Y, Z, T).

    ECLiPSe Prolog gives me, only one redo question
    in the top-level:

    /* ECLiPSe Prolog 7.1beta #13 */
    [eclipse 2]: app(X,Y,[1]).

    X = []
    Y = [1]
    Yes (0.00s cpu, solution 1, maybe more) ? ;

    X = [1]
    Y = []
    Yes (0.00s cpu, solution 2)

    In SWI-Prolog I find, two redo questions
    in the top.level:

    /* SWI-Prolog 9.3.25 */
    ?- app(X,Y,[1]).
    X = [],
    Y = [1] ;
    X = [1],
    Y = [] ;
    false.

    I know SWI-Prolog handles lists differently
    than other Prolog terms during indexing. Could
    this be the reason? Or maybe that the call is
    not “hot” enough, so it doesn’t get JIT-ed.

    ECLiPSe Prolog does it on the very first call,
    and I assume its due to a kind of index on
    the 3rd argument.







    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Mild Shock@janburse@fastmail.fm to comp.lang.prolog on Tue Jul 15 19:02:25 2025
    From Newsgroup: comp.lang.prolog

    Hi,

    1. Everybody’s a programmer now
    The barrier to entry dropped dramatically — you can
    become a "developer" with a few online tutorials
    and a GitHub account.

    2. Everybody’s an academic now
    Academia expanded, but standards often fell. In
    some places, it's publish or perish, so paper
    mills and fake research flourish.

    3. Signal Collapse ↔ Systemic Uncertainty
    Credentials lose meaning, No reliable markers of
    skill, Fragile systems built on shallow knowledge

    4. Signal Collapse ↔ Systemic Uncertainty
    Quantity overwhelms quality, Important truths get
    buried, Bad signals drown good ones

    Etc..

    Bye

    Mild Shock schrieb:
    Hi,

    Having 2544 issues is probably a bad sign.
    I find this many issues here:

    https://github.com/rocq-prover/rocq/issues

    Mostlikely 90% of the issues can be move to
    the new discussion feature of GitHub.

    LoL

    Bye

    P.S.: Same holds for Scryer Prolog with 406 issues.

    Mild Shock schrieb:
    Hi,

    Maybe AGI should take over proving.
    Just take the humans out of the loop
    of any programming, it leads to nowhere.

    Bye

    Julio Di Egidio schrieb:
    But we must thank MS for the nail in that coffin, too: they can't
    be satisfied with just a Lean broken by design, they must own the
    whole compartment: only poisoned meatballs for the public...
    ;
    -Julio

    Mild Shock schrieb:
    Corr.: Small typo in the number
    expansion itself, should read:

    10/81 = 0.(123456790) = 0.12345679(012345679)

    Mild Shock schrieb:
    Hi,

    Now somebody was so friendly to spear head
    a new Don Quixote attempt in fighting the
    windmills of compare/3. Interestingly my

    favorite counter example still goes through:

    ?- X = X-0-9-7-6-5-4-3-2-1, Y = Y-7-5-8-2-4-1,
        compare_with_stack(C, X, Y).
    X = X-0-9-7-6-5-4-3-2-1,
    Y = Y-7-5-8-2-4-1,
    C = (<).

    ?- H = H-9-7-6-5-4-3-2-1-0, Z = H-9-7-6-5-4-3-2-1, Y = Y-7-5-8-2-4-1,
        compare_with_stack(C, Z, Y).
    H = H-9-7-6-5-4-3-2-1-0,
    Z = H-9-7-6-5-4-3-2-1,
    Y = Y-7-5-8-2-4-1,
    C = (>).

    ?- H = H-9-7-6-5-4-3-2-1-0, Z = H-9-7-6-5-4-3-2-1, X =
    X-0-9-7-6-5-4-3-2-1,
        compare_with_stack(C, Z, X).
    H = H-9-7-6-5-4-3-2-1-0,
    Z = X, X = X-0-9-7-6-5-4-3-2-1,
    C = (=).

    I posted it here in March 2023:

    Careful with compare/3 and Brent algorithm
    https://swi-prolog.discourse.group/t/careful-with-compare-3-and-brent-algorithm/6413


    Its based that rational terms are indeed in
    some relation to rational numbers. The above
    terms are related to:

    10/81 = 0.(123456790) = 0.12345679(02345679)

    Bye

    Mild Shock schrieb:
    Hi,

    That false/0 and not fail/0 is now all over the place,
    I don't mean in person but for example here:

    ?- X=f(f(X), X), Y=f(Y, f(Y)), X = Y.
    false.

    Is a little didactical nightmare.

    Syntactic unification has mathematical axioms (1978),
    to fully formalize unifcation you would need to
    formalize both (=)/2 and (≠)/2 (sic!), otherwise you
    rely on some negation as failure concept.

    Keith L. Clark, Negation as Failure
    https://link.springer.com/chapter/10.1007/978-1-4684-3384-5_11

    You can realize a subset of a mixture of (=)/2
    and (≠)/2 in the form of a vanilla unify Prolog
    predicate using some of the meta programming
    facilities of Prolog, like var/1 and having some

    negation as failure reading:

    /* Vanilla Unify */
    unify(V, W) :- var(V), var(W), !, (V \== W -> V = W; true).
    unify(V, T) :- var(V), !, V = T.
    unify(S, W) :- var(W), !, W = S.
    unify(S, T) :- functor(S, F, N), functor(T, F, N),
          S =.. [F|L], T =.. [F|R], maplist(unify, L, R).

    I indeed get:

    ?- X=f(f(X), X), Y=f(Y, f(Y)), unify(X,Y).
    false.

    If the vanilla unify/2 already fails then unify
    with and without subject to occurs check, will also
    fail, and unify with and without ability to
    handle rational terms, will also fail:

    Bye

    Mild Shock schrieb:

    Interestingly, DCG is also affect. Here a
    DCG take of an append app/3, it has the 2nd
    and 3rd argument swapped:

    ?- [user].
    app([]) --> [].
    app([X|Y]) --> [X], app(Y).
    ^D

    Looks like an append, taking the argument swap
    into account, the A=B is redundant, could
    be optimized away:

    /* SWI-Prolog 9.3.25 */
    ?- listing(app/3).
    app([], A, B) :-
         A=B.
    app([A|B], [A|C], D) :-
         app(B, C, D).

    And works like an append, again taking the
    argument swap into account:

    ?- app([1],X,[2,3]).
    X = [1, 2, 3].

    Now the multi-argument indexing test, still
    taking the argument swap into account;

    /* ECLiPSe Prolog 7.1beta #13 */
    [eclipse 3]: app(X, [1], Y).

    X = []
    Y = [1]
    Yes (0.00s cpu, solution 1, maybe more) ? ;

    X = [1]
    Y = []
    Yes (0.00s cpu, solution 2)

    Versus:

    /* SWI-Prolog 9.3.25 */
    ?- app(X, [1], Y).
    X = [],
    Y = [1] ;
    X = [1],
    Y = [] ;
    false.

    Mild Shock schrieb:
    I am currently doing a re-evaluation of an old
    Prolog system, checking what features I could adopt.
    This is unlike the current trend where people have
    turned their focus on GUIs, like XPCE,

    or a are stuck in an endless loop of parser
    problems, like in Trealla. But I would nevertheless
    share my finding. Take this simple example of
    a list append:

    app([], X, X).
    app([X|Y], Z, [X|T]) :- app(Y, Z, T).

    ECLiPSe Prolog gives me, only one redo question
    in the top-level:

    /* ECLiPSe Prolog 7.1beta #13 */
    [eclipse 2]: app(X,Y,[1]).

    X = []
    Y = [1]
    Yes (0.00s cpu, solution 1, maybe more) ? ;

    X = [1]
    Y = []
    Yes (0.00s cpu, solution 2)

    In SWI-Prolog I find, two redo questions
    in the top.level:

    /* SWI-Prolog 9.3.25 */
    ?- app(X,Y,[1]).
    X = [],
    Y = [1] ;
    X = [1],
    Y = [] ;
    false.

    I know SWI-Prolog handles lists differently
    than other Prolog terms during indexing. Could
    this be the reason? Or maybe that the call is
    not “hot” enough, so it doesn’t get JIT-ed.

    ECLiPSe Prolog does it on the very first call,
    and I assume its due to a kind of index on
    the 3rd argument.








    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Mild Shock@janburse@fastmail.fm to comp.lang.prolog on Tue Jul 15 19:52:18 2025
    From Newsgroup: comp.lang.prolog

    Hi,

    A 2020 study analyzing 2,927 GitHub projects found
    that many repositories quickly become unmaintained.
    This implies that the majority of projects don’t
    sustain long-term active development.

    Another study reported 46% of repositories inactive
    for at least six months, and only 13% active in the
    last month, showing low ongoing engagement
    across most repos.

    Because millions of repos exist on GitHub, and
    large portions are abandoned, inactive, or minimal
    “toy” projects, the fraction of repositories that are
    well-maintained, collaborative, and used in
    production contexts is low—roughly estimated
    to be around 1–2%.

    The caravan moves forth, leaving behind the
    occasional turd perfectly captures GitHub. Rename
    GitHub, to TurdPit, and make Amber Heard their CEO.

    Bye

    Mild Shock schrieb:
    Hi,

    1. Everybody’s a programmer now
       The barrier to entry dropped dramatically — you can
       become a "developer" with a few online tutorials
       and a GitHub account.

    2. Everybody’s an academic now
       Academia expanded, but standards often fell. In
       some places, it's publish or perish, so paper
       mills and fake research flourish.

    3. Signal Collapse ↔ Systemic Uncertainty
       Credentials lose meaning, No reliable markers of
       skill, Fragile systems built on shallow knowledge

    4. Signal Collapse ↔ Systemic Uncertainty
       Quantity overwhelms quality, Important truths get
       buried, Bad signals drown good ones

    Etc..

    Bye

    Mild Shock schrieb:
    Hi,

    Having 2544 issues is probably a bad sign.
    I find this many issues here:

    https://github.com/rocq-prover/rocq/issues

    Mostlikely 90% of the issues can be move to
    the new discussion feature of GitHub.

    LoL

    Bye

    P.S.: Same holds for Scryer Prolog with 406 issues.

    Mild Shock schrieb:
    Hi,

    Maybe AGI should take over proving.
    Just take the humans out of the loop
    of any programming, it leads to nowhere.

    Bye

    Julio Di Egidio schrieb:
    But we must thank MS for the nail in that coffin, too: they can't
    be satisfied with just a Lean broken by design, they must own the
    whole compartment: only poisoned meatballs for the public...
    ;
    -Julio

    Mild Shock schrieb:
    Corr.: Small typo in the number
    expansion itself, should read:

    10/81 = 0.(123456790) = 0.12345679(012345679)

    Mild Shock schrieb:
    Hi,

    Now somebody was so friendly to spear head
    a new Don Quixote attempt in fighting the
    windmills of compare/3. Interestingly my

    favorite counter example still goes through:

    ?- X = X-0-9-7-6-5-4-3-2-1, Y = Y-7-5-8-2-4-1,
        compare_with_stack(C, X, Y).
    X = X-0-9-7-6-5-4-3-2-1,
    Y = Y-7-5-8-2-4-1,
    C = (<).

    ?- H = H-9-7-6-5-4-3-2-1-0, Z = H-9-7-6-5-4-3-2-1, Y = Y-7-5-8-2-4-1, >>>>>     compare_with_stack(C, Z, Y).
    H = H-9-7-6-5-4-3-2-1-0,
    Z = H-9-7-6-5-4-3-2-1,
    Y = Y-7-5-8-2-4-1,
    C = (>).

    ?- H = H-9-7-6-5-4-3-2-1-0, Z = H-9-7-6-5-4-3-2-1, X =
    X-0-9-7-6-5-4-3-2-1,
        compare_with_stack(C, Z, X).
    H = H-9-7-6-5-4-3-2-1-0,
    Z = X, X = X-0-9-7-6-5-4-3-2-1,
    C = (=).

    I posted it here in March 2023:

    Careful with compare/3 and Brent algorithm
    https://swi-prolog.discourse.group/t/careful-with-compare-3-and-brent-algorithm/6413


    Its based that rational terms are indeed in
    some relation to rational numbers. The above
    terms are related to:

    10/81 = 0.(123456790) = 0.12345679(02345679)

    Bye

    Mild Shock schrieb:
    Hi,

    That false/0 and not fail/0 is now all over the place,
    I don't mean in person but for example here:

    ?- X=f(f(X), X), Y=f(Y, f(Y)), X = Y.
    false.

    Is a little didactical nightmare.

    Syntactic unification has mathematical axioms (1978),
    to fully formalize unifcation you would need to
    formalize both (=)/2 and (≠)/2 (sic!), otherwise you
    rely on some negation as failure concept.

    Keith L. Clark, Negation as Failure
    https://link.springer.com/chapter/10.1007/978-1-4684-3384-5_11

    You can realize a subset of a mixture of (=)/2
    and (≠)/2 in the form of a vanilla unify Prolog
    predicate using some of the meta programming
    facilities of Prolog, like var/1 and having some

    negation as failure reading:

    /* Vanilla Unify */
    unify(V, W) :- var(V), var(W), !, (V \== W -> V = W; true).
    unify(V, T) :- var(V), !, V = T.
    unify(S, W) :- var(W), !, W = S.
    unify(S, T) :- functor(S, F, N), functor(T, F, N),
          S =.. [F|L], T =.. [F|R], maplist(unify, L, R).

    I indeed get:

    ?- X=f(f(X), X), Y=f(Y, f(Y)), unify(X,Y).
    false.

    If the vanilla unify/2 already fails then unify
    with and without subject to occurs check, will also
    fail, and unify with and without ability to
    handle rational terms, will also fail:

    Bye

    Mild Shock schrieb:

    Interestingly, DCG is also affect. Here a
    DCG take of an append app/3, it has the 2nd
    and 3rd argument swapped:

    ?- [user].
    app([]) --> [].
    app([X|Y]) --> [X], app(Y).
    ^D

    Looks like an append, taking the argument swap
    into account, the A=B is redundant, could
    be optimized away:

    /* SWI-Prolog 9.3.25 */
    ?- listing(app/3).
    app([], A, B) :-
         A=B.
    app([A|B], [A|C], D) :-
         app(B, C, D).

    And works like an append, again taking the
    argument swap into account:

    ?- app([1],X,[2,3]).
    X = [1, 2, 3].

    Now the multi-argument indexing test, still
    taking the argument swap into account;

    /* ECLiPSe Prolog 7.1beta #13 */
    [eclipse 3]: app(X, [1], Y).

    X = []
    Y = [1]
    Yes (0.00s cpu, solution 1, maybe more) ? ;

    X = [1]
    Y = []
    Yes (0.00s cpu, solution 2)

    Versus:

    /* SWI-Prolog 9.3.25 */
    ?- app(X, [1], Y).
    X = [],
    Y = [1] ;
    X = [1],
    Y = [] ;
    false.

    Mild Shock schrieb:
    I am currently doing a re-evaluation of an old
    Prolog system, checking what features I could adopt.
    This is unlike the current trend where people have
    turned their focus on GUIs, like XPCE,

    or a are stuck in an endless loop of parser
    problems, like in Trealla. But I would nevertheless
    share my finding. Take this simple example of
    a list append:

    app([], X, X).
    app([X|Y], Z, [X|T]) :- app(Y, Z, T).

    ECLiPSe Prolog gives me, only one redo question
    in the top-level:

    /* ECLiPSe Prolog 7.1beta #13 */
    [eclipse 2]: app(X,Y,[1]).

    X = []
    Y = [1]
    Yes (0.00s cpu, solution 1, maybe more) ? ;

    X = [1]
    Y = []
    Yes (0.00s cpu, solution 2)

    In SWI-Prolog I find, two redo questions
    in the top.level:

    /* SWI-Prolog 9.3.25 */
    ?- app(X,Y,[1]).
    X = [],
    Y = [1] ;
    X = [1],
    Y = [] ;
    false.

    I know SWI-Prolog handles lists differently
    than other Prolog terms during indexing. Could
    this be the reason? Or maybe that the call is
    not “hot” enough, so it doesn’t get JIT-ed.

    ECLiPSe Prolog does it on the very first call,
    and I assume its due to a kind of index on
    the 3rd argument.









    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Mild Shock@janburse@fastmail.fm to comp.lang.prolog on Wed Jul 16 18:59:13 2025
    From Newsgroup: comp.lang.prolog


    I checked that your examples are not counter
    examples for my compare_with_stack/3.

    What makes you think the values I show, X, Y
    and Z, are possible in a total linear ordering?
    The values also break predsort/3, you can easily
    verify that sort([x,y,z]) =\= sort([y,x,z]):

    value(x, X) :- X = X-0-9-7-6-5-4-3-2-1.
    value(y, Y) :- Y = Y-7-5-8-2-4-1.
    value(z, Z) :- H = H-9-7-6-5-4-3-2-1-0, Z = H-9-7-6-5-4-3-2-1.

    values(L, R) :- maplist(value, L, R).

    ?- values([x,y,z], A), predsort(compare_with_stack, A, B),
    values([y,x,z], C), predsort(compare_with_stack, C, D),
    B == D.
    false.

    But expectation would be sort([x,y,z]) ==
    sort([y,x,z]) since sort/2 should be immune
    to permutation. If this isn’t enough proof that
    there is something fishy in compare_with_stack/3 ,

    well then I don’t know, maybe the earth is indeed flat?

    Mild Shock schrieb:
    Hi,

    Maybe AGI should take over proving.
    Just take the humans out of the loop
    of any programming, it leads to nowhere.

    Bye

    Julio Di Egidio schrieb:
    But we must thank MS for the nail in that coffin, too: they can't
    be satisfied with just a Lean broken by design, they must own the
    whole compartment: only poisoned meatballs for the public...

    -Julio

    Mild Shock schrieb:
    Corr.: Small typo in the number
    expansion itself, should read:

    10/81 = 0.(123456790) = 0.12345679(012345679)

    Mild Shock schrieb:
    Hi,

    Now somebody was so friendly to spear head
    a new Don Quixote attempt in fighting the
    windmills of compare/3. Interestingly my

    favorite counter example still goes through:

    ?- X = X-0-9-7-6-5-4-3-2-1, Y = Y-7-5-8-2-4-1,
        compare_with_stack(C, X, Y).
    X = X-0-9-7-6-5-4-3-2-1,
    Y = Y-7-5-8-2-4-1,
    C = (<).

    ?- H = H-9-7-6-5-4-3-2-1-0, Z = H-9-7-6-5-4-3-2-1, Y = Y-7-5-8-2-4-1,
        compare_with_stack(C, Z, Y).
    H = H-9-7-6-5-4-3-2-1-0,
    Z = H-9-7-6-5-4-3-2-1,
    Y = Y-7-5-8-2-4-1,
    C = (>).

    ?- H = H-9-7-6-5-4-3-2-1-0, Z = H-9-7-6-5-4-3-2-1, X =
    X-0-9-7-6-5-4-3-2-1,
        compare_with_stack(C, Z, X).
    H = H-9-7-6-5-4-3-2-1-0,
    Z = X, X = X-0-9-7-6-5-4-3-2-1,
    C = (=).

    I posted it here in March 2023:

    Careful with compare/3 and Brent algorithm
    https://swi-prolog.discourse.group/t/careful-with-compare-3-and-brent-algorithm/6413


    Its based that rational terms are indeed in
    some relation to rational numbers. The above
    terms are related to:

    10/81 = 0.(123456790) = 0.12345679(02345679)

    Bye

    Mild Shock schrieb:
    Hi,

    That false/0 and not fail/0 is now all over the place,
    I don't mean in person but for example here:

    ?- X=f(f(X), X), Y=f(Y, f(Y)), X = Y.
    false.

    Is a little didactical nightmare.

    Syntactic unification has mathematical axioms (1978),
    to fully formalize unifcation you would need to
    formalize both (=)/2 and (≠)/2 (sic!), otherwise you
    rely on some negation as failure concept.

    Keith L. Clark, Negation as Failure
    https://link.springer.com/chapter/10.1007/978-1-4684-3384-5_11

    You can realize a subset of a mixture of (=)/2
    and (≠)/2 in the form of a vanilla unify Prolog
    predicate using some of the meta programming
    facilities of Prolog, like var/1 and having some

    negation as failure reading:

    /* Vanilla Unify */
    unify(V, W) :- var(V), var(W), !, (V \== W -> V = W; true).
    unify(V, T) :- var(V), !, V = T.
    unify(S, W) :- var(W), !, W = S.
    unify(S, T) :- functor(S, F, N), functor(T, F, N),
          S =.. [F|L], T =.. [F|R], maplist(unify, L, R).

    I indeed get:

    ?- X=f(f(X), X), Y=f(Y, f(Y)), unify(X,Y).
    false.

    If the vanilla unify/2 already fails then unify
    with and without subject to occurs check, will also
    fail, and unify with and without ability to
    handle rational terms, will also fail:

    Bye

    Mild Shock schrieb:

    Interestingly, DCG is also affect. Here a
    DCG take of an append app/3, it has the 2nd
    and 3rd argument swapped:

    ?- [user].
    app([]) --> [].
    app([X|Y]) --> [X], app(Y).
    ^D

    Looks like an append, taking the argument swap
    into account, the A=B is redundant, could
    be optimized away:

    /* SWI-Prolog 9.3.25 */
    ?- listing(app/3).
    app([], A, B) :-
         A=B.
    app([A|B], [A|C], D) :-
         app(B, C, D).

    And works like an append, again taking the
    argument swap into account:

    ?- app([1],X,[2,3]).
    X = [1, 2, 3].

    Now the multi-argument indexing test, still
    taking the argument swap into account;

    /* ECLiPSe Prolog 7.1beta #13 */
    [eclipse 3]: app(X, [1], Y).

    X = []
    Y = [1]
    Yes (0.00s cpu, solution 1, maybe more) ? ;

    X = [1]
    Y = []
    Yes (0.00s cpu, solution 2)

    Versus:

    /* SWI-Prolog 9.3.25 */
    ?- app(X, [1], Y).
    X = [],
    Y = [1] ;
    X = [1],
    Y = [] ;
    false.

    Mild Shock schrieb:
    I am currently doing a re-evaluation of an old
    Prolog system, checking what features I could adopt.
    This is unlike the current trend where people have
    turned their focus on GUIs, like XPCE,

    or a are stuck in an endless loop of parser
    problems, like in Trealla. But I would nevertheless
    share my finding. Take this simple example of
    a list append:

    app([], X, X).
    app([X|Y], Z, [X|T]) :- app(Y, Z, T).

    ECLiPSe Prolog gives me, only one redo question
    in the top-level:

    /* ECLiPSe Prolog 7.1beta #13 */
    [eclipse 2]: app(X,Y,[1]).

    X = []
    Y = [1]
    Yes (0.00s cpu, solution 1, maybe more) ? ;

    X = [1]
    Y = []
    Yes (0.00s cpu, solution 2)

    In SWI-Prolog I find, two redo questions
    in the top.level:

    /* SWI-Prolog 9.3.25 */
    ?- app(X,Y,[1]).
    X = [],
    Y = [1] ;
    X = [1],
    Y = [] ;
    false.

    I know SWI-Prolog handles lists differently
    than other Prolog terms during indexing. Could
    this be the reason? Or maybe that the call is
    not “hot” enough, so it doesn’t get JIT-ed.

    ECLiPSe Prolog does it on the very first call,
    and I assume its due to a kind of index on
    the 3rd argument.







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

    Hi,

    The same example values also create fishy 🐟
    sorting using native sorting in Scryer Prolog:

    /* Scryer Prolog 0.9.4-417 */
    ?- values([z,x,y], A), sort(A, B),
    values([x,y,z], C), sort(C, D), B == D.
    false. /* fishy 🐟 */

    Or using native sorting in SWI-Prolog:

    /* SWI-Prolog 9.3.25 */
    ?- values([z,x,y], A), sort(A, B),
    values([x,y,z], C), sort(C, D), B == D.
    false. /* fishy 🐟 */

    Bye

    Mild Shock schrieb:

    I checked that your examples are not counter
    examples for my compare_with_stack/3.

    What makes you think the values I show, X, Y
    and Z, are possible in a total linear ordering?
    The values also break predsort/3, you can easily
    verify that sort([x,y,z]) =\= sort([y,x,z]):

    value(x, X) :- X = X-0-9-7-6-5-4-3-2-1.
    value(y, Y) :- Y = Y-7-5-8-2-4-1.
    value(z, Z) :- H = H-9-7-6-5-4-3-2-1-0, Z = H-9-7-6-5-4-3-2-1.

    values(L, R) :- maplist(value, L, R).

    ?- values([x,y,z], A), predsort(compare_with_stack, A, B),
       values([y,x,z], C), predsort(compare_with_stack, C, D),
       B == D.
    false.

    But expectation would be sort([x,y,z]) ==
    sort([y,x,z]) since sort/2 should be immune
    to permutation. If this isn’t enough proof that
    there is something fishy in compare_with_stack/3 ,

    well then I don’t know, maybe the earth is indeed flat?

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Mild Shock@janburse@fastmail.fm to comp.lang.prolog on Thu Jul 17 10:57:45 2025
    From Newsgroup: comp.lang.prolog

    You can answer such questions
    to the negative via Fuzzy Testing:

    However such relation induced above is transitive ?

    Typical counter example, showing
    the native compare/3 is not transitive:

    /* SWI-Prolog 9.3.25 */
    ?- repeat, fuzzy(X), fuzzy(Y), compare(<,X,Y), fuzzy(Z),
    compare(<,Y,Z), compare(>,X,Z).
    X = f(f(f(X, 1), 1), 1),
    Y = f(f(Y, 1), 0),
    Z = f(f(f(Z, 1), 0), 1) .
    Etc..

    Works also for Trealla Prolog, so I
    assume compare_expensive/3 also fails:

    /* Trealla Prolog 2.78.5 */
    ?- repeat, fuzzy(X), fuzzy(Y), compare(<,X,Y), fuzzy(Z),
    compare(<,Y,Z), compare(>,X,Z).
    X = f(f(f(...,0),0),1), Y = f(f(...,1),0), Z = f(f(...,0),1)
    ; ... .
    Etc..

    In essence, my nasty fuzzer uses
    variants of Matt Carlsons example.

    P.S.: From a logic viewpoint you could view
    Fuzzy Testing as a form of randomized model
    checking. A little famous Fuzzy Tester was Sandsifter:

    "The tool discovered undocumented instructions
    in all major processors, shared bugs in nearly
    every major assembler and disassembler, flaws in
    enterprise hypervisors, and critical x86 hardware" https://github.com/xoreaxeaxeax/sandsifter/blob/master/references/domas_breaking_the_x86_isa_wp.pdf

    So we are essentially all using Trojan Horses 🐎 daily?

    Mild Shock schrieb:
    Hi,

    The same example values also create fishy 🐟
    sorting using native sorting in Scryer Prolog:

    /* Scryer Prolog 0.9.4-417 */
    ?- values([z,x,y], A), sort(A, B),
       values([x,y,z], C), sort(C, D), B == D.
       false. /* fishy 🐟 */

    Or using native sorting in SWI-Prolog:

    /* SWI-Prolog 9.3.25 */
    ?- values([z,x,y], A), sort(A, B),
       values([x,y,z], C), sort(C, D), B == D.
    false. /* fishy 🐟 */

    Bye

    Mild Shock schrieb:

    I checked that your examples are not counter
    examples for my compare_with_stack/3.

    What makes you think the values I show, X, Y
    and Z, are possible in a total linear ordering?
    The values also break predsort/3, you can easily
    verify that sort([x,y,z]) =\= sort([y,x,z]):

    value(x, X) :- X = X-0-9-7-6-5-4-3-2-1.
    value(y, Y) :- Y = Y-7-5-8-2-4-1.
    value(z, Z) :- H = H-9-7-6-5-4-3-2-1-0, Z = H-9-7-6-5-4-3-2-1.

    values(L, R) :- maplist(value, L, R).

    ?- values([x,y,z], A), predsort(compare_with_stack, A, B),
        values([y,x,z], C), predsort(compare_with_stack, C, D),
        B == D.
    false.

    But expectation would be sort([x,y,z]) ==
    sort([y,x,z]) since sort/2 should be immune
    to permutation. If this isn’t enough proof that
    there is something fishy in compare_with_stack/3 ,

    well then I don’t know, maybe the earth is indeed flat?


    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Mild Shock@janburse@fastmail.fm to comp.lang.prolog on Sun Jul 20 14:36:44 2025
    From Newsgroup: comp.lang.prolog

    Hi,

    Create a ChatGPT for cyclic terms? It seems
    that the SWI-Prolog discourse contains a lot
    of recent exploration of about cyclic terms.
    Yet humans don’t remember them,

    or are too lazy to recall them, look them
    up again. Maybe to offload some of the cognitive
    load and have a easier way forward, one might
    use GPT builder and

    create a cyclic term assistant. One could
    then ask the artificial intelligece (AI) for
    the following things:

    - Automated Testing:
    please perform some monkey testing
    on my news compare/3 idea

    - Automated Proving:
    please suggest a proof for my newest
    lemma about compare/3

    - Code Refactor:
    please refactor my code, I would like to
    use (==)/2 instead of same_time/2

    - Auto Comment:
    please auto comment my code, I was too
    lazy to write comments

    - What else?
    ChatGPT itself gave me a list when I ask
    what will be between now and AGI. Could
    look it up, as a few interesting items as well
    mainly targeting automated summarizing ideas.

    Is SWI-Prolog discourse part of the SWI-Prolog
    assistant building process. Its less a static
    resource, has ongoing discussions. Needs periodic
    retraining of the AI.

    Also the above vision includes some scenarios
    where the Assistant would be better integrated
    into an IDE, but these Assistants have usually
    more expensive price plans.

    Will this IDE be XPCE, who knows?

    Mild Shock schrieb:

    I checked that your examples are not counter
    examples for my compare_with_stack/3.

    What makes you think the values I show, X, Y
    and Z, are possible in a total linear ordering?
    The values also break predsort/3, you can easily
    verify that sort([x,y,z]) =\= sort([y,x,z]):

    value(x, X) :- X = X-0-9-7-6-5-4-3-2-1.
    value(y, Y) :- Y = Y-7-5-8-2-4-1.
    value(z, Z) :- H = H-9-7-6-5-4-3-2-1-0, Z = H-9-7-6-5-4-3-2-1.

    values(L, R) :- maplist(value, L, R).

    ?- values([x,y,z], A), predsort(compare_with_stack, A, B),
       values([y,x,z], C), predsort(compare_with_stack, C, D),
       B == D.
    false.

    But expectation would be sort([x,y,z]) ==
    sort([y,x,z]) since sort/2 should be immune
    to permutation. If this isn’t enough proof that
    there is something fishy in compare_with_stack/3 ,

    well then I don’t know, maybe the earth is indeed flat?

    Mild Shock schrieb:
    Hi,

    Maybe AGI should take over proving.
    Just take the humans out of the loop
    of any programming, it leads to nowhere.

    Bye

    Julio Di Egidio schrieb:
    But we must thank MS for the nail in that coffin, too: they can't
    be satisfied with just a Lean broken by design, they must own the
    whole compartment: only poisoned meatballs for the public...
    ;
    -Julio

    Mild Shock schrieb:
    Corr.: Small typo in the number
    expansion itself, should read:

    10/81 = 0.(123456790) = 0.12345679(012345679)

    Mild Shock schrieb:
    Hi,

    Now somebody was so friendly to spear head
    a new Don Quixote attempt in fighting the
    windmills of compare/3. Interestingly my

    favorite counter example still goes through:

    ?- X = X-0-9-7-6-5-4-3-2-1, Y = Y-7-5-8-2-4-1,
        compare_with_stack(C, X, Y).
    X = X-0-9-7-6-5-4-3-2-1,
    Y = Y-7-5-8-2-4-1,
    C = (<).

    ?- H = H-9-7-6-5-4-3-2-1-0, Z = H-9-7-6-5-4-3-2-1, Y = Y-7-5-8-2-4-1,
        compare_with_stack(C, Z, Y).
    H = H-9-7-6-5-4-3-2-1-0,
    Z = H-9-7-6-5-4-3-2-1,
    Y = Y-7-5-8-2-4-1,
    C = (>).

    ?- H = H-9-7-6-5-4-3-2-1-0, Z = H-9-7-6-5-4-3-2-1, X =
    X-0-9-7-6-5-4-3-2-1,
        compare_with_stack(C, Z, X).
    H = H-9-7-6-5-4-3-2-1-0,
    Z = X, X = X-0-9-7-6-5-4-3-2-1,
    C = (=).

    I posted it here in March 2023:

    Careful with compare/3 and Brent algorithm
    https://swi-prolog.discourse.group/t/careful-with-compare-3-and-brent-algorithm/6413


    Its based that rational terms are indeed in
    some relation to rational numbers. The above
    terms are related to:

    10/81 = 0.(123456790) = 0.12345679(02345679)

    Bye

    Mild Shock schrieb:
    Hi,

    That false/0 and not fail/0 is now all over the place,
    I don't mean in person but for example here:

    ?- X=f(f(X), X), Y=f(Y, f(Y)), X = Y.
    false.

    Is a little didactical nightmare.

    Syntactic unification has mathematical axioms (1978),
    to fully formalize unifcation you would need to
    formalize both (=)/2 and (≠)/2 (sic!), otherwise you
    rely on some negation as failure concept.

    Keith L. Clark, Negation as Failure
    https://link.springer.com/chapter/10.1007/978-1-4684-3384-5_11

    You can realize a subset of a mixture of (=)/2
    and (≠)/2 in the form of a vanilla unify Prolog
    predicate using some of the meta programming
    facilities of Prolog, like var/1 and having some

    negation as failure reading:

    /* Vanilla Unify */
    unify(V, W) :- var(V), var(W), !, (V \== W -> V = W; true).
    unify(V, T) :- var(V), !, V = T.
    unify(S, W) :- var(W), !, W = S.
    unify(S, T) :- functor(S, F, N), functor(T, F, N),
          S =.. [F|L], T =.. [F|R], maplist(unify, L, R).

    I indeed get:

    ?- X=f(f(X), X), Y=f(Y, f(Y)), unify(X,Y).
    false.

    If the vanilla unify/2 already fails then unify
    with and without subject to occurs check, will also
    fail, and unify with and without ability to
    handle rational terms, will also fail:

    Bye

    Mild Shock schrieb:

    Interestingly, DCG is also affect. Here a
    DCG take of an append app/3, it has the 2nd
    and 3rd argument swapped:

    ?- [user].
    app([]) --> [].
    app([X|Y]) --> [X], app(Y).
    ^D

    Looks like an append, taking the argument swap
    into account, the A=B is redundant, could
    be optimized away:

    /* SWI-Prolog 9.3.25 */
    ?- listing(app/3).
    app([], A, B) :-
         A=B.
    app([A|B], [A|C], D) :-
         app(B, C, D).

    And works like an append, again taking the
    argument swap into account:

    ?- app([1],X,[2,3]).
    X = [1, 2, 3].

    Now the multi-argument indexing test, still
    taking the argument swap into account;

    /* ECLiPSe Prolog 7.1beta #13 */
    [eclipse 3]: app(X, [1], Y).

    X = []
    Y = [1]
    Yes (0.00s cpu, solution 1, maybe more) ? ;

    X = [1]
    Y = []
    Yes (0.00s cpu, solution 2)

    Versus:

    /* SWI-Prolog 9.3.25 */
    ?- app(X, [1], Y).
    X = [],
    Y = [1] ;
    X = [1],
    Y = [] ;
    false.

    Mild Shock schrieb:
    I am currently doing a re-evaluation of an old
    Prolog system, checking what features I could adopt.
    This is unlike the current trend where people have
    turned their focus on GUIs, like XPCE,

    or a are stuck in an endless loop of parser
    problems, like in Trealla. But I would nevertheless
    share my finding. Take this simple example of
    a list append:

    app([], X, X).
    app([X|Y], Z, [X|T]) :- app(Y, Z, T).

    ECLiPSe Prolog gives me, only one redo question
    in the top-level:

    /* ECLiPSe Prolog 7.1beta #13 */
    [eclipse 2]: app(X,Y,[1]).

    X = []
    Y = [1]
    Yes (0.00s cpu, solution 1, maybe more) ? ;

    X = [1]
    Y = []
    Yes (0.00s cpu, solution 2)

    In SWI-Prolog I find, two redo questions
    in the top.level:

    /* SWI-Prolog 9.3.25 */
    ?- app(X,Y,[1]).
    X = [],
    Y = [1] ;
    X = [1],
    Y = [] ;
    false.

    I know SWI-Prolog handles lists differently
    than other Prolog terms during indexing. Could
    this be the reason? Or maybe that the call is
    not “hot” enough, so it doesn’t get JIT-ed.

    ECLiPSe Prolog does it on the very first call,
    and I assume its due to a kind of index on
    the 3rd argument.








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

    Hi,

    What you are adressing here, in purely
    symbolic form, without some helpful natural
    language rephrasing:

    Let (H, <) be the standard total oder an the
    Prolog finite terms. Let R be the set of rational
    term. H c R. Then there is total order
    extention (R, <') of (H, <).

    Is the problem of a compare/3 for rational trees,
    that is a extension of the compare/3 for finite aka
    acyclic terms with the submodel property. This is
    quite possible, for example representation

    based compare/3 that uses a collation key:

    S @<' T :<=> rep(S) @< rep(T)

    It has trivially acyclic comparison as a submodel,
    when rep(S) = S for acyclic terms S. The inverse
    rep^-1 itself is the homomorphism, its even an
    embedding, since identity would be injective.

    You might even forget about the plot, and endlessly
    go down the rabbit hole of mathematics, and write a
    100 pages paper, and prove Fermat’s Last Theorem
    in passing again.

    I can only assume mathematics currently hates
    computer science because of AI.

    Bye

    Mild Shock schrieb:
    Hi,

    Create a ChatGPT for cyclic terms? It seems
    that the SWI-Prolog discourse contains a lot
    of recent exploration of about cyclic terms.
    Yet humans don’t remember them,

    or are too lazy to recall them, look them
    up again. Maybe to offload some of the cognitive
    load and have a easier way forward, one might
    use GPT builder and

    create a cyclic term assistant. One could
    then ask the artificial intelligece (AI) for
    the following things:

    - Automated Testing:
      please perform some monkey testing
      on my news compare/3 idea

    - Automated Proving:
      please suggest a proof for my newest
      lemma about compare/3

    - Code Refactor:
      please refactor my code, I would like to
      use (==)/2 instead of same_time/2

    - Auto Comment:
      please auto comment my code, I was too
      lazy to write comments

    - What else?
      ChatGPT itself gave me a list when I ask
      what will be between now and AGI. Could
      look it up, as a few interesting items as well
      mainly targeting automated summarizing ideas.

    Is SWI-Prolog discourse part of the SWI-Prolog
    assistant building process. Its less a static
    resource, has ongoing discussions. Needs periodic
    retraining of the AI.

    Also the above vision includes some scenarios
    where the Assistant would be better integrated
    into an IDE, but these Assistants have usually
    more expensive price plans.

    Will this IDE be XPCE, who knows?


    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Mild Shock@janburse@fastmail.fm to comp.lang.prolog on Tue Nov 25 22:55:40 2025
    From Newsgroup: comp.lang.prolog

    Hi,

    I don't know, but 100x times slower than
    SWI-Prolog doesn't sound good for Scryer Prolog.
    And the 10x times slower than SWI-Prolog

    are also not nice for Trealla Prolog. But I
    guess Trealla uses C code programming that
    has passed the time of test. What is Scryer

    using? Well they do not use something that
    is far away from the Strudel Coding Style for
    Music, namely I find things like:

    let arity = self.code[current_pred_start..current_pred_end]
    .iter()
    .flat_map(Instruction::registers)
    .flat_map(|r| match r {
    RegType::Temp(t) => Some(t),
    _ => None,
    })
    .max()
    .unwrap_or(0);
    https://github.com/mthom/scryer-prolog/issues/3175

    These things usually don't perform well. Even
    if they process tuple oriented and not
    set oriented, still the programming style

    induces a lot of overhead, unless the compiler
    does agressively massage the code. Possibly
    only Haskell can do, since its longer in the

    bussiness. Not sure about Rust. Basically an iter()
    is a constructor and an arrow function is a constructor,
    and they create objects! Also the argument threading

    can be less efficient than a code block with
    registers and a traditional loop. A flat
    map is even a special kind of a horror among

    pipeline elements, since it usually needs a
    little state. Maybe using the novel C+20 Pipes
    would help. They are quite charming, even passing

    sentinells around. LoL

    Bye

    Mild Shock schrieb:
    Hi,

    The same example values also create fishy 🐟
    sorting using native sorting in Scryer Prolog:

    /* Scryer Prolog 0.9.4-417 */
    ?- values([z,x,y], A), sort(A, B),
       values([x,y,z], C), sort(C, D), B == D.
       false. /* fishy 🐟 */

    Or using native sorting in SWI-Prolog:

    /* SWI-Prolog 9.3.25 */
    ?- values([z,x,y], A), sort(A, B),
       values([x,y,z], C), sort(C, D), B == D.
    false. /* fishy 🐟 */

    Bye

    Mild Shock schrieb:

    I checked that your examples are not counter
    examples for my compare_with_stack/3.

    What makes you think the values I show, X, Y
    and Z, are possible in a total linear ordering?
    The values also break predsort/3, you can easily
    verify that sort([x,y,z]) =\= sort([y,x,z]):

    value(x, X) :- X = X-0-9-7-6-5-4-3-2-1.
    value(y, Y) :- Y = Y-7-5-8-2-4-1.
    value(z, Z) :- H = H-9-7-6-5-4-3-2-1-0, Z = H-9-7-6-5-4-3-2-1.

    values(L, R) :- maplist(value, L, R).

    ?- values([x,y,z], A), predsort(compare_with_stack, A, B),
        values([y,x,z], C), predsort(compare_with_stack, C, D),
        B == D.
    false.

    But expectation would be sort([x,y,z]) ==
    sort([y,x,z]) since sort/2 should be immune
    to permutation. If this isn’t enough proof that
    there is something fishy in compare_with_stack/3 ,

    well then I don’t know, maybe the earth is indeed flat?


    --- Synchronet 3.21a-Linux NewsLink 1.2