• Ulrich Neumerkel is like Ozzy Osbourne

    From Mild Shock@21:1/5 to All on Thu Dec 5 11:26:20 2024
    Hi,

    Ulrich Neumerkel is like Ozzy Osbourne.
    He is making me paranoid. Especially this
    F.U.D. here stole one week of my life.

    Precise Garbage Collection in Prolog https://www.swi-prolog.org/download/publications/lifegc.pdf

    The test cases make no sense at all!
    Take this test case run1, similar to run2
    and run3:

    run1 :- f(_).
    f([f|X]) :- f(X).

    You will never find this in real world.
    Perpetual processes usually have a different
    pattern of loop state transition.

    Also its virtually impossible to garbage collect
    via minor incremental garbage collection. We
    might find a chain X=[f,..,f,Y] and collect

    it. But Xn is then colored as old. And instantiation
    of an old variable gets on the changed list, and
    so a new chain Y=[f,..,f,Z] will not be reclaimed,

    so that the beast can be only reclaimed via
    major garbage collection.

    Bye

    P.S.: Maybe there is a chance to solve it
    nevertheless via minor garbage collection, but
    its very difficult. I had something in

    formerly Jekejeke Prolog via reference counting.
    But not sure how to bring it to a Prolog
    system without reference counting.

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mild Shock@21:1/5 to Mild Shock on Thu Dec 5 11:33:31 2024
    Hi,

    This test case is also extremly cringe.
    In our Prolog system it conflicts with another
    optimization, that is in place to reduce the

    length of instantiation chains.

    run4 :- run(_).
    run(X) :- f(X).
    run(X) :- X == [].

    Our Prolog system doesn't create a variable
    at all for the first clause of run. It speculates
    that return value variables are passed around and

    thus resulting in no extra instantiation chains.
    So it passes the anonymous variable from run4
    to the call of f/1. But since the anonymous variable

    is from the run(_) call site, and since there is
    a choice point. The anonymous variable is always
    reachable never carbage collected, similarly chains

    _=[f,..,f|T] will never get garbage collected.
    In as far the test case fails after a while with
    memory overflow.

    Bye

    Mild Shock schrieb:
    Hi,

    Ulrich Neumerkel is like Ozzy Osbourne.
    He is making me paranoid. Especially this
    F.U.D. here stole one week of my life.

    Precise Garbage Collection in Prolog https://www.swi-prolog.org/download/publications/lifegc.pdf

    The test cases make no sense at all!
    Take this test case run1, similar to run2
    and run3:

    run1 :- f(_).
    f([f|X]) :- f(X).

    You will never find this in real world.
    Perpetual processes usually have a different
    pattern of loop state transition.

    Also its virtually impossible to garbage collect
    via minor incremental garbage collection. We
    might find a chain X=[f,..,f,Y] and collect

    it. But Xn is then colored as old. And instantiation
    of an old variable gets on the changed list, and
    so a new chain Y=[f,..,f,Z] will not be reclaimed,

    so that the beast can be only reclaimed via
    major garbage collection.

    Bye

    P.S.: Maybe there is a chance to solve it
    nevertheless via minor garbage collection, but
    its very difficult. I had something in

    formerly Jekejeke Prolog via reference counting.
    But not sure how to bring it to a Prolog
    system without reference counting.




    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mild Shock@21:1/5 to Mild Shock on Thu Dec 5 11:41:41 2024
    Hi,

    A further test case with choice points is this test case:

    run5(Z) :- p(_,_,Z).
    p(X,Y,Z) :- (Z > 0-> f(X), g(Y), dummy ; g(Y), f(X), dummy).
    g([g|X]) :- g(X).
    dummy.

    But the choice points go away, if Z > 0 the then (->)/2 will
    cut away any choice point. And if not Z > 0 the usual
    optimization is anyway to have no choice point.

    So we are back to the problem of minor garbage collection.
    If we attack the problems with major garbage collection,
    we can run all examples indefinitely. We only need to

    find a high enough major garbage collection frequency.
    Our usual setting is Period: 60, Dirty: 60. With changing
    the setting to Period: 15, Dirty: 15 we can run the

    viable test cases for straight 5 minutes long:

    ?- suite.
    % Zeit 300966 ms, GC 51595 ms, Lips 2026565, Uhr 04.12.2024 12:01
    % Zeit 300622 ms, GC 59049 ms, Lips 1929996, Uhr 04.12.2024 12:06
    % Zeit 301023 ms, GC 62909 ms, Lips 1911479, Uhr 04.12.2024 12:11
    % Zeit 300192 ms, GC 58244 ms, Lips 1925432, Uhr 04.12.2024 12:16
    % Zeit 300065 ms, GC 52253 ms, Lips 1944909, Uhr 04.12.2024 12:21
    true.

    The test code was:

    suite :-
    time(sys_trap(time_out(run1, 300000), _, true)),
    time(sys_trap(time_out(run2, 300000), _, true)),
    time(sys_trap(time_out(run3, 300000), _, true)),
    time(sys_trap(time_out(run5(0), 300000), _, true)),
    time(sys_trap(time_out(run5(1), 300000), _, true)).

    Bye

    Mild Shock schrieb:
    Hi,

    This test case is also extremly cringe.
    In our Prolog system it conflicts with another
    optimization, that is in place to reduce the

    length of instantiation chains.

    run4 :- run(_).
    run(X) :- f(X).
    run(X) :- X == [].

    Our Prolog system doesn't create a variable
    at all for the first clause of run. It speculates
    that return value variables are passed around and

    thus resulting in no extra instantiation chains.
    So it passes the anonymous variable from run4
    to the call of f/1. But since the anonymous variable

    is from the run(_) call site, and since there is
    a choice point. The anonymous variable is always
    reachable never carbage collected, similarly chains

    _=[f,..,f|T] will never get garbage collected.
    In as far the test case fails after a while with
    memory overflow.

    Bye

    Mild Shock schrieb:
    Hi,

    Ulrich Neumerkel is like Ozzy Osbourne.
    He is making me paranoid. Especially this
    F.U.D. here stole one week of my life.

    Precise Garbage Collection in Prolog
    https://www.swi-prolog.org/download/publications/lifegc.pdf

    The test cases make no sense at all!
    Take this test case run1, similar to run2
    and run3:

    run1 :- f(_).
    f([f|X]) :- f(X).

    You will never find this in real world.
    Perpetual processes usually have a different
    pattern of loop state transition.

    Also its virtually impossible to garbage collect
    via minor incremental garbage collection. We
    might find a chain X=[f,..,f,Y] and collect

    it. But Xn is then colored as old. And instantiation
    of an old variable gets on the changed list, and
    so a new chain Y=[f,..,f,Z] will not be reclaimed,

    so that the beast can be only reclaimed via
    major garbage collection.

    Bye

    P.S.: Maybe there is a chance to solve it
    nevertheless via minor garbage collection, but
    its very difficult. I had something in

    formerly Jekejeke Prolog via reference counting.
    But not sure how to bring it to a Prolog
    system without reference counting.





    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mild Shock@21:1/5 to Mild Shock on Thu Dec 5 11:44:27 2024
    Hi,

    But we will not promote this test cases as testing anything
    concering Precise Garbage collection. They are rather F.U.D.

    There are other better test cases. See what Trealla Prolog was
    using to improve their Tail Call Optimization (TCO).

    Bye

    Mild Shock schrieb:
    Hi,

    A further test case with choice points is this test case:

    run5(Z) :- p(_,_,Z).
    p(X,Y,Z) :- (Z > 0-> f(X), g(Y), dummy ; g(Y), f(X), dummy).
    g([g|X]) :- g(X).
    dummy.

    But the choice points go away, if Z > 0 the then (->)/2 will
    cut away any choice point. And if not Z > 0 the usual
    optimization is anyway to have no choice point.

    So we are back to the problem of minor garbage collection.
    If we attack the problems with major garbage collection,
    we can run all examples indefinitely. We only need to

    find a high enough major garbage collection frequency.
    Our usual setting is Period: 60, Dirty: 60. With changing
    the setting to Period: 15, Dirty: 15 we can run the

    viable test cases for straight 5 minutes long:

    ?- suite.
    % Zeit 300966 ms, GC 51595 ms, Lips 2026565, Uhr 04.12.2024 12:01
    % Zeit 300622 ms, GC 59049 ms, Lips 1929996, Uhr 04.12.2024 12:06
    % Zeit 301023 ms, GC 62909 ms, Lips 1911479, Uhr 04.12.2024 12:11
    % Zeit 300192 ms, GC 58244 ms, Lips 1925432, Uhr 04.12.2024 12:16
    % Zeit 300065 ms, GC 52253 ms, Lips 1944909, Uhr 04.12.2024 12:21
    true.

    The test code was:

    suite :-
       time(sys_trap(time_out(run1, 300000), _, true)),
       time(sys_trap(time_out(run2, 300000), _, true)),
       time(sys_trap(time_out(run3, 300000), _, true)),
       time(sys_trap(time_out(run5(0), 300000), _, true)),
       time(sys_trap(time_out(run5(1), 300000), _, true)).

    Bye

    Mild Shock schrieb:
    Hi,

    This test case is also extremly cringe.
    In our Prolog system it conflicts with another
    optimization, that is in place to reduce the

    length of instantiation chains.

    run4 :- run(_).
    run(X) :- f(X).
    run(X) :- X == [].

    Our Prolog system doesn't create a variable
    at all for the first clause of run. It speculates
    that return value variables are passed around and

    thus resulting in no extra instantiation chains.
    So it passes the anonymous variable from run4
    to the call of f/1. But since the anonymous variable

    is from the run(_) call site, and since there is
    a choice point. The anonymous variable is always
    reachable never carbage collected, similarly chains

    _=[f,..,f|T] will never get garbage collected.
    In as far the test case fails after a while with
    memory overflow.

    Bye

    Mild Shock schrieb:
    Hi,

    Ulrich Neumerkel is like Ozzy Osbourne.
    He is making me paranoid. Especially this
    F.U.D. here stole one week of my life.

    Precise Garbage Collection in Prolog
    https://www.swi-prolog.org/download/publications/lifegc.pdf

    The test cases make no sense at all!
    Take this test case run1, similar to run2
    and run3:

    run1 :- f(_).
    f([f|X]) :- f(X).

    You will never find this in real world.
    Perpetual processes usually have a different
    pattern of loop state transition.

    Also its virtually impossible to garbage collect
    via minor incremental garbage collection. We
    might find a chain X=[f,..,f,Y] and collect

    it. But Xn is then colored as old. And instantiation
    of an old variable gets on the changed list, and
    so a new chain Y=[f,..,f,Z] will not be reclaimed,

    so that the beast can be only reclaimed via
    major garbage collection.

    Bye

    P.S.: Maybe there is a chance to solve it
    nevertheless via minor garbage collection, but
    its very difficult. I had something in

    formerly Jekejeke Prolog via reference counting.
    But not sure how to bring it to a Prolog
    system without reference counting.






    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mild Shock@21:1/5 to Mild Shock on Sun May 25 09:46:57 2025
    Hi,

    The development of Trealla Prolog and Scryer Prolog
    looks like a random search in a mental ocean.

    It is like Prolog Development à la Sigmund Freud,
    you have only to dig deep enough, and a solution

    will pop up. Otherwise blame your mother or other
    relatives that raised you for supression.

    LoL

    Bye

    Examples: Still clueless how to detect singletons? https://github.com/trealla-prolog/trealla/issues/743

    Mild Shock schrieb:
    Hi,

    But we will not promote this test cases as testing anything
    concering Precise Garbage collection. They are rather F.U.D.

    There are other better test cases. See what Trealla Prolog was
    using to improve their Tail Call Optimization (TCO).

    Bye

    Mild Shock schrieb:
    Hi,

    A further test case with choice points is this test case:

    run5(Z) :- p(_,_,Z).
    p(X,Y,Z) :- (Z > 0-> f(X), g(Y), dummy ; g(Y), f(X), dummy).
    g([g|X]) :- g(X).
    dummy.

    But the choice points go away, if Z > 0 the then (->)/2 will
    cut away any choice point. And if not Z > 0 the usual
    optimization is anyway to have no choice point.

    So we are back to the problem of minor garbage collection.
    If we attack the problems with major garbage collection,
    we can run all examples indefinitely. We only need to

    find a high enough major garbage collection frequency.
    Our usual setting is Period: 60, Dirty: 60. With changing
    the setting to Period: 15, Dirty: 15 we can run the

    viable test cases for straight 5 minutes long:

    ?- suite.
    % Zeit 300966 ms, GC 51595 ms, Lips 2026565, Uhr 04.12.2024 12:01
    % Zeit 300622 ms, GC 59049 ms, Lips 1929996, Uhr 04.12.2024 12:06
    % Zeit 301023 ms, GC 62909 ms, Lips 1911479, Uhr 04.12.2024 12:11
    % Zeit 300192 ms, GC 58244 ms, Lips 1925432, Uhr 04.12.2024 12:16
    % Zeit 300065 ms, GC 52253 ms, Lips 1944909, Uhr 04.12.2024 12:21
    true.

    The test code was:

    suite :-
        time(sys_trap(time_out(run1, 300000), _, true)),
        time(sys_trap(time_out(run2, 300000), _, true)),
        time(sys_trap(time_out(run3, 300000), _, true)),
        time(sys_trap(time_out(run5(0), 300000), _, true)),
        time(sys_trap(time_out(run5(1), 300000), _, true)).

    Bye

    Mild Shock schrieb:
    Hi,

    This test case is also extremly cringe.
    In our Prolog system it conflicts with another
    optimization, that is in place to reduce the

    length of instantiation chains.

    run4 :- run(_).
    run(X) :- f(X).
    run(X) :- X == [].

    Our Prolog system doesn't create a variable
    at all for the first clause of run. It speculates
    that return value variables are passed around and

    thus resulting in no extra instantiation chains.
    So it passes the anonymous variable from run4
    to the call of f/1. But since the anonymous variable

    is from the run(_) call site, and since there is
    a choice point. The anonymous variable is always
    reachable never carbage collected, similarly chains

    _=[f,..,f|T] will never get garbage collected.
    In as far the test case fails after a while with
    memory overflow.

    Bye

    Mild Shock schrieb:
    Hi,

    Ulrich Neumerkel is like Ozzy Osbourne.
    He is making me paranoid. Especially this
    F.U.D. here stole one week of my life.

    Precise Garbage Collection in Prolog
    https://www.swi-prolog.org/download/publications/lifegc.pdf

    The test cases make no sense at all!
    Take this test case run1, similar to run2
    and run3:

    run1 :- f(_).
    f([f|X]) :- f(X).

    You will never find this in real world.
    Perpetual processes usually have a different
    pattern of loop state transition.

    Also its virtually impossible to garbage collect
    via minor incremental garbage collection. We
    might find a chain X=[f,..,f,Y] and collect

    it. But Xn is then colored as old. And instantiation
    of an old variable gets on the changed list, and
    so a new chain Y=[f,..,f,Z] will not be reclaimed,

    so that the beast can be only reclaimed via
    major garbage collection.

    Bye

    P.S.: Maybe there is a chance to solve it
    nevertheless via minor garbage collection, but
    its very difficult. I had something in

    formerly Jekejeke Prolog via reference counting.
    But not sure how to bring it to a Prolog
    system without reference counting.







    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mild Shock@21:1/5 to Mild Shock on Sun May 25 09:57:10 2025
    Hi,

    People from Vienna were always a little strange.
    Why not adopt term_singletons/2 its already around
    for a while. You can do quite some magic with it.

    Example: Determining singletons during listing,
    from Dogelog Player library(tester/tools):

    % sys_listing_write(+Term, +Stream)
    sys_listing_write(C, T) :-
    term_variables(C, V),
    term_singletons(C, A),
    sys_listing_names(V, A, 0, N),
    write_term(T, C, [quoted(true), variable_names(N), format(true)]),
    sys_answer_period(T).

    If term_singletons/2 has the same variable ordering
    guarantees, i.e. left to right, as in term_variables/2
    you can use an algorithm without expensive lookup,

    sys_listing_names([], _, _, []).
    sys_listing_names([X|L], [Y|R], K, ['_'=X|S]) :- X==Y, !,
    sys_listing_names(L, R, K, S).
    sys_listing_names([X|L], A, K, [N=X|R]) :-
    sys_listing_name(K, N),
    J is K+1,
    sys_listing_names(L, A, J, R).

    Just run along the two lists , if something is both in
    the term_variables/2 and term_singletons/2 list, generate
    a '_' name, otherwise generate a synthetic name.

    Bye

    Mild Shock schrieb:
    Hi,

    The development of Trealla Prolog and Scryer Prolog
    looks like a random search in a mental ocean.

    It is like Prolog Development à la Sigmund Freud,
    you have only to dig deep enough, and a solution

    will pop up. Otherwise blame your mother or other
    relatives that raised you for supression.

    LoL

    Bye

    Examples: Still clueless how to detect singletons? https://github.com/trealla-prolog/trealla/issues/743

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mild Shock@21:1/5 to Mild Shock on Sun May 25 10:18:43 2025
    SWI-Prolog has quite an elaborate '_' determiner:

    /* SWI-Prolog */
    ?- length(L,2), (R = L; length(R,2)).
    L = R, R = [_, _] ;
    L = [_, _],
    R = [_, _].

    ?- length(L,2), (R = f(L); length(R,2)).
    L = [_A, _B],
    R = f([_A, _B]) ;
    L = [_, _],
    R = [_, _].

    Especially the L = R detection, seems challenging.
    Thats something more complex than my listing/[0,1]
    and term_singletons/2 usage there.

    I have no pure Prolog solutions yet. My stupid
    Dogelog Player falls back to _:

    /* Dogelog Player */
    ?- length(L,2), (R = L; length(R,2)).
    L = [_309342, _309344], R = [_309342, _309344];
    L = [_309342, _309344], R = [_309495, _309497].

    ?- length(L,2), (R = f(L); length(R,2)).
    L = [_310399, _310401], R = f([_310399, _310401]);
    L = [_310399, _310401], R = [_310574, _310576].

    Mild Shock schrieb:
    Hi,

    People from Vienna were always a little strange.
    Why not adopt term_singletons/2 its already around
    for a while. You can do quite some magic with it.

    Example: Determining singletons during listing,
    from Dogelog Player library(tester/tools):

    % sys_listing_write(+Term, +Stream)
    sys_listing_write(C, T) :-
       term_variables(C, V),
       term_singletons(C, A),
       sys_listing_names(V, A, 0, N),
       write_term(T, C, [quoted(true), variable_names(N), format(true)]),
       sys_answer_period(T).

    If term_singletons/2 has the same variable ordering
    guarantees, i.e. left to right, as in term_variables/2
    you can use an algorithm without expensive lookup,

    sys_listing_names([], _, _, []).
    sys_listing_names([X|L], [Y|R], K, ['_'=X|S]) :- X==Y, !,
       sys_listing_names(L, R, K, S).
    sys_listing_names([X|L], A, K, [N=X|R]) :-
       sys_listing_name(K, N),
       J is K+1,
       sys_listing_names(L, A, J, R).

    Just run along the two lists , if something is both in
    the term_variables/2 and term_singletons/2 list, generate
    a '_' name, otherwise generate a synthetic name.

    Bye

    Mild Shock schrieb:
    Hi,

    The development of Trealla Prolog and Scryer Prolog
    looks like a random search in a mental ocean.

    It is like Prolog Development à la Sigmund Freud,
    you have only to dig deep enough, and a solution

    will pop up. Otherwise blame your mother or other
    relatives that raised you for supression.

    LoL

    Bye

    Examples: Still clueless how to detect singletons?
    https://github.com/trealla-prolog/trealla/issues/743

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mild Shock@21:1/5 to All on Tue May 27 07:45:04 2025
    Expectation:

    /* Dogelog Player 1.3.3, Trealla Prolog 2.71.33,
    Scryer Prolog 0.9.4-403 */
    ?- length(L,2), f(L) = R, S = [_A].
    L = [_B, _C], R = f([_B, _C]), S = [_A].

    /* Dogelog Player 1.3.3, SWI-Prolog 9.3.22 */
    ?- length(L,2), f(L) = R, S = [_].
    L = [_A, _B], R = f([_A, _B]), S = [_].

    Reality:

    /* Trealla Prolog 2.71.33, Scryer Prolog 0.9.4-403 */
    ?- length(L,2), f(L) = R, S = [_].
    L = [_A,_B], R = f([_A,_B]), S = [_C].

    It seems that _ is not reconstructed.

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mild Shock@21:1/5 to Mild Shock on Wed May 28 16:12:52 2025
    I don't understand why some Prolog systems tend to gravitate
    more and more into implementing everything in C. I don't see
    any advantage. Take listing/1, do you get clauses faster and better

    printed when you use C? Starting with the pretty/1 implementation
    in Prolog itself I am pretty sure things can be enhanced. Similarly a
    top level written in pure Prolog can be advantageous.

    SWI-Prolog has a similar deseases of C code overkill sometimes.

    The only argument for C is maybe a different datastructure for
    variable_names. But the algorthm I posted on comp.lang.prolog
    doesn't need a different datastructures, its just a

    pairing algorithm. Running through both the term_variables
    and term_singleton lists in parallel. So there is no advantage of
    C code at all.

    Mild Shock schrieb:
    Hi,

    People from Vienna were always a little strange.
    Why not adopt term_singletons/2 its already around
    for a while. You can do quite some magic with it.

    Example: Determining singletons during listing,
    from Dogelog Player library(tester/tools):

    % sys_listing_write(+Term, +Stream)
    sys_listing_write(C, T) :-
       term_variables(C, V),
       term_singletons(C, A),
       sys_listing_names(V, A, 0, N),
       write_term(T, C, [quoted(true), variable_names(N), format(true)]),
       sys_answer_period(T).

    If term_singletons/2 has the same variable ordering
    guarantees, i.e. left to right, as in term_variables/2
    you can use an algorithm without expensive lookup,

    sys_listing_names([], _, _, []).
    sys_listing_names([X|L], [Y|R], K, ['_'=X|S]) :- X==Y, !,
       sys_listing_names(L, R, K, S).
    sys_listing_names([X|L], A, K, [N=X|R]) :-
       sys_listing_name(K, N),
       J is K+1,
       sys_listing_names(L, A, J, R).

    Just run along the two lists , if something is both in
    the term_variables/2 and term_singletons/2 list, generate
    a '_' name, otherwise generate a synthetic name.

    Bye

    Mild Shock schrieb:
    Hi,

    The development of Trealla Prolog and Scryer Prolog
    looks like a random search in a mental ocean.

    It is like Prolog Development à la Sigmund Freud,
    you have only to dig deep enough, and a solution

    will pop up. Otherwise blame your mother or other
    relatives that raised you for supression.

    LoL

    Bye

    Examples: Still clueless how to detect singletons?
    https://github.com/trealla-prolog/trealla/issues/743

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mild Shock@21:1/5 to Mild Shock on Wed May 28 16:32:34 2025
    Hi,

    Quintus Folks were not hating Prolog that much.
    If you inspect the source code you find mirriads
    of utilities written in Prolog itself.

    Now we find Prolog implementors which seeem to
    be more in love with the host language than with
    Prolog itself, they often totally miss the point,

    that Prolog is a much more elegant and concise
    language than their host language. Namely:

    - Prolog doesn't need to declare a type of variable
    - Prolog doesn't need malloc and free explicitly
    - What else?

    Probably some more postive properties of Prolog,
    make it the ideal language to write most of a Prolog
    system in Prolog itself, such as:

    - The top-level including answer substitution display
    - Tools such as listing/1 including annonymous variable
    - What else?



    Mild Shock schrieb:
    I don't understand why some Prolog systems tend to gravitate
    more and more into implementing everything in C. I don't see
    any advantage. Take listing/1, do you get clauses faster and better

    printed when you use C? Starting with the pretty/1 implementation
    in Prolog itself I am pretty sure things can be enhanced. Similarly a
    top level written in pure Prolog can be advantageous.

    SWI-Prolog has a similar deseases of C code overkill sometimes.

    The only argument for C is maybe a different datastructure for variable_names. But the algorthm I posted on comp.lang.prolog
    doesn't need a different datastructures, its just a

    pairing algorithm. Running through both the term_variables
    and term_singleton lists in parallel. So there is no advantage of
    C code at all.

    Mild Shock schrieb:
    Hi,

    People from Vienna were always a little strange.
    Why not adopt term_singletons/2 its already around
    for a while. You can do quite some magic with it.

    Example: Determining singletons during listing,
    from Dogelog Player library(tester/tools):

    % sys_listing_write(+Term, +Stream)
    sys_listing_write(C, T) :-
        term_variables(C, V),
        term_singletons(C, A),
        sys_listing_names(V, A, 0, N),
        write_term(T, C, [quoted(true), variable_names(N), format(true)]),
        sys_answer_period(T).

    If term_singletons/2 has the same variable ordering
    guarantees, i.e. left to right, as in term_variables/2
    you can use an algorithm without expensive lookup,

    sys_listing_names([], _, _, []).
    sys_listing_names([X|L], [Y|R], K, ['_'=X|S]) :- X==Y, !,
        sys_listing_names(L, R, K, S).
    sys_listing_names([X|L], A, K, [N=X|R]) :-
        sys_listing_name(K, N),
        J is K+1,
        sys_listing_names(L, A, J, R).

    Just run along the two lists , if something is both in
    the term_variables/2 and term_singletons/2 list, generate
    a '_' name, otherwise generate a synthetic name.

    Bye

    Mild Shock schrieb:
    Hi,

    The development of Trealla Prolog and Scryer Prolog
    looks like a random search in a mental ocean.

    It is like Prolog Development à la Sigmund Freud,
    you have only to dig deep enough, and a solution

    will pop up. Otherwise blame your mother or other
    relatives that raised you for supression.

    LoL

    Bye

    Examples: Still clueless how to detect singletons?
    https://github.com/trealla-prolog/trealla/issues/743


    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)