• Re: Prolog code for alpha variants

    From Mild Shock@bursejan@gmail.com to comp.lang.prolog on Wed Oct 18 05:59:24 2023
    From Newsgroup: comp.lang.prolog


    Things that are not in the ISO core standard are more
    likely to behave differently across Prolog systems?

    GNU Prolog behaves already differently to SWI-Prolog in
    numbervars/3. I find this discrepancy:

    /* GNU Prolog 1.5.0 */
    ?- X = f(A,X), numbervars(X, 0, _), write_canonical(A), nl.
    _24
    cannot display cyclic term for X

    /* SWI-Prolog 9.1.16 */
    ?- X = f(A,X), numbervars(X, 0, _), write_canonical(A), nl.
    '$VAR'(0)
    X = f(A, X),
    A = A.

    LoL
    --- Synchronet 3.20a-Linux NewsLink 1.114
  • From Mild Shock@bursejan@gmail.com to comp.lang.prolog on Wed Oct 18 08:56:51 2023
    From Newsgroup: comp.lang.prolog

    So what goodies are there in library(compat) as well?
    Check this out:
    /* SWI-Prolog 9.1.16 */
    ?- numlist(1,100000,A), numlist(1,100000,B),
    time((between(1,1000,_), subsumes((f(_),X,X),(_,A,B)),
    fail; true)), fail.
    % 2,999 inferences, 2.375 CPU in 2.498 seconds (95% CPU, 1263 Lips)
    false.
    /* Dogelog Player 1.1.3 for Java (new!) */
    ?- numlist(1,100000,A), numlist(1,100000,B),
    time((between(1,1000,_), subsumes((f(_),X,X),(_,A,B)),
    fail; true)), fail.
    % Zeit 2 ms, GC 0 ms, Lips 1550000, Uhr 18.10.2023 17:40
    fail.
    Dogelog Player for Java came out a few days ago. To get
    subsumes/2 you have to use ensure_loaded(library(compat)).
    I am using Richard O’Keefes algorithm from 1984 for subsumes/2.
    Mild Shock schrieb am Mittwoch, 18. Oktober 2023 um 14:59:26 UTC+2:
    Things that are not in the ISO core standard are more
    likely to behave differently across Prolog systems?

    GNU Prolog behaves already differently to SWI-Prolog in
    numbervars/3. I find this discrepancy:

    /* GNU Prolog 1.5.0 */
    ?- X = f(A,X), numbervars(X, 0, _), write_canonical(A), nl.
    _24
    cannot display cyclic term for X

    /* SWI-Prolog 9.1.16 */
    ?- X = f(A,X), numbervars(X, 0, _), write_canonical(A), nl.
    '$VAR'(0)
    X = f(A, X),
    A = A.

    LoL
    --- Synchronet 3.20a-Linux NewsLink 1.114
  • From Mild Shock@bursejan@gmail.com to comp.lang.prolog on Thu Oct 19 10:02:21 2023
    From Newsgroup: comp.lang.prolog

    I am not extremly convinced by Richard O'Keefes approach
    for subsumes/2. Especially how I have implemented it in
    Dogelog Player, avoiding term_variables/2 all togtether!
    Possibly I can produce some drastic test cases where it
    doesn't run very well. On the other hand Jan W. is conceptually
    promoting this bootstrapping of subsumes/2:
    subsumes(General, Specific) :-
    term_variables(Specific, SVars),
    General = Specific,
    term_variables(SVars, SVars).
    The above cannot fast fail like Richard O'Keefes approach
    can do. The further boostrapping is identical:
    subsumes_term(General, Specific) :-
    \+ \+ subsumes(General, Specific).
    Mild Shock schrieb am Mittwoch, 18. Oktober 2023 um 17:56:52 UTC+2:
    So what goodies are there in library(compat) as well?

    Check this out:

    /* SWI-Prolog 9.1.16 */
    ?- numlist(1,100000,A), numlist(1,100000,B),
    time((between(1,1000,_), subsumes((f(_),X,X),(_,A,B)),
    fail; true)), fail.
    % 2,999 inferences, 2.375 CPU in 2.498 seconds (95% CPU, 1263 Lips)
    false.

    /* Dogelog Player 1.1.3 for Java (new!) */
    ?- numlist(1,100000,A), numlist(1,100000,B),
    time((between(1,1000,_), subsumes((f(_),X,X),(_,A,B)),
    fail; true)), fail.
    % Zeit 2 ms, GC 0 ms, Lips 1550000, Uhr 18.10.2023 17:40
    fail.

    Dogelog Player for Java came out a few days ago. To get
    subsumes/2 you have to use ensure_loaded(library(compat)).
    I am using Richard O’Keefes algorithm from 1984 for subsumes/2.
    Mild Shock schrieb am Mittwoch, 18. Oktober 2023 um 14:59:26 UTC+2:
    Things that are not in the ISO core standard are more
    likely to behave differently across Prolog systems?

    GNU Prolog behaves already differently to SWI-Prolog in
    numbervars/3. I find this discrepancy:

    /* GNU Prolog 1.5.0 */
    ?- X = f(A,X), numbervars(X, 0, _), write_canonical(A), nl.
    _24
    cannot display cyclic term for X

    /* SWI-Prolog 9.1.16 */
    ?- X = f(A,X), numbervars(X, 0, _), write_canonical(A), nl.
    '$VAR'(0)
    X = f(A, X),
    A = A.

    LoL
    --- Synchronet 3.20a-Linux NewsLink 1.114
  • From Mild Shock@bursejan@gmail.com to comp.lang.prolog on Thu Oct 19 10:04:21 2023
    From Newsgroup: comp.lang.prolog

    But Jan W. conceptualization can be used to develop
    a funny variant/2 predicate. If we start from this here,
    we will have two unifications, in each subsumes_term/2:

    variant2(A,B) :-
    subsumes_term(A,B),
    subsumes_term(B,A).

    We can also use only one unification:

    equalizer(A, B) :-
    term_variables(A, L),
    term_variables(B, R),
    A = B,
    term_variables(L, L),
    term_variables(R, R).

    variant3(A, B) :-
    \+ \+ equalizer(A, B).

    Seems to work:

    A B variant2(A,B) variant3(A,B)
    f(X,g(Y,X),Y) f(Z,g(T,Z),T) true true
    f(X,g(Y,X),Y) f(Z,g(Z,Z),T) false false
    f(X,g(Y,X),X) f(Z,g(T,Z),T) false false
    f(A,A,B) f(B,A,A) false false
    X+Y Y+Z false false

    Mild Shock schrieb am Donnerstag, 19. Oktober 2023 um 19:02:23 UTC+2:
    I am not extremly convinced by Richard O'Keefes approach
    for subsumes/2. Especially how I have implemented it in
    Dogelog Player, avoiding term_variables/2 all togtether!

    Possibly I can produce some drastic test cases where it
    doesn't run very well. On the other hand Jan W. is conceptually
    promoting this bootstrapping of subsumes/2:

    subsumes(General, Specific) :-
    term_variables(Specific, SVars),
    General = Specific,
    term_variables(SVars, SVars).

    The above cannot fast fail like Richard O'Keefes approach
    can do. The further boostrapping is identical:

    subsumes_term(General, Specific) :-
    \+ \+ subsumes(General, Specific).
    --- Synchronet 3.20a-Linux NewsLink 1.114