• =?UTF-8?Q?Dushnik=e2=80=93Miller_theorem_[1940]_=28Was:_VIP0909:_Vi?==?UTF-8?Q?beCore_Improvement_Proposal_[term=5fsingletons]=29?=

    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 Mercio’s
    Algorithm where rep(A) = A’. We can also arrange
    that it leads to natural orders that are

    conservative, using the Dushnik–
    Miller theorem:

    Dushnik–Miller 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
    don’t 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),
       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: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 Mercio’s
    Algorithm where rep(A) = A’. We can also arrange
    that it leads to natural orders that are

    conservative, using the Dushnik–
    Miller theorem:

    Dushnik–Miller 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
    don’t 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),
        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: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) :-
        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 Mercio’s
    Algorithm where rep(A) = A’. We can also arrange
    that it leads to natural orders that are

    conservative, using the Dushnik–
    Miller theorem:

    Dushnik–Miller 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
    don’t 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),
        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