• Dogzilla: Arrow Functions can be Super Dicts (Was: VIP0909: VibeCoreImprovement Proposal [term_singletons])

    From Mild Shock@[email protected] to comp.lang.prolog on Sun Nov 2 15:50:56 2025
    From Newsgroup: comp.lang.prolog

    Hi,

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

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

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

    The translation is as follows:

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

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

    They work as expected:

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

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

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

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

    Bye

    Mild Shock schrieb:
    Hi,

    Functional requirement:

    ?- Y = g(_,_), X = f(Y,C,D,Y), term_singletons(X, L),
       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@[email protected] to comp.lang.prolog on Sun Nov 2 15:58:19 2025
    From Newsgroup: comp.lang.prolog

    Hi,

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

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

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

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

    We made the keys example to show backtracking:

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

    But this example suffers from a spurious choice point:

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

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

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

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

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

    Bye

    Mild Shock schrieb:
    Hi,

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

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

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

    The translation is as follows:

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

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

    They work as expected:

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

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

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

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

    Bye

    Mild Shock schrieb:
    Hi,

    Functional requirement:

    ?- Y = g(_,_), X = f(Y,C,D,Y), term_singletons(X, L),
        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@[email protected] to comp.lang.prolog on Sun Nov 2 16:28:49 2025
    From Newsgroup: comp.lang.prolog

    Hi,

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

    Lean:

    def fun_update (f : α → β) (a : α) (b : β) : α → β :=
    λ x => if x = a then b else f x

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

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

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

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

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

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

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

    Bye

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

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

    Defining relation extension:

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

    Or defining "calling" them:

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

    See also:

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

    Mild Shock schrieb:
    Hi,

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

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

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


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

    We made the keys example to show backtracking:

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

    But this example suffers from a spurious choice point:

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

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

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

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

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

    Bye

    Mild Shock schrieb:
    Hi,

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

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

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

    The translation is as follows:

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

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

    They work as expected:

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

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

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

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

    Bye

    Mild Shock schrieb:
    Hi,

    Functional requirement:

    ?- Y = g(_,_), X = f(Y,C,D,Y), term_singletons(X, L),
        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@[email protected] to comp.lang.prolog on Sun Nov 2 16:41:52 2025
    From Newsgroup: comp.lang.prolog

    Hi,

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

    To reasoning about. For eample I find:

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

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

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

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

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

    Bye


    Mild Shock schrieb:
    Hi,

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

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

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


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

    We made the keys example to show backtracking:

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

    But this example suffers from a spurious choice point:

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

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

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

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

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

    Bye

    Mild Shock schrieb:
    Hi,

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

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

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

    The translation is as follows:

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

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

    They work as expected:

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

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

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

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

    Bye

    Mild Shock schrieb:
    Hi,

    Functional requirement:

    ?- Y = g(_,_), X = f(Y,C,D,Y), term_singletons(X, L),
        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@[email protected] to comp.lang.prolog on Sun Nov 2 19:47:04 2025
    From Newsgroup: comp.lang.prolog

    Hi,

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

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

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

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

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

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

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

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

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

    (K,V) ∉ R <- (K ≠ foo; V ≠ 123), (K ≠ bar; V ≠ baz)

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

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

    Bye

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

    (K,V) ∉ R <- (K,V) ≠ (foo, 123), (K,V) ≠ (bar, baz).

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

    Mild Shock schrieb:
    Hi,

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

    To reasoning about. For eample I find:

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

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

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

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

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

    Bye

    --- Synchronet 3.21a-Linux NewsLink 1.2