• Re: About the Operator '|' and the DCG Draft

    From Mostowski Collapse@21:1/5 to Mostowski Collapse on Mon Jan 10 12:48:39 2022
    Using DCG is not mandatory. You could also imagine a Prolog
    only solution where this DCG here:

    p --> ['foo bar'], q.

    Is replaced by old CGI style web service:

    p :- write('foo bar'), q.

    You could also use something similar for client side, like Tau-
    Prolog not only server side like for SWI-Prolog. Performance
    depends on the stream that write/1 will use.

    On the server side you could write into a buffer, and then serve
    a HTTP request with a known length, or directly write into the
    HTTP response socket and deliver the result chunked.

    What I observed is that DCG is more handy for debugging. In
    CGI style write/1, when you use it in the Prolog debugger, in
    some console based debugger, the write/1 will constantly

    flood the console, making it practically impossible
    to sensibly debug the thingy.

    Mostowski Collapse schrieb am Montag, 10. Januar 2022 um 21:45:19 UTC+1:
    Now have drummed for DCG usage for the web. Only to notice that
    the DCG Draft has made everything to make this not work. My point
    of departure was Phil Zuckers mixture of Prolog and JavaScript.

    I always thought there is an overselling of Prolog DCG. But somehow
    there is an underselling when doing web stuff. Phil Zuckers example
    using JavaScript for pretty printing is the worst thing I have ever

    seen. If you search a proof tree via Prolog and then use JavaScript
    to render it, you generate a hell of Problems:

    - You need to assume some JavaScript representation of
    the Prolog terms. In the case of Phil Zucker the TauProlog
    this is just an arbitarily designed API. There is no such
    standard for such APIs.
    → Your code is not portable.

    - You need to do stuff in JavaScript that Prolog is much
    better suited for. Like doing text generation, proof filtering
    etc…, I wouldn’t want to do this in JavaScript.
    → Your code is not concise.

    - When doing stuff in Prolog you have automatically
    some flexible indexing, like first argument indexing. Also
    Prolog has additional garbage collection. Things not
    available in JavaScript.
    → Your code is not efficient.

    - It might be prohibitive to call repeatedly Prolog
    predicates during JavaScript rendering. So that
    you might implement stuff twice, in Prolog and
    in JavaScript.
    → Your code is not single source.

    - What else?
    Mostowski Collapse schrieb am Montag, 10. Januar 2022 um 21:32:54 UTC+1:
    Just dont use it for DCG. This here is much more better:

    p --> q; r.
    ?- listing.

    p(_0, _1) :- q(_0, _1); r(_0, _1).
    true.

    Works in Dogelog like that: http://www.xlog.ch/izytab/moblet/en/docs/18_live/10_reference/example01/package.html

    Rational: Ever tried to convert some ordinary code into
    DCG? With (;)/2 reflected as (;)/4 in DCG, this is easy.
    Just replace (:-)/2 by (-->)/2.

    But now the DCG draft wants people to also change (;)/2
    into (|)/4. What a nonsense, since (,)/2 reflects into (,)/4,
    )/2 reflects into (->)/2 and !/0 reflects into !/2.

    With the Dogelog approach all ISO control construct
    reflect without any need for renaming. You can leave '|'
    untouched and use it for TPTP Syntax side by side

    with DCG. On the other hand the DCG Draft wants an
    exception for the (;)/2 and reflect it into (|)/2, causing
    infinitely many nonsense problems.

    See also:

    % operator definitions (TPTP syntax)

    :- op( 500, fy, ~). % negation
    :- op(1000, xfy, &). % conjunction
    :- op(1100, xfy, '|'). % disjunction
    :- op(1110, xfy, =>). % implication

    https://www.philipzucker.com/javascript-automated-proving/

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mostowski Collapse@21:1/5 to All on Mon Jan 10 12:32:53 2022
    Just dont use it for DCG. This here is much more better:

    p --> q; r.
    ?- listing.

    p(_0, _1) :- q(_0, _1); r(_0, _1).
    true.

    Works in Dogelog like that: http://www.xlog.ch/izytab/moblet/en/docs/18_live/10_reference/example01/package.html

    Rational: Ever tried to convert some ordinary code into
    DCG? With (;)/2 reflected as (;)/4 in DCG, this is easy.
    Just replace (:-)/2 by (-->)/2.

    But now the DCG draft wants people to also change (;)/2
    into (|)/4. What a nonsense, since (,)/2 reflects into (,)/4,
    )/2 reflects into (->)/2 and !/0 reflects into !/2.

    With the Dogelog approach all ISO control construct
    reflect without any need for renaming. You can leave '|'
    untouched and use it for TPTP Syntax side by side

    with DCG. On the other hand the DCG Draft wants an
    exception for the (;)/2 and reflect it into (|)/2, causing
    infinitely many nonsense problems.

    See also:

    % operator definitions (TPTP syntax)

    :- op( 500, fy, ~). % negation
    :- op(1000, xfy, &). % conjunction
    :- op(1100, xfy, '|'). % disjunction
    :- op(1110, xfy, =>). % implication

    https://www.philipzucker.com/javascript-automated-proving/

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mostowski Collapse@21:1/5 to Mostowski Collapse on Mon Jan 10 12:45:17 2022
    Now have drummed for DCG usage for the web. Only to notice that
    the DCG Draft has made everything to make this not work. My point
    of departure was Phil Zuckers mixture of Prolog and JavaScript.

    I always thought there is an overselling of Prolog DCG. But somehow
    there is an underselling when doing web stuff. Phil Zuckers example
    using JavaScript for pretty printing is the worst thing I have ever

    seen. If you search a proof tree via Prolog and then use JavaScript
    to render it, you generate a hell of Problems:

    - You need to assume some JavaScript representation of
    the Prolog terms. In the case of Phil Zucker the TauProlog
    this is just an arbitarily designed API. There is no such
    standard for such APIs.
    → Your code is not portable.

    - You need to do stuff in JavaScript that Prolog is much
    better suited for. Like doing text generation, proof filtering
    etc…, I wouldn’t want to do this in JavaScript.
    → Your code is not concise.

    - When doing stuff in Prolog you have automatically
    some flexible indexing, like first argument indexing. Also
    Prolog has additional garbage collection. Things not
    available in JavaScript.
    → Your code is not efficient.

    - It might be prohibitive to call repeatedly Prolog
    predicates during JavaScript rendering. So that
    you might implement stuff twice, in Prolog and
    in JavaScript.
    → Your code is not single source.

    - What else?

    Mostowski Collapse schrieb am Montag, 10. Januar 2022 um 21:32:54 UTC+1:
    Just dont use it for DCG. This here is much more better:

    p --> q; r.
    ?- listing.

    p(_0, _1) :- q(_0, _1); r(_0, _1).
    true.

    Works in Dogelog like that: http://www.xlog.ch/izytab/moblet/en/docs/18_live/10_reference/example01/package.html

    Rational: Ever tried to convert some ordinary code into
    DCG? With (;)/2 reflected as (;)/4 in DCG, this is easy.
    Just replace (:-)/2 by (-->)/2.

    But now the DCG draft wants people to also change (;)/2
    into (|)/4. What a nonsense, since (,)/2 reflects into (,)/4,
    )/2 reflects into (->)/2 and !/0 reflects into !/2.

    With the Dogelog approach all ISO control construct
    reflect without any need for renaming. You can leave '|'
    untouched and use it for TPTP Syntax side by side

    with DCG. On the other hand the DCG Draft wants an
    exception for the (;)/2 and reflect it into (|)/2, causing
    infinitely many nonsense problems.

    See also:

    % operator definitions (TPTP syntax)

    :- op( 500, fy, ~). % negation
    :- op(1000, xfy, &). % conjunction
    :- op(1100, xfy, '|'). % disjunction
    :- op(1110, xfy, =>). % implication

    https://www.philipzucker.com/javascript-automated-proving/

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mostowski Collapse@21:1/5 to Mostowski Collapse on Mon Jan 10 13:15:20 2022
    I dont know yet how much legacy will be destroyed by
    adopting (;)/2 and only (;)/2. If I remember well some
    Prolog system support both (|)/2 and (;)/2 in DCG?

    Not sure. And not sure what the experts say.
    Typically (|)/2 is rather rare, because for DCG there
    is not so much the idiom as seen in syntax docu:

    p --> "foo"
    | "bar"
    | "baz".

    Since we want to parse something, and return
    something. So although a syntax docu might read
    as in the above, practically this often turns into:

    p(ast1) --> "foo".
    p(ast2) --> "bar".
    p(ast3) --> "baz".

    The DCG disjunction disappears!

    Mostowski Collapse schrieb am Montag, 10. Januar 2022 um 21:48:40 UTC+1:
    Using DCG is not mandatory. You could also imagine a Prolog
    only solution where this DCG here:

    p --> ['foo bar'], q.

    Is replaced by old CGI style web service:

    p :- write('foo bar'), q.

    You could also use something similar for client side, like Tau-
    Prolog not only server side like for SWI-Prolog. Performance
    depends on the stream that write/1 will use.

    On the server side you could write into a buffer, and then serve
    a HTTP request with a known length, or directly write into the
    HTTP response socket and deliver the result chunked.

    What I observed is that DCG is more handy for debugging. In
    CGI style write/1, when you use it in the Prolog debugger, in
    some console based debugger, the write/1 will constantly

    flood the console, making it practically impossible
    to sensibly debug the thingy.
    Mostowski Collapse schrieb am Montag, 10. Januar 2022 um 21:45:19 UTC+1:
    Now have drummed for DCG usage for the web. Only to notice that
    the DCG Draft has made everything to make this not work. My point
    of departure was Phil Zuckers mixture of Prolog and JavaScript.

    I always thought there is an overselling of Prolog DCG. But somehow
    there is an underselling when doing web stuff. Phil Zuckers example
    using JavaScript for pretty printing is the worst thing I have ever

    seen. If you search a proof tree via Prolog and then use JavaScript
    to render it, you generate a hell of Problems:

    - You need to assume some JavaScript representation of
    the Prolog terms. In the case of Phil Zucker the TauProlog
    this is just an arbitarily designed API. There is no such
    standard for such APIs.
    → Your code is not portable.

    - You need to do stuff in JavaScript that Prolog is much
    better suited for. Like doing text generation, proof filtering
    etc…, I wouldn’t want to do this in JavaScript.
    → Your code is not concise.

    - When doing stuff in Prolog you have automatically
    some flexible indexing, like first argument indexing. Also
    Prolog has additional garbage collection. Things not
    available in JavaScript.
    → Your code is not efficient.

    - It might be prohibitive to call repeatedly Prolog
    predicates during JavaScript rendering. So that
    you might implement stuff twice, in Prolog and
    in JavaScript.
    → Your code is not single source.

    - What else?
    Mostowski Collapse schrieb am Montag, 10. Januar 2022 um 21:32:54 UTC+1:
    Just dont use it for DCG. This here is much more better:

    p --> q; r.
    ?- listing.

    p(_0, _1) :- q(_0, _1); r(_0, _1).
    true.

    Works in Dogelog like that: http://www.xlog.ch/izytab/moblet/en/docs/18_live/10_reference/example01/package.html

    Rational: Ever tried to convert some ordinary code into
    DCG? With (;)/2 reflected as (;)/4 in DCG, this is easy.
    Just replace (:-)/2 by (-->)/2.

    But now the DCG draft wants people to also change (;)/2
    into (|)/4. What a nonsense, since (,)/2 reflects into (,)/4,
    )/2 reflects into (->)/2 and !/0 reflects into !/2.

    With the Dogelog approach all ISO control construct
    reflect without any need for renaming. You can leave '|'
    untouched and use it for TPTP Syntax side by side

    with DCG. On the other hand the DCG Draft wants an
    exception for the (;)/2 and reflect it into (|)/2, causing
    infinitely many nonsense problems.

    See also:

    % operator definitions (TPTP syntax)

    :- op( 500, fy, ~). % negation
    :- op(1000, xfy, &). % conjunction
    :- op(1100, xfy, '|'). % disjunction
    :- op(1110, xfy, =>). % implication

    https://www.philipzucker.com/javascript-automated-proving/

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mostowski Collapse@21:1/5 to All on Tue Jan 11 14:55:48 2022
    Here is a little educational parser called Birdy. Joseph Vidal-Rosset might
    use it in his prover web site? It understands xfy and fy only, very primitiv. Advantage, Birdy accepts lower and upper case as atom:

    /* Welcome to SWI-Prolog (threaded, 64 bits, version 8.5.1) */

    ?- parse('p=>(q=>p)', T), write_canonical(T), nl.
    (p,=>(q,p))

    ?- parse('P=>(Q=>P)', T), write_canonical(T), nl.
    ('P',=>('Q','P'))

    ?- parse('p=>p|q=>(q=> ~ ~r&s)', T), write_canonical(T), nl. =>(p,=>('|'(p,q),=>(q,&(~(~(r)),s))))

    Thats the code of Birdy:

    :- set_prolog_flag(double_quotes, codes).

    oper(500, fy, ~).
    oper(1000, xfy, &).
    oper(1100, xfy, '|').
    oper(1110, xfy, =>).

    parse(A, T) :-
    atom_codes(A, C),
    tokens(L, C, []),
    term(T, 1200, L, []).

    term(X, L) --> factor(Y), rest(Y, L, X).

    rest(Y, L, S) --> [atom(X)], {oper(M, xfy, X)}, {M =< L}, !,
    term(Z, M), {T =.. [X,Y,Z]}, rest(T, L, S).
    rest(Y, _, Y) --> [].

    factor(X) --> [lpar], !, term(X, 1200), [rpar].
    factor(Z) --> [atom(X)], {oper(L, fy, X)}, !,
    term(Y, L), {Z =.. [X,Y]}.
    factor(X) --> [atom(X)].

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mostowski Collapse@21:1/5 to Mostowski Collapse on Tue Jan 11 14:57:59 2022
    This belongs also to Birdy, the tokenizer:

    tokens([X|L]) --> token(X), !, tokens(L).
    tokens([]) --> [].

    token(F) --> " ", !, token(F).
    token(atom(A)) --> alpha(X), !, alphanums(L), {atom_codes(A, [X|L])}. token(atom(A)) --> sym(X), !, syms(L), {atom_codes(A, [X|L])}.
    token(lpar) --> "(", !.
    token(rpar) --> ")".

    alphanums([X|L]) --> alpha(X), !, alphanums(L).
    alphanums([X|L]) --> num(X), !, alphanums(L).
    alphanums([]) --> [].

    alpha(X) --> [X], {0'a =< X, X =< 0'z}, !.
    alpha(X) --> [X], {0'A =< X, X =< 0'Z}, !.
    alpha(X) --> [X], {member(X, "_")}.

    num(X) --> [X], {0'0 =< X, X =< 0'9}, !.

    syms([X|L]) --> sym(X), !, syms(L).
    syms([]) --> [].

    sym(X) --> [X], {member(X, "<=>&|~")}.

    Why do such a thing? Well it gets interesting, since we could now
    add quantifier parsing, which is not available in ordinary Prolog. We
    could also extend it by automatically for example mapping Unicode
    → into ASCII =>.

    Mostowski Collapse schrieb am Dienstag, 11. Januar 2022 um 23:55:49 UTC+1:
    Here is a little educational parser called Birdy. Joseph Vidal-Rosset might use it in his prover web site? It understands xfy and fy only, very primitiv.
    Advantage, Birdy accepts lower and upper case as atom:

    /* Welcome to SWI-Prolog (threaded, 64 bits, version 8.5.1) */

    ?- parse('p=>(q=>p)', T), write_canonical(T), nl.
    (p,=>(q,p))

    ?- parse('P=>(Q=>P)', T), write_canonical(T), nl.
    ('P',=>('Q','P'))

    ?- parse('p=>p|q=>(q=> ~ ~r&s)', T), write_canonical(T), nl. =>(p,=>('|'(p,q),=>(q,&(~(~(r)),s))))

    Thats the code of Birdy:

    :- set_prolog_flag(double_quotes, codes).

    oper(500, fy, ~).
    oper(1000, xfy, &).
    oper(1100, xfy, '|').
    oper(1110, xfy, =>).

    parse(A, T) :-
    atom_codes(A, C),
    tokens(L, C, []),
    term(T, 1200, L, []).

    term(X, L) --> factor(Y), rest(Y, L, X).

    rest(Y, L, S) --> [atom(X)], {oper(M, xfy, X)}, {M =< L}, !,
    term(Z, M), {T =.. [X,Y,Z]}, rest(T, L, S).
    rest(Y, _, Y) --> [].

    factor(X) --> [lpar], !, term(X, 1200), [rpar].
    factor(Z) --> [atom(X)], {oper(L, fy, X)}, !,
    term(Y, L), {Z =.. [X,Y]}.
    factor(X) --> [atom(X)].

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mostowski Collapse@21:1/5 to Mostowski Collapse on Wed Jan 12 03:58:20 2022
    Ok I made a further version, which in summary adresses
    two issues with the default Prolog parser:

    - Upper Case: The new tokenizer should not classify upper
    case tokens into Prolog variables, instead they should
    simply go into Prolog atoms.

    - Solo Characters: The new tokenizer should have a larger
    class of solo character tokens, this is more comfortable
    for prefix operators.

    See also:

    Prolog Operator Syntax in One Page https://twitter.com/dogelogch/status/1481227386939183107

    Prolog Operator Syntax in One Page
    https://www.facebook.com/groups/dogelog

    Mostowski Collapse schrieb am Dienstag, 11. Januar 2022 um 23:58:01 UTC+1:
    This belongs also to Birdy, the tokenizer:

    tokens([X|L]) --> token(X), !, tokens(L).
    tokens([]) --> [].

    token(F) --> " ", !, token(F).
    token(atom(A)) --> alpha(X), !, alphanums(L), {atom_codes(A, [X|L])}. token(atom(A)) --> sym(X), !, syms(L), {atom_codes(A, [X|L])}.
    token(lpar) --> "(", !.
    token(rpar) --> ")".

    alphanums([X|L]) --> alpha(X), !, alphanums(L).
    alphanums([X|L]) --> num(X), !, alphanums(L).
    alphanums([]) --> [].

    alpha(X) --> [X], {0'a =< X, X =< 0'z}, !.
    alpha(X) --> [X], {0'A =< X, X =< 0'Z}, !.
    alpha(X) --> [X], {member(X, "_")}.

    num(X) --> [X], {0'0 =< X, X =< 0'9}, !.

    syms([X|L]) --> sym(X), !, syms(L).
    syms([]) --> [].

    sym(X) --> [X], {member(X, "<=>&|~")}.

    Why do such a thing? Well it gets interesting, since we could now
    add quantifier parsing, which is not available in ordinary Prolog. We
    could also extend it by automatically for example mapping Unicode
    → into ASCII =>.
    Mostowski Collapse schrieb am Dienstag, 11. Januar 2022 um 23:55:49 UTC+1:
    Here is a little educational parser called Birdy. Joseph Vidal-Rosset might
    use it in his prover web site? It understands xfy and fy only, very primitiv.
    Advantage, Birdy accepts lower and upper case as atom:

    /* Welcome to SWI-Prolog (threaded, 64 bits, version 8.5.1) */

    ?- parse('p=>(q=>p)', T), write_canonical(T), nl.
    (p,=>(q,p))

    ?- parse('P=>(Q=>P)', T), write_canonical(T), nl.
    ('P',=>('Q','P'))

    ?- parse('p=>p|q=>(q=> ~ ~r&s)', T), write_canonical(T), nl. =>(p,=>('|'(p,q),=>(q,&(~(~(r)),s))))

    Thats the code of Birdy:

    :- set_prolog_flag(double_quotes, codes).

    oper(500, fy, ~).
    oper(1000, xfy, &).
    oper(1100, xfy, '|').
    oper(1110, xfy, =>).

    parse(A, T) :-
    atom_codes(A, C),
    tokens(L, C, []),
    term(T, 1200, L, []).

    term(X, L) --> factor(Y), rest(Y, L, X).

    rest(Y, L, S) --> [atom(X)], {oper(M, xfy, X)}, {M =< L}, !,
    term(Z, M), {T =.. [X,Y,Z]}, rest(T, L, S).
    rest(Y, _, Y) --> [].

    factor(X) --> [lpar], !, term(X, 1200), [rpar].
    factor(Z) --> [atom(X)], {oper(L, fy, X)}, !,
    term(Y, L), {Z =.. [X,Y]}.
    factor(X) --> [atom(X)].

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mostowski Collapse@21:1/5 to Mostowski Collapse on Wed Jan 12 04:45:17 2022
    BTW: I have already a prototype in the pipeline that can do
    quantifiers. But unfortunately not yet in the TPTP syntax.
    Also not in the TPTP syntax with my modification.

    But its relatively easy to add quantifier syntax to such
    a parser/unparser. For example I added, so the idea is
    that a quantifier has novel associativity icon fzy:

    oper(!, fzy, 500).
    oper(?, fzy, 500).

    The parser needs only this additional clause:

    factor(T) --> [atom(X)], {oper(X, fzy, M)}, !,
    term(Y, 0), term(Z, M), {T =.. [X,Y,Z]}.

    The unparser needs only this additional clause:

    show(T, L) --> {T =.. [X, Y, Z], oper(X, fzy, M)}, !,
    needs(L, M, '('),
    [X], show(Y, 0), [' '], show(Z, M),
    needs(L, M, ')').

    Eh voilà the following works:

    ?- parse('!x p=>?x p', X).
    X = =>(!(x, p), ?(x, p)).

    ?- unparse(=>(!(x, p), ?(x, p)), X).
    X = '!x p=>?x p'.

    ?- parse('!x(p=>q)=>!x p=>!x q', X).
    X = =>(!(x, =>(p, q)), =>(!(x, p), !(x, q))).

    ?- unparse(=>(!(x, =>(p, q)), =>(!(x, p), !(x, q))), X).
    X = '!x (p=>q)=>!x p=>!x q'.

    They are on par with prefix operators, so I assume they are
    solo characters, which I did arrange in the tokenizer, and I
    can then omit spaces around them.

    Mostowski Collapse schrieb am Mittwoch, 12. Januar 2022 um 12:58:21 UTC+1:
    Ok I made a further version, which in summary adresses
    two issues with the default Prolog parser:

    - Upper Case: The new tokenizer should not classify upper
    case tokens into Prolog variables, instead they should
    simply go into Prolog atoms.

    - Solo Characters: The new tokenizer should have a larger
    class of solo character tokens, this is more comfortable
    for prefix operators.

    See also:

    Prolog Operator Syntax in One Page https://twitter.com/dogelogch/status/1481227386939183107

    Prolog Operator Syntax in One Page
    https://www.facebook.com/groups/dogelog
    Mostowski Collapse schrieb am Dienstag, 11. Januar 2022 um 23:58:01 UTC+1:
    This belongs also to Birdy, the tokenizer:

    tokens([X|L]) --> token(X), !, tokens(L).
    tokens([]) --> [].

    token(F) --> " ", !, token(F).
    token(atom(A)) --> alpha(X), !, alphanums(L), {atom_codes(A, [X|L])}. token(atom(A)) --> sym(X), !, syms(L), {atom_codes(A, [X|L])}.
    token(lpar) --> "(", !.
    token(rpar) --> ")".

    alphanums([X|L]) --> alpha(X), !, alphanums(L).
    alphanums([X|L]) --> num(X), !, alphanums(L).
    alphanums([]) --> [].

    alpha(X) --> [X], {0'a =< X, X =< 0'z}, !.
    alpha(X) --> [X], {0'A =< X, X =< 0'Z}, !.
    alpha(X) --> [X], {member(X, "_")}.

    num(X) --> [X], {0'0 =< X, X =< 0'9}, !.

    syms([X|L]) --> sym(X), !, syms(L).
    syms([]) --> [].

    sym(X) --> [X], {member(X, "<=>&|~")}.

    Why do such a thing? Well it gets interesting, since we could now
    add quantifier parsing, which is not available in ordinary Prolog. We could also extend it by automatically for example mapping Unicode
    → into ASCII =>.
    Mostowski Collapse schrieb am Dienstag, 11. Januar 2022 um 23:55:49 UTC+1:
    Here is a little educational parser called Birdy. Joseph Vidal-Rosset might
    use it in his prover web site? It understands xfy and fy only, very primitiv.
    Advantage, Birdy accepts lower and upper case as atom:

    /* Welcome to SWI-Prolog (threaded, 64 bits, version 8.5.1) */

    ?- parse('p=>(q=>p)', T), write_canonical(T), nl.
    (p,=>(q,p))

    ?- parse('P=>(Q=>P)', T), write_canonical(T), nl.
    ('P',=>('Q','P'))

    ?- parse('p=>p|q=>(q=> ~ ~r&s)', T), write_canonical(T), nl. =>(p,=>('|'(p,q),=>(q,&(~(~(r)),s))))

    Thats the code of Birdy:

    :- set_prolog_flag(double_quotes, codes).

    oper(500, fy, ~).
    oper(1000, xfy, &).
    oper(1100, xfy, '|').
    oper(1110, xfy, =>).

    parse(A, T) :-
    atom_codes(A, C),
    tokens(L, C, []),
    term(T, 1200, L, []).

    term(X, L) --> factor(Y), rest(Y, L, X).

    rest(Y, L, S) --> [atom(X)], {oper(M, xfy, X)}, {M =< L}, !,
    term(Z, M), {T =.. [X,Y,Z]}, rest(T, L, S).
    rest(Y, _, Y) --> [].

    factor(X) --> [lpar], !, term(X, 1200), [rpar].
    factor(Z) --> [atom(X)], {oper(L, fy, X)}, !,
    term(Y, L), {Z =.. [X,Y]}.
    factor(X) --> [atom(X)].

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mostowski Collapse@21:1/5 to All on Wed Jan 12 12:47:47 2022
    Ok, there is a first prototype integrating the one page
    Prolog operator syntax code, with the MathJax renderer.
    The idea is simple, add a column to the table oper/3:

    oper(~, fy, 800, '\\neg ').
    oper(&, xfy, 1000, ' \\land ').
    oper('|', xfy, 1100, ' \\lor ').
    oper(=>, xfy, 1200, ' \\implies ').

    See also:

    Latex Bliss from Prolog Operator Syntax https://twitter.com/dogelogch/status/1481360427636375554

    Latex Bliss from Prolog Operator Syntax
    https://www.facebook.com/groups/dogelog

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mostowski Collapse@21:1/5 to Mostowski Collapse on Sun Jan 16 04:25:56 2022
    Now having fun with an output switch, can do:

    ?- parse('∀x ∃y f(x) = y', F).
    F = !(:([_0 = x], ?(:([_1 = y], f(_0) = _1)))).

    ?- unparse(!(:([A = x], ?(:([B = y], f(A) = B)))), unicode, T).
    T = '∀x ∃y f(x) = y'.

    ?- unparse(!(:([A = x], ?(:([B = y], f(A) = B)))), latex, T).
    T = '\\forall x\\, \\exists y\\, \\mathup{f}(x) = y'.

    The LaTeX DCG result can be used inside a browser via MathJax.
    But with the novel operator type fzy, that is used under the hood,
    I am also solving another problem, not only LaTeX output.

    The other problem that is also solved is dealing with input and output
    of formulas that contain quantifiers. The library is now called
    Formula Interlingua Library (FIL).

    See also:

    Formula Interlingua from Prolog Operator Syntax https://twitter.com/dogelogch/status/1482536744872521732

    Formula Interlingua from Prolog Operator Syntax https://www.facebook.com/groups/dogelog

    Mostowski Collapse schrieb am Mittwoch, 12. Januar 2022 um 21:47:49 UTC+1:
    Ok, there is a first prototype integrating the one page
    Prolog operator syntax code, with the MathJax renderer.
    The idea is simple, add a column to the table oper/3:

    oper(~, fy, 800, '\\neg ').
    oper(&, xfy, 1000, ' \\land ').
    oper('|', xfy, 1100, ' \\lor ').
    oper(=>, xfy, 1200, ' \\implies ').

    See also:

    Latex Bliss from Prolog Operator Syntax https://twitter.com/dogelogch/status/1481360427636375554

    Latex Bliss from Prolog Operator Syntax https://www.facebook.com/groups/dogelog

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mostowski Collapse@21:1/5 to Mostowski Collapse on Sun Jan 16 04:30:11 2022
    Adding MathJax to your web site is very simple,
    bypassing the now outdated and not widely
    supported MathML. MathJax notes the following

    problems with MathML:

    CommonHTML and not MathML is MathJax’s primary output
    mode since MathJax version 2.6. Its major advantage is its
    quality, consistency, and the fact that its output is independent
    of the browser, operating system, and user environment.
    HTML Support — MathJax 3.2 documentation https://docs.mathjax.org/en/latest/output/html.html

    This worked for me:

    - Step 1: Load the MathJax library. Load the CommonHTML
    output processor (chtml), that renders your mathematics
    using HTML with CSS styling:

    <script src="http://cdn.jsdelivr.net/npm/mathjax@3/es5/tex-chtml.js" id="MathJax-script" async=""> </script>

    - Step 2: Make the MathJax library load some stuff by itself.
    This is a little cludge, not sure what would be the official
    approach here, this loads bussproof:

    <p>\begin{prooftree} \end{prooftree}</p>

    - Step 3: Notify MathJax library if you have DOM changes. Not
    needed after browser page load, only for user interaction. Do
    this JavaScript when you are finished doing updates:

    MathJax.typeset();

    Mostowski Collapse schrieb am Sonntag, 16. Januar 2022 um 13:25:57 UTC+1:
    Now having fun with an output switch, can do:

    ?- parse('∀x ∃y f(x) = y', F).
    F = !(:([_0 = x], ?(:([_1 = y], f(_0) = _1)))).

    ?- unparse(!(:([A = x], ?(:([B = y], f(A) = B)))), unicode, T).
    T = '∀x ∃y f(x) = y'.

    ?- unparse(!(:([A = x], ?(:([B = y], f(A) = B)))), latex, T).
    T = '\\forall x\\, \\exists y\\, \\mathup{f}(x) = y'.

    The LaTeX DCG result can be used inside a browser via MathJax.
    But with the novel operator type fzy, that is used under the hood,
    I am also solving another problem, not only LaTeX output.

    The other problem that is also solved is dealing with input and output
    of formulas that contain quantifiers. The library is now called
    Formula Interlingua Library (FIL).

    See also:

    Formula Interlingua from Prolog Operator Syntax https://twitter.com/dogelogch/status/1482536744872521732

    Formula Interlingua from Prolog Operator Syntax https://www.facebook.com/groups/dogelog
    Mostowski Collapse schrieb am Mittwoch, 12. Januar 2022 um 21:47:49 UTC+1:
    Ok, there is a first prototype integrating the one page
    Prolog operator syntax code, with the MathJax renderer.
    The idea is simple, add a column to the table oper/3:

    oper(~, fy, 800, '\\neg ').
    oper(&, xfy, 1000, ' \\land ').
    oper('|', xfy, 1100, ' \\lor ').
    oper(=>, xfy, 1200, ' \\implies ').

    See also:

    Latex Bliss from Prolog Operator Syntax https://twitter.com/dogelogch/status/1481360427636375554

    Latex Bliss from Prolog Operator Syntax https://www.facebook.com/groups/dogelog

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mostowski Collapse@21:1/5 to Mostowski Collapse on Mon Jan 17 12:51:19 2022
    Currently picking up the topic again. Seems I don't run
    into problems when abandoning (|)/2 and favoring (;)/2 for DCG.

    Its rather the rule to have (;)/2 and the exception
    to have (|)/2. Take this example:

    p --> q;r.
    p --> q|r.

    Just out of curriousity checked TauProlog, it barks
    at the operator (|)/2, but does (;)/2:

    error parsing program: error(syntax_error(. or operator expected),[line(3),column(7),found(|)])
    ?- listing(p/2).
    p(_1,_3) :- (q(_1,_2);r(_1,_3)),_2=_3.

    And then checked SWI-Prolog. It does both operators:

    ?- listing(p/2).
    p(A, B) :-
    ( q(A, B)
    ; r(A, B)
    ).
    p(A, B) :-
    ( q(A, B)
    ; r(A, B)
    ).

    So they both have (;)/2 as DCG disjunction.
    Thats nice.

    Mostowski Collapse schrieb am Montag, 10. Januar 2022 um 22:15:21 UTC+1:
    I dont know yet how much legacy will be destroyed by
    adopting (;)/2 and only (;)/2. If I remember well some
    Prolog system support both (|)/2 and (;)/2 in DCG?

    Not sure. And not sure what the experts say.
    Typically (|)/2 is rather rare, because for DCG there
    is not so much the idiom as seen in syntax docu:

    p --> "foo"
    | "bar"
    | "baz".

    Since we want to parse something, and return
    something. So although a syntax docu might read
    as in the above, practically this often turns into:

    p(ast1) --> "foo".
    p(ast2) --> "bar".
    p(ast3) --> "baz".

    The DCG disjunction disappears!

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mostowski Collapse@21:1/5 to All on Tue Feb 22 16:23:07 2022
    Some of the best kept secrets in Prolog. How to make a parser
    that can parse TPTP Syntax? Here is the problem:

    :- op( 600, fy, !).
    prove(F, C, I) :- norm(F, C, G), iter(G, 0, C, I), !.

    Hell breaks loose, and a naive Prolog parser wants me to write the
    cut with parenthesis (!). But SWI-Prolog doesn't need that.

    What is the magic potion that does this feat?

    See also:
    https://github.com/mthom/scryer-prolog/issues/1289

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mostowski Collapse@21:1/5 to Mostowski Collapse on Tue Feb 22 16:50:39 2022
    In general I think its good that SWI-Prolog pioneers a little bit
    more than what is usually considered Prolog syntax. The only
    problem is that Prolog has no “Living Standard” project,

    unlike for example HTML.
    https://html.spec.whatwg.org/

    Mostowski Collapse schrieb am Mittwoch, 23. Februar 2022 um 01:30:28 UTC+1:
    SWI-Prolog might have yet another heuristic, this is genuine
    Dogelog player. But its a quite useful heuristic. Here you see
    how the ',' stopper together with the ')' stopper does a little more.

    I can for example parse the following in Dogelog player:

    ?- X = (-, -).
    X = (-, -). http://www.xlog.ch/izytab/doclet/docs/18_live/10_reference/example01/package.html

    SWI-Prolog adds some parenthesis around - during writing, but
    this is not necessary, when it can parse it without, why should it
    write it with? Formerly Jekejeke Prolog and Dogelog cover this

    case also during writing. On the other hand Scryer Prolog gives me:

    ?- X = (-, -).
    caught: error(syntax_error(incomplete_reduction),read_term/3:1)
    Mostowski Collapse schrieb am Mittwoch, 23. Februar 2022 um 01:26:12 UTC+1:
    For example in formerly Jekejeke Prolog and in Dogelog I can
    also parse the same. Because I do have additional rules to the
    following operator escaping that is suggested:

    (!)

    I added these operator escapes, the ')' escaping is only a special
    case of it, the general routine does the following:

    % read_prefix(-Term, +Integer, +Integer, +Integer, +Quad, -Quad) read_prefix(A, A, _, _, _) --> current_token(T), {is_stopper(T)}, !. read_prefix(H, A, L, R, E) -->
    {L < R -> throw(error(syntax_error(operator_clash), _)); true},
    {T is R-E}, read(Z, T), {H =.. [A, Z]}.
    % is_stopper(+Term)
    is_stopper(',').
    is_stopper('|').
    is_stopper(')'). %%% Covers the usual ( op ) and more %%%% is_stopper(']').
    is_stopper('}').
    is_stopper('.').

    Its open source and 100% pure Prolog: http://pages.xlog.ch/littab/doclet/docs/05_devel/transpiler/loader.html Mostowski Collapse schrieb am Mittwoch, 23. Februar 2022 um 01:23:10 UTC+1:
    Some of the best kept secrets in Prolog. How to make a parser
    that can parse TPTP Syntax? Here is the problem:

    :- op( 600, fy, !).
    prove(F, C, I) :- norm(F, C, G), iter(G, 0, C, I), !.

    Hell breaks loose, and a naive Prolog parser wants me to write the
    cut with parenthesis (!). But SWI-Prolog doesn't need that.

    What is the magic potion that does this feat?

    See also:
    https://github.com/mthom/scryer-prolog/issues/1289

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mostowski Collapse@21:1/5 to Mostowski Collapse on Tue Feb 22 16:26:10 2022
    For example in formerly Jekejeke Prolog and in Dogelog I can
    also parse the same. Because I do have additional rules to the
    following operator escaping that is suggested:

    (!)

    I added these operator escapes, the ')' escaping is only a special
    case of it, the general routine does the following:

    % read_prefix(-Term, +Integer, +Integer, +Integer, +Quad, -Quad)
    read_prefix(A, A, _, _, _) --> current_token(T), {is_stopper(T)}, !. read_prefix(H, A, L, R, E) -->
    {L < R -> throw(error(syntax_error(operator_clash), _)); true},
    {T is R-E}, read(Z, T), {H =.. [A, Z]}.
    % is_stopper(+Term)
    is_stopper(',').
    is_stopper('|').
    is_stopper(')'). %%% Covers the usual ( op ) and more %%%%
    is_stopper(']').
    is_stopper('}').
    is_stopper('.').

    Its open source and 100% pure Prolog: http://pages.xlog.ch/littab/doclet/docs/05_devel/transpiler/loader.html

    Mostowski Collapse schrieb am Mittwoch, 23. Februar 2022 um 01:23:10 UTC+1:
    Some of the best kept secrets in Prolog. How to make a parser
    that can parse TPTP Syntax? Here is the problem:

    :- op( 600, fy, !).
    prove(F, C, I) :- norm(F, C, G), iter(G, 0, C, I), !.

    Hell breaks loose, and a naive Prolog parser wants me to write the
    cut with parenthesis (!). But SWI-Prolog doesn't need that.

    What is the magic potion that does this feat?

    See also:
    https://github.com/mthom/scryer-prolog/issues/1289

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mostowski Collapse@21:1/5 to Mostowski Collapse on Tue Feb 22 16:30:25 2022
    SWI-Prolog might have yet another heuristic, this is genuine
    Dogelog player. But its a quite useful heuristic. Here you see
    how the ',' stopper together with the ')' stopper does a little more.

    I can for example parse the following in Dogelog player:

    ?- X = (-, -).
    X = (-, -). http://www.xlog.ch/izytab/doclet/docs/18_live/10_reference/example01/package.html

    SWI-Prolog adds some parenthesis around - during writing, but
    this is not necessary, when it can parse it without, why should it
    write it with? Formerly Jekejeke Prolog and Dogelog cover this

    case also during writing. On the other hand Scryer Prolog gives me:

    ?- X = (-, -).
    caught: error(syntax_error(incomplete_reduction),read_term/3:1)

    Mostowski Collapse schrieb am Mittwoch, 23. Februar 2022 um 01:26:12 UTC+1:
    For example in formerly Jekejeke Prolog and in Dogelog I can
    also parse the same. Because I do have additional rules to the
    following operator escaping that is suggested:

    (!)

    I added these operator escapes, the ')' escaping is only a special
    case of it, the general routine does the following:

    % read_prefix(-Term, +Integer, +Integer, +Integer, +Quad, -Quad) read_prefix(A, A, _, _, _) --> current_token(T), {is_stopper(T)}, !. read_prefix(H, A, L, R, E) -->
    {L < R -> throw(error(syntax_error(operator_clash), _)); true},
    {T is R-E}, read(Z, T), {H =.. [A, Z]}.
    % is_stopper(+Term)
    is_stopper(',').
    is_stopper('|').
    is_stopper(')'). %%% Covers the usual ( op ) and more %%%%
    is_stopper(']').
    is_stopper('}').
    is_stopper('.').

    Its open source and 100% pure Prolog: http://pages.xlog.ch/littab/doclet/docs/05_devel/transpiler/loader.html Mostowski Collapse schrieb am Mittwoch, 23. Februar 2022 um 01:23:10 UTC+1:
    Some of the best kept secrets in Prolog. How to make a parser
    that can parse TPTP Syntax? Here is the problem:

    :- op( 600, fy, !).
    prove(F, C, I) :- norm(F, C, G), iter(G, 0, C, I), !.

    Hell breaks loose, and a naive Prolog parser wants me to write the
    cut with parenthesis (!). But SWI-Prolog doesn't need that.

    What is the magic potion that does this feat?

    See also:
    https://github.com/mthom/scryer-prolog/issues/1289

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mostowski Collapse@21:1/5 to Mostowski Collapse on Wed Feb 23 01:49:56 2022
    I have the impression many Prolog systems have it or had it, and maybe
    it slipped the ISO core standard or the Ulrich Neumerkel test cases, otherwise I cannot explain how mode declarations such as append(+, +, -)

    were/are handled? The is_stopper/1 doesn't change when something is a
    prefix operator, its a conservative extension concerning the accepted
    sentences by the language grammar.

    It only changes when something is not a prefix operator. It produces
    less many errors, i.e. the cryptic incomplete_reduction error by Scryer
    Prolog goes away. It does so in a very simple and efficient way, not

    needing some extra look ahead or complicated algorithm.

    Mostowski Collapse schrieb am Mittwoch, 23. Februar 2022 um 10:48:07 UTC+1:
    It is extremly trivial as the is_stopper/1 source code shows,
    it can be verbalized as follows:

    /**
    * Dont use the grammar production prefix_op term, when term is
    * anyway no term determined by looking at the current token.
    */
    And when in doubt, you can just try it online:

    ?- X = (- - a), write_canonical(X), nl.
    -(-(a))
    X = - -a.
    ?- X = (- - -), write_canonical(X), nl.
    -(-(-))
    X = - - - .

    http://www.xlog.ch/izytab/doclet/docs/18_live/10_reference/example01/package.html

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mostowski Collapse@21:1/5 to All on Wed Feb 23 01:48:05 2022
    It is extremly trivial as the is_stopper/1 source code shows,
    it can be verbalized as follows:

    /**
    * Dont use the grammar production prefix_op term, when term is
    * anyway no term determined by looking at the current token.
    */
    And when in doubt, you can just try it online:

    ?- X = (- - a), write_canonical(X), nl.
    -(-(a))
    X = - -a.
    ?- X = (- - -), write_canonical(X), nl.
    -(-(-))
    X = - - - .

    http://www.xlog.ch/izytab/doclet/docs/18_live/10_reference/example01/package.html

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mostowski Collapse@21:1/5 to Mostowski Collapse on Wed Feb 23 02:28:54 2022
    The main challenge for Dogelog player was only to write a tokenizer
    that plays into the hands of the parser, so that is_stopper/1 works
    as desired. Note that I also have is_stopper('|'). This is consistent with:

    ?- X = '|'.
    X = '|'.

    ?- X = | .
    error(syntax_error(cannot_start_term), _0) http://www.xlog.ch/izytab/doclet/docs/18_live/10_reference/example01/package.html

    So there is some special handling of ',' and '|' already in the
    tokenizer. For example the bare | is tokenized as '|' whereas
    the quoted '|' is tokenized as atom('|').

    Conceptually the same happens now in Dogelog player
    and formerly Jekejeke Prolog, although Jekejeke Prolog does it
    in Java, whereas Dogelog player does it in Prolog itself,

    since also the tokenizer is 100% Prolog. So you could lookup
    this part as well and find it "specified" in Prolog. Or lookup
    some other Prolog or non-Prolog implementation.

    Mostowski Collapse schrieb am Mittwoch, 23. Februar 2022 um 10:49:58 UTC+1:
    I have the impression many Prolog systems have it or had it, and maybe
    it slipped the ISO core standard or the Ulrich Neumerkel test cases, otherwise
    I cannot explain how mode declarations such as append(+, +, -)

    were/are handled? The is_stopper/1 doesn't change when something is a
    prefix operator, its a conservative extension concerning the accepted sentences by the language grammar.

    It only changes when something is not a prefix operator. It produces
    less many errors, i.e. the cryptic incomplete_reduction error by Scryer Prolog goes away. It does so in a very simple and efficient way, not

    needing some extra look ahead or complicated algorithm.
    Mostowski Collapse schrieb am Mittwoch, 23. Februar 2022 um 10:48:07 UTC+1:
    It is extremly trivial as the is_stopper/1 source code shows,
    it can be verbalized as follows:

    /**
    * Dont use the grammar production prefix_op term, when term is
    * anyway no term determined by looking at the current token.
    */
    And when in doubt, you can just try it online:

    ?- X = (- - a), write_canonical(X), nl.
    -(-(a))
    X = - -a.
    ?- X = (- - -), write_canonical(X), nl.
    -(-(-))
    X = - - - .

    http://www.xlog.ch/izytab/doclet/docs/18_live/10_reference/example01/package.html

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mostowski Collapse@21:1/5 to All on Thu Mar 3 07:51:54 2022
    I got just new interest in the issue of a living standard.
    I found more evidence that Prolog systems or Prolog
    related languages implement something more elaborate

    than what a certain interpretation of the ISO core standard
    would gives. New use case, the Mercury language state
    variables notation, which uses ! prefix:

    main(!IO) :-
    io.write_string("The 100th prime is ", !IO),
    X = prime(100),
    io.write_int(X, !IO),
    io.nl(!IO). https://www.mercurylang.org/information/doc-latest/mercury_ref/State-variables.html#State-variables

    Bringing the above to Prolog, you will possibly get scolded by
    the ISO core standard orthodoxy fighters. As soon as ! is a prefix,
    according to the orthodoxy fighters, whos names I do not want to

    mention, you have to write (!) in your ordinary code, for the ordinary cut.

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mostowski Collapse@21:1/5 to Mostowski Collapse on Fri Mar 4 18:23:28 2022
    But putting aside how pPEG was implement. It is not
    fully used. The SWIPL example uses the formal grammar
    only for tokenization? Or something between tokenization

    and parsing. Then something interesting happens in a second
    pass and a separate Prolog text, not anymore pPEG based, the
    parsed expression is flattened and then rebuilt again only then

    using operators priority. So pPEG was not chosen to parse
    the SWIPL dialect itself directly?

    Mostowski Collapse schrieb am Samstag, 5. März 2022 um 03:21:23 UTC+1:
    So there is a new study object, SWI-Prolog parser/scanner
    reverse engineered into partially pPEG and manual Prolog code.

    https://github.com/ridgeworks/pPEGpl/tree/main/Examples/SWIP-grammar

    It becomes now apparent why SWI-Prolog is quite some dialect.
    A lot of Prolog coding! Cudos. Trying to understand the example.

    Historical backround why I am asking. The old DEC-10 Prolog
    manual had a DCG specification of the Prolog syntax, which can
    be turned into a direct Prolog parser, unless maybe when the

    dialect is too far away. And pPEG can be more directly realized by
    using DCG (\+)/1 for the non consuming features of pPEG and
    by using DCG (!)/0 for the commited choice features of pPEG,

    making pPEG anyway a rip-off of DCG. So I would imagine
    a transpiler from pPEG to DCG, a path that was not chosen,
    possibly because more complex threaded state.
    Mostowski Collapse schrieb am Donnerstag, 3. März 2022 um 16:51:56 UTC+1:
    I got just new interest in the issue of a living standard.
    I found more evidence that Prolog systems or Prolog
    related languages implement something more elaborate

    than what a certain interpretation of the ISO core standard
    would gives. New use case, the Mercury language state
    variables notation, which uses ! prefix:

    main(!IO) :-
    io.write_string("The 100th prime is ", !IO),
    X = prime(100),
    io.write_int(X, !IO),
    io.nl(!IO). https://www.mercurylang.org/information/doc-latest/mercury_ref/State-variables.html#State-variables

    Bringing the above to Prolog, you will possibly get scolded by
    the ISO core standard orthodoxy fighters. As soon as ! is a prefix, according to the orthodoxy fighters, whos names I do not want to

    mention, you have to write (!) in your ordinary code, for the ordinary cut.

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mostowski Collapse@21:1/5 to Mostowski Collapse on Fri Mar 4 18:21:21 2022
    So there is a new study object, SWI-Prolog parser/scanner
    reverse engineered into partially pPEG and manual Prolog code.

    https://github.com/ridgeworks/pPEGpl/tree/main/Examples/SWIP-grammar

    It becomes now apparent why SWI-Prolog is quite some dialect.
    A lot of Prolog coding! Cudos. Trying to understand the example.

    Historical backround why I am asking. The old DEC-10 Prolog
    manual had a DCG specification of the Prolog syntax, which can
    be turned into a direct Prolog parser, unless maybe when the

    dialect is too far away. And pPEG can be more directly realized by
    using DCG (\+)/1 for the non consuming features of pPEG and
    by using DCG (!)/0 for the commited choice features of pPEG,

    making pPEG anyway a rip-off of DCG. So I would imagine
    a transpiler from pPEG to DCG, a path that was not chosen,
    possibly because more complex threaded state.

    Mostowski Collapse schrieb am Donnerstag, 3. März 2022 um 16:51:56 UTC+1:
    I got just new interest in the issue of a living standard.
    I found more evidence that Prolog systems or Prolog
    related languages implement something more elaborate

    than what a certain interpretation of the ISO core standard
    would gives. New use case, the Mercury language state
    variables notation, which uses ! prefix:

    main(!IO) :-
    io.write_string("The 100th prime is ", !IO),
    X = prime(100),
    io.write_int(X, !IO),
    io.nl(!IO). https://www.mercurylang.org/information/doc-latest/mercury_ref/State-variables.html#State-variables

    Bringing the above to Prolog, you will possibly get scolded by
    the ISO core standard orthodoxy fighters. As soon as ! is a prefix, according to the orthodoxy fighters, whos names I do not want to

    mention, you have to write (!) in your ordinary code, for the ordinary cut.

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mostowski Collapse@21:1/5 to All on Sat Mar 5 13:42:39 2022
    Such 100% Prolog tokenizers and parsers are quite interesting. One could attempt a multi-Prolog that can read various dialects of Prolog systems.
    But if you would do that, you would possibly choose some

    framework and model all Prolog system dialects in this framework?
    Become independent of the other Prolog systems and its other
    plattform. On the other hand one could of course spawn the other

    Prolog system, consut there and call some listing/1 or write_canonical/1
    to get the Prolog text. Wasn’t Logtalk working on a package exchange.
    A package could have a tag in which dialect it is implemented and

    a multi-Prolog could act accordingly.

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mostowski Collapse@21:1/5 to Mostowski Collapse on Sun Mar 6 03:57:53 2022
    But this syntax enhancement will possibly not come in
    release 0.9.8, too much other stuff to do. Also if Rick Workmans
    reverse engineering where end-to-end grammarly specified,

    also using some grammar notation for the operator
    building phase, it would be easier to asses from paper
    reading allone whether some ideas work or not,

    currently its not end-to-end gammarly specified, we find:

    properties such as precedence and associativity are part of the
    semantics and will be addressed in post-parsing semantic analysis.
    https://github.com/ridgeworks/pPEGpl/tree/main/Examples/SWIP-grammar

    But usually this is not called semantics. If your operator building
    pass turns surface S op T into op(S,T) thats not really semantics,
    although some communities might like to call it so.

    Specifications that are more grammarly are:

    DEC-10 Prolog Manual (1982 University of Edinburgh, Dept of Artificial Intelligence)
    https://www.cs.cmu.edu/afs/cs/project/ai-repository/ai/lang/prolog/doc/intro/prolog.doc

    Tau Prolog
    http://tau-prolog.org/files/doc/grammar-specification.pdf

    ISO Core Standard
    Have to recheck how it casts the operator building...

    Mostowski Collapse schrieb am Sonntag, 6. März 2022 um 12:49:17 UTC+1:
    Living standard Prolog systems could also solve the package
    exchange problem. The packages would not have a dialect tag,
    the Prolog system would be polyglott enough to understand

    a more flexible Prolog syntax. For example SWI-Prolog allows me to do, something that is often used in TPTP syntax:

    /* SWI-Prolog (threaded, 64 bits, version 8.5.1) */
    ?- [user].
    p(A :- B) :- q(A), r(B).
    ^D

    In another Prolog system this is not accepted:

    /* TauProlog 0.3.2 (beta) */

    /* In Program Textarea */
    p(A :- B) :- q(A), r(B).

    /* Press Reconsult program */
    error parsing program: error(syntax_error(, or ) expected),[line(2),column(4),found(:-)])

    But from reading Rick Workman reverse engineering of
    SWI-Prolog dialect, I have now indeed an idea how this happens.
    I guess I could try an according modification for the Dogelog player,

    so that Dogelog player would be another living standard Prolog system. Currently Dogelog player is already polyglott in some other corners of
    the Prolog syntax, but not yet in this corner.
    Mostowski Collapse schrieb am Samstag, 5. März 2022 um 22:42:40 UTC+1:
    Such 100% Prolog tokenizers and parsers are quite interesting. One could attempt a multi-Prolog that can read various dialects of Prolog systems. But if you would do that, you would possibly choose some

    framework and model all Prolog system dialects in this framework?
    Become independent of the other Prolog systems and its other
    plattform. On the other hand one could of course spawn the other

    Prolog system, consut there and call some listing/1 or write_canonical/1 to get the Prolog text. Wasn’t Logtalk working on a package exchange.
    A package could have a tag in which dialect it is implemented and

    a multi-Prolog could act accordingly.

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mostowski Collapse@21:1/5 to Mostowski Collapse on Sun Mar 6 03:49:15 2022
    Living standard Prolog systems could also solve the package
    exchange problem. The packages would not have a dialect tag,
    the Prolog system would be polyglott enough to understand

    a more flexible Prolog syntax. For example SWI-Prolog allows me to do, something that is often used in TPTP syntax:

    /* SWI-Prolog (threaded, 64 bits, version 8.5.1) */
    ?- [user].
    p(A :- B) :- q(A), r(B).
    ^D

    In another Prolog system this is not accepted:

    /* TauProlog 0.3.2 (beta) */

    /* In Program Textarea */
    p(A :- B) :- q(A), r(B).

    /* Press Reconsult program */
    error parsing program: error(syntax_error(, or ) expected),[line(2),column(4),found(:-)])

    But from reading Rick Workman reverse engineering of
    SWI-Prolog dialect, I have now indeed an idea how this happens.
    I guess I could try an according modification for the Dogelog player,

    so that Dogelog player would be another living standard Prolog system. Currently Dogelog player is already polyglott in some other corners of
    the Prolog syntax, but not yet in this corner.

    Mostowski Collapse schrieb am Samstag, 5. März 2022 um 22:42:40 UTC+1:
    Such 100% Prolog tokenizers and parsers are quite interesting. One could attempt a multi-Prolog that can read various dialects of Prolog systems.
    But if you would do that, you would possibly choose some

    framework and model all Prolog system dialects in this framework?
    Become independent of the other Prolog systems and its other
    plattform. On the other hand one could of course spawn the other

    Prolog system, consut there and call some listing/1 or write_canonical/1
    to get the Prolog text. Wasn’t Logtalk working on a package exchange.
    A package could have a tag in which dialect it is implemented and

    a multi-Prolog could act accordingly.

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mostowski Collapse@21:1/5 to All on Sat Apr 9 03:51:12 2022
    Now I found a test case where SWI-Prolog and
    Scryer Prolog differ in parsing:

    /* SWI-Prolog */
    ?- op(9,fy,fy), op(9,yfx,yfx).
    true.

    ?- X = (fy 1 yfx 2), write_canonical(X), nl.
    yfx(fy(1),2)

    But then:

    /* Scryer Prolog */
    ?- op(9,fy,fy), op(9,yfx,yfx).
    true.

    ?- X = (fy 1 yfx 2), write_canonical(X), nl.
    fy(yfx(1,2))

    Was worried what Dogelog Player does. But it seems Dogelog Player
    sides with Scryer Prolog, also GNU Prolog, Tau Prolog and
    formerly Jekejeke Prolog do.

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mostowski Collapse@21:1/5 to Mostowski Collapse on Sat Apr 9 05:17:15 2022
    Can he use his SWIPL example to figure out whats going wrong here:

    /* SWI-Prolog */
    ?- op(9,fy,fy), op(9,yfx,yfx).
    true.

    ?- X = (fy 1 yfx 2), write_canonical(X), nl.
    yfx(fy(1),2)

    Maybe its just a small bug, like (>=)/2 instead of (>)/2 or somesuch.

    I am refering to: https://github.com/ridgeworks/pPEGpl/tree/main/Examples/SWIP-grammar

    Mostowski Collapse schrieb am Samstag, 9. April 2022 um 12:51:13 UTC+2:
    Now I found a test case where SWI-Prolog and
    Scryer Prolog differ in parsing:

    /* SWI-Prolog */
    ?- op(9,fy,fy), op(9,yfx,yfx).
    true.

    ?- X = (fy 1 yfx 2), write_canonical(X), nl.
    yfx(fy(1),2)

    But then:

    /* Scryer Prolog */
    ?- op(9,fy,fy), op(9,yfx,yfx).
    true.

    ?- X = (fy 1 yfx 2), write_canonical(X), nl.
    fy(yfx(1,2))

    Was worried what Dogelog Player does. But it seems Dogelog Player
    sides with Scryer Prolog, also GNU Prolog, Tau Prolog and
    formerly Jekejeke Prolog do.

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mostowski Collapse@21:1/5 to Mostowski Collapse on Sun Apr 10 13:39:26 2022
    Yet another bug, which is even a test case from
    the ISO core standard, its the 4-th example from
    Table 6 - Equivalent Terms:

    /* SWI-Prolog */
    ?- op(9,fy,fy), op(9,yf,yf).
    true.
    ?- X = (fy 2 yf), write_canonical(X), nl.
    yf(fy(2))
    X = fy 2 yf.

    On the other hand:

    /* GNU Prolog */
    ?- op(9,fy,fy), op(9,yf,yf).
    yes
    ?- X = (fy 2 yf), write_canonical(X), nl.
    fy(yf(2))
    X = fy 2 yf

    My suspicion, in terms of https://github.com/ridgeworks/pPEGpl/tree/main/Examples/SWIP-grammar

    These here are probably wrong:

    op_associativityEq(fy,yfx,left).
    op_associativityEq(fy,yf,left).

    Actually I don’t know exactly, I am new to this code. Whats
    especially difficult for me, to specify a change, even if I
    can locate the error, I don’t know what to do as a fix?

    But I guess more extensive testing would be needed to find
    all table errors. I have only spotted two, because of analogy
    between yfx and yf. But maybe there are more nasty bugs?

    Mostowski Collapse schrieb am Samstag, 9. April 2022 um 14:17:17 UTC+2:
    Can he use his SWIPL example to figure out whats going wrong here:
    /* SWI-Prolog */
    ?- op(9,fy,fy), op(9,yfx,yfx).
    true.

    ?- X = (fy 1 yfx 2), write_canonical(X), nl.
    yfx(fy(1),2)
    Maybe its just a small bug, like (>=)/2 instead of (>)/2 or somesuch.

    I am refering to: https://github.com/ridgeworks/pPEGpl/tree/main/Examples/SWIP-grammar Mostowski Collapse schrieb am Samstag, 9. April 2022 um 12:51:13 UTC+2:
    Now I found a test case where SWI-Prolog and
    Scryer Prolog differ in parsing:

    /* SWI-Prolog */
    ?- op(9,fy,fy), op(9,yfx,yfx).
    true.

    ?- X = (fy 1 yfx 2), write_canonical(X), nl.
    yfx(fy(1),2)

    But then:

    /* Scryer Prolog */
    ?- op(9,fy,fy), op(9,yfx,yfx).
    true.

    ?- X = (fy 1 yfx 2), write_canonical(X), nl.
    fy(yfx(1,2))

    Was worried what Dogelog Player does. But it seems Dogelog Player
    sides with Scryer Prolog, also GNU Prolog, Tau Prolog and
    formerly Jekejeke Prolog do.

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mostowski Collapse@21:1/5 to All on Sun Apr 10 14:22:46 2022
    But now things get funky, this example does also not work.
    Is there a systemic error in the SWI-Prolog table or its handling?
    In that something is systematically flipped by some error that

    happend once? Here the result, doesn’t agree with Table 6:

    /* SWI-Prolog */
    ?- op(9,xfy,xfy), op(9,yfx,yfx).
    true.

    ?- X = (1 xfy 2 yfx 3), write_canonical(X), nl.
    yfx(xfy(1,2),3)
    X = 1 xfy 2 yfx 3.

    On the other hand, this agrees:

    /* GNU Prolog */
    ?- op(9,xfy,xfy), op(9,yfx,yfx).
    yes
    ?- X = (1 xfy 2 yfx 3), write_canonical(X), nl.
    xfy(1,yfx(2,3))
    X = 1 xfy 2 yfx 3

    Also changing the associativity rule tables of the parser, what will
    happen to the unparser in SWI-Prolog? Does it use the same
    associativity rule tables, from a single point?

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mostowski Collapse@21:1/5 to All on Mon Apr 11 01:50:30 2022
    Is it a sign, that the SWI-Prolog parser/unparser wasn’t built
    from a master class in test driven development? Well testing
    input/output in Prolog system can be a headache.

    I have a new take on a corresponding harness. This is quite
    interesting. It is a harness tailored towards Dogelog Player,
    which unlike formerly Jekejeke Prolog does NOT ASSUME:

    - Memory Files: For Dogelog Player we do NOT ASSUME
    to have access as we did in formerly Jekejeke Prolog. So
    a memory file is simulated by memory.txt, ordinary file.

    - setup_call_cleanup/3: For Dogelog Player we currently do
    NOT ASSUME, although such a predicate might come later.
    In formerly Jekejeke Prolog the harness uses this.

    So how do we check with output to? Here is our new take:

    /**
    * with_text_to(A, G):
    * The predicate succeeds whenever the goal G succeeds and
    * unifies A with its text output.
    */
    % with_text_to(-Atom, +Goal)
    with_text_to(A, G) :-
    current_output(S),
    try_call_finally(
    redirect_text_output,
    G,
    fetch_text_output(S, A)).

    % redirect_text_output
    redirect_text_output :-
    open('memory.txt', write, S),
    set_output(S).

    % fetch_text_output(+Stream, -Atom)
    fetch_text_output(S, A) :-
    current_output(T),
    close(T),
    open('memory.txt', read, R),
    get_atom(R, -1, A),
    close(R),
    set_output(S).

    And then:

    /**
    * try_call_finally(T, G, F):
    * The predicate succeeds whenever G succeeds. The goal T is
    * called for the call and redo port. The goal F is called for
    * the exit, fail and error port.
    */
    % try_call_finally(+Goal, +Goal, +Goal)
    try_call_finally(T, G, F) :-
    (T; F, fail),
    '$MARK'(X),
    catch(G, E, (F, throw(E))),
    '$MARK'(Y),
    (X == Y -> !, F; (F; T, fail)).

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mostowski Collapse@21:1/5 to Mostowski Collapse on Mon Apr 11 10:56:25 2022
    It should be noted that we added a new built-in
    to Dogelog Player, get_atom/3. This is a kind of
    read_line/2, but with a different semantic than the

    read line we had so far. get_atom/3 can be used
    to read line via get_atom(S, 0'\n, X), and it can
    be also used to read full files get_atom(S, -1, X).

    The difference to our old read line, when using
    get_atom(S, 0'\n, X) it will include the 0'\n in
    the result. A big surprise was now the harness

    for with input from. It uses change_arg/3 !!!

    /**
    * with_text_from(A, G):
    * The predicate succeeds whenever the goal G succeeds and
    * provides A as its text input.
    */
    % with_text_from(+Atom, +Goal)
    with_text_from(A, G) :-
    current_input(S),
    H = v(A),
    try_call_finally(
    redirect_text_input(H),
    G,
    advance_text_input(S, H)).

    % redirect_text_input(+Compound)
    redirect_text_input(H) :-
    arg(1, H, A),
    open('memory.txt', write, S),
    put_atom(S, A),
    close(S),
    open('memory.txt', read, T),
    set_input(T).

    % advance_text_input(+Stream, +Compound)
    advance_text_input(S, H) :-
    current_input(T),
    get_atom(T, -1, A),
    close(T),
    change_arg(1, H, A),
    set_input(S).

    The source code of these Dogelog Player testing utilities
    is open sourced in a new folder dogelog_comply:

    Prolog Text "charsio" - Compliance Dogelog Spieler http://pages.xlog.ch/littab/doclet/docs/10_samples/04_doge_comply/reference/harness/charsio.html

    Mostowski Collapse schrieb:
    Is it a sign, that the SWI-Prolog parser/unparser wasn’t built
    from a master class in test driven development? Well testing
    input/output in Prolog system can be a headache.

    I have a new take on a corresponding harness. This is quite
    interesting. It is a harness tailored towards Dogelog Player,
    which unlike formerly Jekejeke Prolog does NOT ASSUME:

    - Memory Files: For Dogelog Player we do NOT ASSUME
    to have access as we did in formerly Jekejeke Prolog. So
    a memory file is simulated by memory.txt, ordinary file.

    - setup_call_cleanup/3: For Dogelog Player we currently do
    NOT ASSUME, although such a predicate might come later.
    In formerly Jekejeke Prolog the harness uses this.

    So how do we check with output to? Here is our new take:

    /**
    * with_text_to(A, G):
    * The predicate succeeds whenever the goal G succeeds and
    * unifies A with its text output.
    */
    % with_text_to(-Atom, +Goal)
    with_text_to(A, G) :-
    current_output(S),
    try_call_finally(
    redirect_text_output,
    G,
    fetch_text_output(S, A)).

    % redirect_text_output
    redirect_text_output :-
    open('memory.txt', write, S),
    set_output(S).

    % fetch_text_output(+Stream, -Atom)
    fetch_text_output(S, A) :-
    current_output(T),
    close(T),
    open('memory.txt', read, R),
    get_atom(R, -1, A),
    close(R),
    set_output(S).

    And then:

    /**
    * try_call_finally(T, G, F):
    * The predicate succeeds whenever G succeeds. The goal T is
    * called for the call and redo port. The goal F is called for
    * the exit, fail and error port.
    */
    % try_call_finally(+Goal, +Goal, +Goal)
    try_call_finally(T, G, F) :-
    (T; F, fail),
    '$MARK'(X),
    catch(G, E, (F, throw(E))),
    '$MARK'(Y),
    (X == Y -> !, F; (F; T, fail)).


    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mostowski Collapse@21:1/5 to All on Mon Apr 11 03:04:55 2022
    This is probably not the canary in the coal mine for the
    suspected bugs. One can check by himself/herself, not
    a single use of fy or yfx operator:

    ALE – Attribute Logic Engine http://www.cs.toronto.edu/~gpenn/ale/files/ale.pl

    Maybe I can dig out an TPTP example, currently working
    with the normal test cases that circulate, that are more abstract.
    The trouble maker is this here from Phil Zucker:

    :- op( 500, fy, !). % universal quantifier: ![X]:
    :- op( 500, fy, ?). % existential quantifier: ?[X]:
    :- op( 500,xfy, :).

    If you change the later into:

    :- op( 500,yfx, :).

    You get a difference in SWI-Prolog and SICStus Prolog:

    /* SWI-Prolog (threaded, 64 bits, version 8.5.8) */
    ?- X = (![Y]:p(Y)), write_canonical(X), nl.
    :(!([A]),p(A))
    X = ![Y]:p(Y).

    /* SICStus 4.7.1 (x86_64-win32-nt-4) */
    ?- X = (![Y]:p(Y)), write_canonical(X), nl.
    !(:('.'(_953,[]),p(_953)))
    X = ![Y]:p(Y) ?

    Note the difference, SWI-Prolog gives :(!(...) whereas SICStus Prolog
    gives !(:(...). So the same SICStus Prolog code that would use a !_
    pattern somewhere in his Prolog clauses, doesn’t run in SWI-Prolog.

    There are LeanTap variants that use such patterns

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mostowski Collapse@21:1/5 to Mostowski Collapse on Mon Apr 11 03:17:25 2022
    Basically you get a **silent error**. Everything parses
    fine, the Prolog text can be prepared for execution,
    your code just stops working correctly, when

    migrating from SICStus Prolog to SWI-Prolog.

    Mostowski Collapse schrieb am Montag, 11. April 2022 um 12:04:56 UTC+2:
    This is probably not the canary in the coal mine for the
    suspected bugs. One can check by himself/herself, not
    a single use of fy or yfx operator:

    ALE – Attribute Logic Engine http://www.cs.toronto.edu/~gpenn/ale/files/ale.pl

    Maybe I can dig out an TPTP example, currently working
    with the normal test cases that circulate, that are more abstract.
    The trouble maker is this here from Phil Zucker:

    :- op( 500, fy, !). % universal quantifier: ![X]:
    :- op( 500, fy, ?). % existential quantifier: ?[X]:
    :- op( 500,xfy, :).

    If you change the later into:

    :- op( 500,yfx, :).

    You get a difference in SWI-Prolog and SICStus Prolog:

    /* SWI-Prolog (threaded, 64 bits, version 8.5.8) */
    ?- X = (![Y]:p(Y)), write_canonical(X), nl.
    :(!([A]),p(A))
    X = ![Y]:p(Y).

    /* SICStus 4.7.1 (x86_64-win32-nt-4) */
    ?- X = (![Y]:p(Y)), write_canonical(X), nl.
    !(:('.'(_953,[]),p(_953)))
    X = ![Y]:p(Y) ?

    Note the difference, SWI-Prolog gives :(!(...) whereas SICStus Prolog
    gives !(:(...). So the same SICStus Prolog code that would use a !_
    pattern somewhere in his Prolog clauses, doesn’t run in SWI-Prolog.

    There are LeanTap variants that use such patterns

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mostowski Collapse@21:1/5 to Mostowski Collapse on Tue Apr 12 19:27:20 2022
    Just joking, the business is basically finished, I have now:

    Dogelog Player is now at 80% of Testing its Predicates https://twitter.com/dogelogch/status/1514036461968015362

    Dogelog Player is now at 80% of Testing its Predicates https://www.facebook.com/groups/dogelog

    Mostowski Collapse schrieb am Mittwoch, 13. April 2022 um 04:24:01 UTC+2:
    Suddently, in a flash of light, thanks to Mr Peter Ludemann,
    my guardian angle, the good shepherd, I saw that my whole
    life was a lie. Why did I become so deeply absorbed with

    the parsing problem? Ok, I will stop from now on. LoL
    Mostowski Collapse schrieb am Montag, 11. April 2022 um 12:17:26 UTC+2:
    Basically you get a **silent error**. Everything parses
    fine, the Prolog text can be prepared for execution,
    your code just stops working correctly, when

    migrating from SICStus Prolog to SWI-Prolog.

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mostowski Collapse@21:1/5 to Mostowski Collapse on Tue Apr 12 19:23:59 2022
    Suddently, in a flash of light, thanks to Mr Peter Ludemann,
    my guardian angle, the good shepherd, I saw that my whole
    life was a lie. Why did I become so deeply absorbed with

    the parsing problem? Ok, I will stop from now on. LoL

    Mostowski Collapse schrieb am Montag, 11. April 2022 um 12:17:26 UTC+2:
    Basically you get a **silent error**. Everything parses
    fine, the Prolog text can be prepared for execution,
    your code just stops working correctly, when

    migrating from SICStus Prolog to SWI-Prolog.

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mostowski Collapse@21:1/5 to Mostowski Collapse on Tue Apr 12 21:32:27 2022
    Here is a funny example in the wild, the authors seems not to have known
    the ridgeworks rules, since he used:

    % Christophe Meudec
    % Eclipse 6.0 program
    :- op(30, fy, [not]). % must be fy for 'not not a' expressions
    :- op(30, yfx, [**, abs]). % must be left to right for 'a ** b ** c' expressions

    https://github.com/echancrure/PTC-Solver/blob/f02c64925fbc06a9f2cbbef252684ebccd5bd217/source/util__post_precedence.pl#L12

    Which is an attempt to model ADA programming language. The poor guy will have quite a surprise when mirgating from ECLiPSe to SWI-Prolog:

    /* ECLiPSe Prolog */
    [eclipse 2]: X = (not not not 2 ** 3 ** 4), write_canonical(X), nl. not(not(not(**(**(2, 3), 4))))

    X = not not not 2 ** 3 ** 4
    Yes (0.00s cpu)

    And then:

    /* SWI-Prolog */
    ?- op(30, fy, not), op(30, yfx, **).
    true.

    ?- X = (not not not 2 ** 3 ** 4), write_canonical(X), nl. **(**(not(not(not(2))),3),4)
    X = not not not 2**3**4.

    If you evaluate the two expressions with bitwise arithmetic you get different results:

    [eclipse 6]: X is \(\(\((2^3)^4))).
    X = -4097

    [eclipse 7]: X is (\(\(\(2)))^3)^4.
    X = 531441

    For ADA operators: https://www.adaic.org/resources/add_content/standards/05rm/html/RM-4-5.html

    Mostowski Collapse schrieb am Mittwoch, 13. April 2022 um 06:30:18 UTC+2:
    Thats quite some news:

    I see the problem corner cases as ones than can be easily avoided
    through judicious operator definitions. Any DSL’s that use such cases
    are asking for trouble IMO.

    Do I understand you correctly. You say avoid certain operator combinations? How would a normal end-user or DSL designer notice them?

    Do they have some special characteristics? Or do you have an explicit list of
    those operator combinations that should be avoided?

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mostowski Collapse@21:1/5 to All on Tue Apr 12 21:30:17 2022
    Thats quite some news:

    I see the problem corner cases as ones than can be easily avoided
    through judicious operator definitions. Any DSL’s that use such cases
    are asking for trouble IMO.

    Do I understand you correctly. You say avoid certain operator combinations?
    How would a normal end-user or DSL designer notice them?

    Do they have some special characteristics? Or do you have an explicit list of those operator combinations that should be avoided?

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mostowski Collapse@21:1/5 to All on Wed Apr 13 02:43:15 2022
    Woke up in the morning and my brain only produced new challenges.

    I am still trying to find a case in the wild in favor of SWI-Prolog. For example if ADA would effectively parse:

    abs x ** y

    As this here:

    **(abs(x), y)

    Then the ISO core standard is somehow not “right”, or lets say more “arbitrary” than
    I tought. Which could be an interesting turn of events.

    The problem with my suggested fix, using “fx” instead “fy”, it does not work when you
    you want to support multiple braketless occurences of an operator.

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mostowski Collapse@21:1/5 to Mostowski Collapse on Wed Apr 13 02:44:19 2022
    Take the pPEG parsers rule:

    op_associativityEq(fy,yfx,left).

    Change it into this:

    op_associativityEq(fy,yfx,left) :- current_prolog_flag(iso, false). op_associativityEq(fy,yfx,right) :- current_prolog_flag(iso, true).

    What will the pPEG parser do now? Is there also a pPEG unparser?

    https://swi-prolog.discourse.group/t/parsing-text-using-a-formal-grammar/5086

    Mostowski Collapse schrieb am Mittwoch, 13. April 2022 um 11:43:16 UTC+2:
    Woke up in the morning and my brain only produced new challenges.

    I am still trying to find a case in the wild in favor of SWI-Prolog. For example if ADA would effectively parse:

    abs x ** y

    As this here:

    **(abs(x), y)

    Then the ISO core standard is somehow not “right”, or lets say more “arbitrary” than
    I tought. Which could be an interesting turn of events.

    The problem with my suggested fix, using “fx” instead “fy”, it does not work when you
    you want to support multiple braketless occurences of an operator.

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mostowski Collapse@21:1/5 to Mostowski Collapse on Wed Apr 13 11:32:50 2022
    Interestingly the standard unparser of SWI-Prolog doesn’t give a damn.
    But this is another defect which I have posted about already in some thread.

    aLSO who_ever wrote this code of pPEG deserves to burn in hell,
    for mixing underscore and camelcase. Took me quite a while to run the query.

    Mostowski Collapse schrieb am Mittwoch, 13. April 2022 um 20:30:53 UTC+2:
    Ok it wurks. I changed pl_parser.pl accordingly, and I now get:

    ?- string_termList("fy 1 yfx 2.", [T]), write_canonical(T), nl.
    yfx(fy(1),2)
    T = fy 1 yfx 2.

    ?- set_prolog_flag(iso, true).
    true.

    ?- string_termList("fy 1 yfx 2.", [T]), write_canonical(T), nl.
    fy(yfx(1,2))
    T = fy 1 yfx 2.

    Eh voila SWI-Prolog has become member of the ISO core standard club.
    Maybe it can even apply for V.I.P. membership, because its so important? Mostowski Collapse schrieb am Mittwoch, 13. April 2022 um 11:44:20 UTC+2:
    Take the pPEG parsers rule:

    op_associativityEq(fy,yfx,left).

    Change it into this:

    op_associativityEq(fy,yfx,left) :- current_prolog_flag(iso, false). op_associativityEq(fy,yfx,right) :- current_prolog_flag(iso, true).

    What will the pPEG parser do now? Is there also a pPEG unparser?

    https://swi-prolog.discourse.group/t/parsing-text-using-a-formal-grammar/5086
    Mostowski Collapse schrieb am Mittwoch, 13. April 2022 um 11:43:16 UTC+2:
    Woke up in the morning and my brain only produced new challenges.

    I am still trying to find a case in the wild in favor of SWI-Prolog. For example if ADA would effectively parse:

    abs x ** y

    As this here:

    **(abs(x), y)

    Then the ISO core standard is somehow not “right”, or lets say more “arbitrary” than
    I tought. Which could be an interesting turn of events.

    The problem with my suggested fix, using “fx” instead “fy”, it does not work when you
    you want to support multiple braketless occurences of an operator.

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mostowski Collapse@21:1/5 to Mostowski Collapse on Wed Apr 13 11:30:52 2022
    Ok it wurks. I changed pl_parser.pl accordingly, and I now get:

    ?- string_termList("fy 1 yfx 2.", [T]), write_canonical(T), nl.
    yfx(fy(1),2)
    T = fy 1 yfx 2.

    ?- set_prolog_flag(iso, true).
    true.

    ?- string_termList("fy 1 yfx 2.", [T]), write_canonical(T), nl.
    fy(yfx(1,2))
    T = fy 1 yfx 2.

    Eh voila SWI-Prolog has become member of the ISO core standard club.
    Maybe it can even apply for V.I.P. membership, because its so important?

    Mostowski Collapse schrieb am Mittwoch, 13. April 2022 um 11:44:20 UTC+2:
    Take the pPEG parsers rule:

    op_associativityEq(fy,yfx,left).

    Change it into this:

    op_associativityEq(fy,yfx,left) :- current_prolog_flag(iso, false). op_associativityEq(fy,yfx,right) :- current_prolog_flag(iso, true).

    What will the pPEG parser do now? Is there also a pPEG unparser?

    https://swi-prolog.discourse.group/t/parsing-text-using-a-formal-grammar/5086 Mostowski Collapse schrieb am Mittwoch, 13. April 2022 um 11:43:16 UTC+2:
    Woke up in the morning and my brain only produced new challenges.

    I am still trying to find a case in the wild in favor of SWI-Prolog. For example if ADA would effectively parse:

    abs x ** y

    As this here:

    **(abs(x), y)

    Then the ISO core standard is somehow not “right”, or lets say more “arbitrary” than
    I tought. Which could be an interesting turn of events.

    The problem with my suggested fix, using “fx” instead “fy”, it does not work when you
    you want to support multiple braketless occurences of an operator.

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mostowski Collapse@21:1/5 to Mostowski Collapse on Wed Apr 13 12:05:43 2022
    Maybe they should organize the ISO core standard club like here:

    Platin Sponsor
    Gold Sponsor
    Silver Sponsor
    https://www.jug.ch/sponsors.php

    Then you can buy different grades of VIPness with Mamon.
    Sad Story: Any poor John Doe Prolog system will be non-VIP.

    Mostowski Collapse schrieb am Mittwoch, 13. April 2022 um 20:32:51 UTC+2:
    Interestingly the standard unparser of SWI-Prolog doesn’t give a damn.
    But this is another defect which I have posted about already in some thread.

    aLSO who_ever wrote this code of pPEG deserves to burn in hell,
    for mixing underscore and camelcase. Took me quite a while to run the query. Mostowski Collapse schrieb am Mittwoch, 13. April 2022 um 20:30:53 UTC+2:
    Ok it wurks. I changed pl_parser.pl accordingly, and I now get:

    ?- string_termList("fy 1 yfx 2.", [T]), write_canonical(T), nl. yfx(fy(1),2)
    T = fy 1 yfx 2.

    ?- set_prolog_flag(iso, true).
    true.

    ?- string_termList("fy 1 yfx 2.", [T]), write_canonical(T), nl. fy(yfx(1,2))
    T = fy 1 yfx 2.

    Eh voila SWI-Prolog has become member of the ISO core standard club.
    Maybe it can even apply for V.I.P. membership, because its so important? Mostowski Collapse schrieb am Mittwoch, 13. April 2022 um 11:44:20 UTC+2:
    Take the pPEG parsers rule:

    op_associativityEq(fy,yfx,left).

    Change it into this:

    op_associativityEq(fy,yfx,left) :- current_prolog_flag(iso, false). op_associativityEq(fy,yfx,right) :- current_prolog_flag(iso, true).

    What will the pPEG parser do now? Is there also a pPEG unparser?

    https://swi-prolog.discourse.group/t/parsing-text-using-a-formal-grammar/5086
    Mostowski Collapse schrieb am Mittwoch, 13. April 2022 um 11:43:16 UTC+2:
    Woke up in the morning and my brain only produced new challenges.

    I am still trying to find a case in the wild in favor of SWI-Prolog. For
    example if ADA would effectively parse:

    abs x ** y

    As this here:

    **(abs(x), y)

    Then the ISO core standard is somehow not “right”, or lets say more “arbitrary” than
    I tought. Which could be an interesting turn of events.

    The problem with my suggested fix, using “fx” instead “fy”, it does not work when you
    you want to support multiple braketless occurences of an operator.

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mostowski Collapse@21:1/5 to All on Thu Apr 14 07:58:48 2022
    Transfering pPEG results back to C code is not self
    evident. The pPEG parser could be a blessing, but it
    could be also a further curse.

    We don’t know what the pPEG parser does. For example
    I don’t find the op_associativityEq/3 table in pl-read.c.
    Where it you get it from? Also very simple examples

    don’t work in the pPEG parser:

    ?- string_termList("(- -1).", [T]), write_canonical(T), nl.
    -(-,1)
    T = (-)-1.

    ?- X = (- -1), write_canonical(X), nl.
    -(-1)
    X = - -1.

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mostowski Collapse@21:1/5 to Mostowski Collapse on Thu Apr 14 11:18:52 2022
    I will not touch pPEG anymore, even not with tweezers,
    until it comes with a test suite, in the same folder like where the
    source code is housed. At least this is what Ulrich Neumerkel did

    for ISO core standard prolog, and which serves as a point of orientation.
    Now we have for SWI-Prolog dialect nor the pPEG dialect any point of orientation. Its just arbitary code uploaded to the internet. Although I think

    SWI-Prolog might be in a better situation. Not sure, it has plunit and maybe
    it has somewhere read test cases? But it has only with_output_to/2, and
    no with_input_from/2. How is parsing tested? I never did dig up some

    SWI-Prolog read test cases, maybe there are some? Thats of course my fault.

    Mostowski Collapse schrieb am Donnerstag, 14. April 2022 um 16:58:50 UTC+2:
    Transfering pPEG results back to C code is not self
    evident. The pPEG parser could be a blessing, but it
    could be also a further curse.

    We don’t know what the pPEG parser does. For example
    I don’t find the op_associativityEq/3 table in pl-read.c.
    Where it you get it from? Also very simple examples

    don’t work in the pPEG parser:

    ?- string_termList("(- -1).", [T]), write_canonical(T), nl.
    -(-,1)
    T = (-)-1.

    ?- X = (- -1), write_canonical(X), nl.
    -(-1)
    X = - -1.

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mostowski Collapse@21:1/5 to All on Thu Apr 14 15:35:25 2022
    What I could exclude as a source of error, is ordering of
    the operator table itself. At least for SWI-Prolog C code it does not
    have an impact, which sequence of operator definitions I use:

    This sequence of op/3 calls:

    ?- op(9, fy, fy), op(9, yfx, yfx).
    true.

    ?- X = (fy 1 yfx 2), write_canonical(X), nl.
    yfx(fy(1),2)
    X = fy 1 yfx 2.

    And this sequence of op/3 calls, give the same:

    ?- op(9, yfx, yfx), op(9, fy, fy).
    true.

    ?- X = (fy 1 yfx 2), write_canonical(X), nl.
    yfx(fy(1),2)
    X = fy 1 yfx 2.

    This does not exclude the possibility, that reordering the
    operator table, inside SWI-Prolog C code, wouldn’t give
    another result. It only shows that op/3 cannot confuse the parser.

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mostowski Collapse@21:1/5 to Mostowski Collapse on Thu Apr 14 15:38:57 2022
    Here is an example where operator table ordering, respective
    reduction rules ordering, influence the reduction result.
    Reduction rules ordered like this:

    [fy,X] ~> [fy(X)].
    [X,yfx,Y] ~> [yfx(X,Y)].

    ?- reduce([fy,1,yfx,2],X), write_canonical(X), nl.
    [yfx(fy(1),2)]
    X = [fy 1 yfx 2].

    Or the same reduction rules ordered like this, gives a different result:

    [X,yfx,Y] ~> [yfx(X,Y)].
    [fy,X] ~> [fy(X)].

    ?- reduce([fy,1,yfx,2],X), write_canonical(X), nl.
    [fy(yfx(1,2))]
    X = [fy 1 yfx 2].

    The reducer code itself is here below, it has a cut (!), so its
    sensitive to the reduction rule ordering:

    :- op(1200,xfx,~>).

    reduce(X, Y) :-
    (A ~> B),
    append(U, V, X),
    append(A, H, V),
    append(B, H, W),
    append(U, W, Z), !, reduce(Z, Y).
    reduce(X, X).

    Mostowski Collapse schrieb am Freitag, 15. April 2022 um 00:35:26 UTC+2:
    What I could exclude as a source of error, is ordering of
    the operator table itself. At least for SWI-Prolog C code it does not
    have an impact, which sequence of operator definitions I use:

    This sequence of op/3 calls:

    ?- op(9, fy, fy), op(9, yfx, yfx).
    true.

    ?- X = (fy 1 yfx 2), write_canonical(X), nl.
    yfx(fy(1),2)
    X = fy 1 yfx 2.

    And this sequence of op/3 calls, give the same:

    ?- op(9, yfx, yfx), op(9, fy, fy).
    true.

    ?- X = (fy 1 yfx 2), write_canonical(X), nl.
    yfx(fy(1),2)
    X = fy 1 yfx 2.

    This does not exclude the possibility, that reordering the
    operator table, inside SWI-Prolog C code, wouldn’t give
    another result. It only shows that op/3 cannot confuse the parser.

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mostowski Collapse@21:1/5 to Mostowski Collapse on Fri Apr 15 03:39:18 2022
    The fuzzer code is here:

    :- op(9, xfx, xfx).
    :- op(9, yfx, yfx).
    :- op(9, xfy, xfy).
    :- op(9, fx, fx).
    :- op(9, fy, fy).
    :- op(9, xf, xf).
    :- op(9, yf, yf).

    % random_expr(+Integer, -Integer, -Atom)
    random_expr(N, M, A) :-
    K is 10+N*5,
    random(0, K, I),
    random_action(I, N, M, A).

    % random_expr(+Integer, +Integer, -Integer, -Atom)
    random_action(0, N, M, A) :- !,
    random_expr(N, H, B),
    random_expr(H, M, C),
    atom_concat(B, ' xfx ', D),
    atom_concat(D, C, A).
    random_action(1, N, M, A) :- !,
    random_expr(N, H, B),
    random_expr(H, M, C),
    atom_concat(B, ' yfx ', D),
    atom_concat(D, C, A).
    random_action(2, N, M, A) :- !,
    random_expr(N, H, B),
    random_expr(H, M, C),
    atom_concat(B, ' xfy ', D),
    atom_concat(D, C, A).
    random_action(3, N, M, A) :- !,
    random_expr(N, M, B),
    atom_concat('fx ', B, A).
    random_action(4, N, M, A) :- !,
    random_expr(N, M, B),
    atom_concat('fy ', B, A).
    random_action(5, N, M, A) :- !,
    random_expr(N, M, B),
    atom_concat(B, ' xf', A).
    random_action(6, N, M, A) :- !,
    random_expr(N, M, B),
    atom_concat(B, ' yf', A).
    random_action(_, N, M, A) :-
    number_codes(N, L),
    atom_codes(A, L),
    M is N+1.

    Mostowski Collapse schrieb am Freitag, 15. April 2022 um 12:38:29 UTC+2:
    Using a fuzzer, I find differences what SWI-Prolog native C code
    considers an operator clash and what the pPEG SWIPL examples
    considers an operator clash. It seems pPEG is more tolerant.

    There are also some fundamental differences in what
    Prolog terms the SWI-Prolog native C code builds, and what
    the pPEG SWIPL example builds.

    This is how I used the fuzzer:

    ?- between(1,100,_), random_expr(0, _, A), swi_parse(A, X),
    ppeg_parse(A, Y), X \== Y, write('expr: '), write(A), write('\nswi: '), write_canonical(X), write('\nppeg: '), write_canonical(Y), nl, nl, fail.

    expr: 0 xfx fy 1 yfx 2 yfx 3
    swi: syntax_error(operator_clash)
    ppeg: xfx(0,yfx(yfx(fy(1),2),3))

    expr: fy fx fx 0
    swi: syntax_error(operator_clash)
    ppeg: fy(fx(fx(0)))

    expr: fy fx 0 yf yf yf
    swi: yf(yf(yf(fy(fx(0)))))
    ppeg: fy(yf(yf(yf(fx(0)))))

    expr: fy 0 xf yfx 1 yfx 2 yf
    swi: yf(yfx(yfx(fy(xf(0)),1),2))
    ppeg: fy(yf(yfx(yfx(xf(0),1),2)))

    false.

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mostowski Collapse@21:1/5 to All on Fri Apr 15 03:38:28 2022
    Using a fuzzer, I find differences what SWI-Prolog native C code
    considers an operator clash and what the pPEG SWIPL examples
    considers an operator clash. It seems pPEG is more tolerant.

    There are also some fundamental differences in what
    Prolog terms the SWI-Prolog native C code builds, and what
    the pPEG SWIPL example builds.

    This is how I used the fuzzer:

    ?- between(1,100,_), random_expr(0, _, A), swi_parse(A, X),
    ppeg_parse(A, Y), X \== Y, write('expr: '), write(A), write('\nswi: '), write_canonical(X), write('\nppeg: '), write_canonical(Y), nl, nl, fail.

    expr: 0 xfx fy 1 yfx 2 yfx 3
    swi: syntax_error(operator_clash)
    ppeg: xfx(0,yfx(yfx(fy(1),2),3))

    expr: fy fx fx 0
    swi: syntax_error(operator_clash)
    ppeg: fy(fx(fx(0)))

    expr: fy fx 0 yf yf yf
    swi: yf(yf(yf(fy(fx(0)))))
    ppeg: fy(yf(yf(yf(fx(0)))))

    expr: fy 0 xf yfx 1 yfx 2 yf
    swi: yf(yfx(yfx(fy(xf(0)),1),2))
    ppeg: fy(yf(yfx(yfx(xf(0),1),2)))

    false.

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mostowski Collapse@21:1/5 to All on Sat Apr 16 17:43:19 2022
    Everybody knows that Prolog doesn't parse
    (a = b = c), this is what operator icon xfx is made
    for. But what is the operator icon fx made for?

    Oh my god, SICStus Prolog tolerates this?

    /* SICStus Prolog 4.7.1 */
    ?- X = (:- :- x0).
    X = ((:-):-x0) ?

    SWI-Prolog and Scryer Prolog are more thight:

    /* Scryer Prolog */
    ?- X = (:- :- x0).
    caught: error(syntax_error(incomplete_reduction),read_term/3:1)

    /* SWI-Prolog */
    ?- X = (:- :- x0).
    ERROR: Syntax error: Operator priority clash

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mostowski Collapse@21:1/5 to Mostowski Collapse on Sat Apr 16 17:50:38 2022
    Now I posted already a tight Prolog reader on SWI-Prolog
    discourse. Here is it in all its glory. It doesn't handle negative
    numbers, but its cute to play around with operator parsing,

    like for example:

    /* SICStus 4.7.1 */
    ?- consult('reader.p').

    ?- reader(T,1200,[:-,x0],[]).
    T = (:-x0) ?

    ?- reader(T,1200,[:-,:-,x0],[]).
    error(syntax_error(operator_clash),_415)

    The code is only one page:

    reader(X, L) -->
    reader_primary(Z, L, K), reader_secondary(Z, X, L, K).

    reader_primary(H, L, R) --> [A], {current_op(R, M, A), is_prefix(M, E)}, !,
    {L < R -> throw(error(syntax_error(operator_clash),_)); true},
    {T is R-E}, reader(Z, T), {H =.. [A,Z]}.
    reader_primary(X, _, 0) --> [X].

    reader_secondary(H, X, L, C) --> [A],
    {current_op(R, M, A), is_infix(M, D, E), L >= R}, !,
    {R-D < C -> throw(error(syntax_error(operator_clash),_)); true},
    {T is R-E}, reader(Z, T),
    {J =.. [A,H,Z]},
    reader_secondary(J, X, L, R).
    reader_secondary(H, X, L, C) --> [A],
    {current_op(R, M, A), is_postfix(M, D), L >= R}, !,
    {R-D < C -> throw(error(syntax_error(operator_clash),_)); true},
    {J =.. [A,H]},
    reader_secondary(J, X, L, R).
    reader_secondary(H, H, _, _) --> [].

    is_infix(xfx, 1, 1).
    is_infix(yfx, 0, 1).
    is_infix(xfy, 1, 0).

    is_prefix(fx, 1).
    is_prefix(fy, 0).

    is_postfix(xf, 1).
    is_postfix(yf, 0).

    Mostowski Collapse schrieb am Sonntag, 17. April 2022 um 02:43:21 UTC+2:
    Everybody knows that Prolog doesn't parse
    (a = b = c), this is what operator icon xfx is made
    for. But what is the operator icon fx made for?

    Oh my god, SICStus Prolog tolerates this?

    /* SICStus Prolog 4.7.1 */
    ?- X = (:- :- x0).
    X = ((:-):-x0) ?

    SWI-Prolog and Scryer Prolog are more thight:

    /* Scryer Prolog */
    ?- X = (:- :- x0).
    caught: error(syntax_error(incomplete_reduction),read_term/3:1)

    /* SWI-Prolog */
    ?- X = (:- :- x0).
    ERROR: Syntax error: Operator priority clash

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mostowski Collapse@21:1/5 to Mostowski Collapse on Mon Apr 18 14:33:19 2022
    My reader prototype sides with SWI-Prolog. Also
    Dogelog Player and formerly Jekejeke Prolog side
    with SWI-Prolog. Dogelog Player can be tried online:

    ?- X = (- :- x0).
    error(syntax_error(operator_clash), [user:0]) error(syntax_error(cannot_start_term), [user:1])
    ?- X = (:- :- x0).
    error(syntax_error(operator_clash), [user:1]) error(syntax_error(cannot_start_term), [user:2]) http://www.xlog.ch/izytab/moblet/docs/18_live/10_reference/example01/package.html

    Unfortunately resyncing after an error is not yet
    implemented, so there are two errors. But we got
    already line numbers for Dogelog Player,

    this is quite a gas!!!

    Mostowski Collapse schrieb am Montag, 18. April 2022 um 23:27:20 UTC+2:
    Holy Cow, ECLiPSe Prolog is somewhere between SWI-Prolog
    and SICStus Prolog, concerning tolerating extra syntax.

    SICStus Prolog, quite tolerant:

    ?- X = (- :- x0).
    X = ((-):-x0) ?
    ?- X = (:- :- x0).
    X = ((:-):-x0) ?
    ECLIPSe Prolog, half way tolerant:

    [eclipse 36]: X = (- :- x0).
    X = ((-) :- x0)
    [eclipse 37]: X = (:- :- x0).
    syntax error: postfix/infix operator expected

    SWI-Prolog, intolerant, good!!!

    ?- X = (- :- x0).
    ERROR: Syntax error: Operator priority clash
    ?- X = (:- :- x0).
    ERROR: Syntax error: Operator priority clash

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mostowski Collapse@21:1/5 to All on Mon Apr 18 14:27:19 2022
    Holy Cow, ECLiPSe Prolog is somewhere between SWI-Prolog
    and SICStus Prolog, concerning tolerating extra syntax.

    SICStus Prolog, quite tolerant:

    ?- X = (- :- x0).
    X = ((-):-x0) ?
    ?- X = (:- :- x0).
    X = ((:-):-x0) ?

    ECLIPSe Prolog, half way tolerant:

    [eclipse 36]: X = (- :- x0).
    X = ((-) :- x0)
    [eclipse 37]: X = (:- :- x0).
    syntax error: postfix/infix operator expected

    SWI-Prolog, intolerant, good!!!

    ?- X = (- :- x0).
    ERROR: Syntax error: Operator priority clash
    ?- X = (:- :- x0).
    ERROR: Syntax error: Operator priority clash

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mostowski Collapse@21:1/5 to All on Fri Apr 29 03:42:19 2022
    More proof that Logtalk is utter nonsense. What
    does the Logtalk test suite even test concerning
    the various "adapters" it has, like Trealla?

    This is a nice gem:

    $ ./tpl -v
    Trealla Prolog (c) Infradig 2020-2022, v1.27.12-31-g3575df
    $ ./tpl
    ?- X = (:- (:- x0)).
    Error: operator clash, line 1
    false.
    ?-

    There is something wrong with Ulrich Neumerkels
    compliance test suite, and maybe some QuickCheck
    resp. Fuzzer approach is needed,

    to chop of all heads of the hydra.

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mostowski Collapse@21:1/5 to Mostowski Collapse on Fri Apr 29 03:47:01 2022
    I implemented this already for the full fledged parser. But the simplified version doesn’t have it yet, because the simplified version didn’t parse a list of period terminated terms anyway yet. If I have time I will do the

    simplified version as well. Currently I get nice syncing, like for example:

    ?- X = (:- :- x0).
    error(syntax_error(operator_clash), [user:1])
    ?- X = (:- x0.
    error(syntax_error(parenthesis_balance), [user:2])
    ?- X = :- x0).
    error(syntax_error(operator_clash), [user:3])
    ?- X = (:- x0).
    X = (:- x0). http://www.xlog.ch/izytab/doclet/docs/18_live/10_reference/example01/package.html

    It can parse all 4 queries, and doesn’t get out of sync. read_sync//0 is currently implemented by skipping tokens until the terminating period
    is reached or end of file. A more mature implementation of throw//1

    can do much more, like fetching line number before it does read_sync//0.

    Mostowski Collapse schrieb am Freitag, 29. April 2022 um 12:45:50 UTC+2:
    I am little bit behind schedule of a Fuzzer that also
    does parenthesis. So this was my sixth sense. Was also
    working on another front, resyncing after errors.

    I found a solution today: Have a grammer that covers non-errorneous sentences and errorneous sentences. How to do this simply?
    Its more difficult to resync the tokenization, then to resync the

    parsing. For parsing I found this useful, since Prolog has the
    concept of terminating period. Take the very simplified
    prototype posted elsewhere:
    reader_secondary(H, X, L, C) --> [A],
    {current_op(R, M, A), is_infix(M, D, E), L >= R}, !,
    {R-D < C -> throw(error(syntax_error(operator_clash),_)); true},
    {T is R-E}, reader(Z, T),
    {J =.. [A,H,Z]},
    reader_secondary(J, X, L, R).
    It throws an exception inside an auxiliary action {}/1 of DCG. But
    you can define throw//1, i.e. make throw itself a DCG non-terminal:

    throw(T) --> read_sync, {throw(T)}.

    And then replace the infix parsing, its only an example, works also
    for all other parser errors:
    reader_secondary(H, X, L, C) --> [A],
    {current_op(R, M, A), is_infix(M, D, E), L >= R}, !,
    ({R-D < C} -> throw(error(syntax_error(operator_clash),_)); {true}),
    {T is R-E}, reader(Z, T),
    {J =.. [A,H,Z]},
    reader_secondary(J, X, L, R).
    The parser is now calling throw//1 instead of throw/1. And throw//1
    can do some syncing.
    Mostowski Collapse schrieb am Freitag, 29. April 2022 um 12:42:21 UTC+2:
    More proof that Logtalk is utter nonsense. What
    does the Logtalk test suite even test concerning
    the various "adapters" it has, like Trealla?

    This is a nice gem:

    $ ./tpl -v
    Trealla Prolog (c) Infradig 2020-2022, v1.27.12-31-g3575df
    $ ./tpl
    ?- X = (:- (:- x0)).
    Error: operator clash, line 1
    false.
    ?-

    There is something wrong with Ulrich Neumerkels
    compliance test suite, and maybe some QuickCheck
    resp. Fuzzer approach is needed,

    to chop of all heads of the hydra.

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mostowski Collapse@21:1/5 to Mostowski Collapse on Fri Apr 29 03:45:48 2022
    I am little bit behind schedule of a Fuzzer that also
    does parenthesis. So this was my sixth sense. Was also
    working on another front, resyncing after errors.

    I found a solution today: Have a grammer that covers non-errorneous
    sentences and errorneous sentences. How to do this simply?
    Its more difficult to resync the tokenization, then to resync the

    parsing. For parsing I found this useful, since Prolog has the
    concept of terminating period. Take the very simplified
    prototype posted elsewhere:

    reader_secondary(H, X, L, C) --> [A],
    {current_op(R, M, A), is_infix(M, D, E), L >= R}, !,
    {R-D < C -> throw(error(syntax_error(operator_clash),_)); true},
    {T is R-E}, reader(Z, T),
    {J =.. [A,H,Z]},
    reader_secondary(J, X, L, R).

    It throws an exception inside an auxiliary action {}/1 of DCG. But
    you can define throw//1, i.e. make throw itself a DCG non-terminal:

    throw(T) --> read_sync, {throw(T)}.

    And then replace the infix parsing, its only an example, works also
    for all other parser errors:

    reader_secondary(H, X, L, C) --> [A],
    {current_op(R, M, A), is_infix(M, D, E), L >= R}, !,
    ({R-D < C} -> throw(error(syntax_error(operator_clash),_)); {true}),
    {T is R-E}, reader(Z, T),
    {J =.. [A,H,Z]},
    reader_secondary(J, X, L, R).

    The parser is now calling throw//1 instead of throw/1. And throw//1
    can do some syncing.

    Mostowski Collapse schrieb am Freitag, 29. April 2022 um 12:42:21 UTC+2:
    More proof that Logtalk is utter nonsense. What
    does the Logtalk test suite even test concerning
    the various "adapters" it has, like Trealla?

    This is a nice gem:

    $ ./tpl -v
    Trealla Prolog (c) Infradig 2020-2022, v1.27.12-31-g3575df
    $ ./tpl
    ?- X = (:- (:- x0)).
    Error: operator clash, line 1
    false.
    ?-

    There is something wrong with Ulrich Neumerkels
    compliance test suite, and maybe some QuickCheck
    resp. Fuzzer approach is needed,

    to chop of all heads of the hydra.

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mostowski Collapse@21:1/5 to All on Sat Apr 30 14:29:58 2022
    This is an interesting pPEG example bug. Actually I wanted to hunt
    parenthesis parsing bugs, so I was up to generating some test cases that contain parenthesis. But this test case doesn’t contain any parenthesis,

    but it seems a binary infix operator is parsed as an unary functor?

    ?- string_termList(":- x0 =:= :- x1 - x2 .", [Y]), write_canonical(Y), nl. :-(:-(=:=(x0),-(x1,x2)))
    Y = (:- (=:=(x0):-x1-x2)).

    I am still using pPEG from 14.04.2022. How do I do a package update?

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mostowski Collapse@21:1/5 to Mostowski Collapse on Sat Apr 30 14:30:41 2022
    Concerning parenthesis I only found this bug, but its not
    really parenthesis related. So unlike Trealla it could be
    that parenthesis are not a problem. This here gives the same

    associativity hickup with and without parenthesis:

    ?- string_termList("- ( x0 * x1 ) ** x2 =:= x3 .", [Y]),
    write_canonical(Y), nl.
    -(=:=(**(*(x0,x1),x2),x3))
    Y = - ((x0*x1)**x2=:=x3).

    ?- string_termList("- x4 ** x2 =:= x3 .", [Y]), write_canonical(Y), nl. -(=:=(**(x4,x2),x3))
    Y = - (x4**x2=:=x3).

    ?- Y = (- x4 ** x2 =:= x3), write_canonical(Y), nl.
    =:=(-(**(x4,x2)),x3)
    Y = (-x4**x2=:=x3).

    Mostowski Collapse schrieb:
    This is an interesting pPEG example bug. Actually I wanted to hunt parenthesis parsing bugs, so I was up to generating some test cases that contain parenthesis. But this test case doesn’t contain any parenthesis,

    but it seems a binary infix operator is parsed as an unary functor?

    ?- string_termList(":- x0 =:= :- x1 - x2 .", [Y]), write_canonical(Y), nl. :-(:-(=:=(x0),-(x1,x2)))
    Y =  (:- (=:=(x0):-x1-x2)).

    I am still using pPEG from 14.04.2022. How do I do a package update?

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mostowski Collapse@21:1/5 to All on Mon May 2 07:48:55 2022
    I didn’t start a new testing campaign with pPEG yet, where I get
    a new type of error, which I do not yet know how to silence.
    But meanwhile I have a funny test case where

    SWI-Prolog and SICStus disagree:

    /* SWI-Prolog */
    ?- X = (- - - * - - - x0), write_canonical(X), nl. *(-(-(-)),-(-(-(x0))))
    X = - - (-)* - - -x0.

    /* SICStus Prolog */
    ?- X = (- - - * - - - x0), write_canonical(X), nl. -(-(-(-(*))),-(-(x0)))
    X = - - - (*)- - -x0 ?

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mostowski Collapse@21:1/5 to Mostowski Collapse on Mon May 2 07:49:50 2022
    The SWI-Prolog built-in with_output_to/2 does also not work.
    Would need something like a with_error_to/2 ?
    Does this exist? I only get:

    ?- with_output_to(atom(_), (write('I am chatty'), nl)).
    true.

    ?- with_output_to(atom(_), string_termList("- x4 ** x2 =:= .", [Y])).
    % pPEG Error: Prolog.expr failed, expected Prolog.expr at line 1.16:
    % 1 | - x4 ** x2 =:= .
    % ^
    false.

    Mostowski Collapse schrieb am Montag, 2. Mai 2022 um 16:48:56 UTC+2:
    I didn’t start a new testing campaign with pPEG yet, where I get
    a new type of error, which I do not yet know how to silence.
    But meanwhile I have a funny test case where

    SWI-Prolog and SICStus disagree:

    /* SWI-Prolog */
    ?- X = (- - - * - - - x0), write_canonical(X), nl.
    *(-(-(-)),-(-(-(x0))))
    X = - - (-)* - - -x0.

    /* SICStus Prolog */
    ?- X = (- - - * - - - x0), write_canonical(X), nl.
    -(-(-(-(*))),-(-(x0)))
    X = - - - (*)- - -x0 ?

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mostowski Collapse@21:1/5 to Mostowski Collapse on Tue May 17 14:37:10 2022
    It seems Scryer Prolog is not that advanced like ECLiPSe Prolog:

    $ target/release/scryer-prolog
    ?- X = foo = bar = baz = 'ab\qc' .
    error(syntax_error(invalid_single_quoted_character),read_term/3).

    Initially my thought was my monadic parser from Dogelog player
    will automatically be able to deal with this. But its non-trivial.
    But my Dogelog player got a scanner/parser booster yesterday:

    ?- X = foo = bar = baz = 'ab\qc' .
    error(syntax_error(operator_clash), [user:1])

    Mostowski Collapse schrieb am Dienstag, 17. Mai 2022 um 23:34:51 UTC+2:
    My parser research has arrived at this eclectic challenge.
    Here is an example where I can coerce both SWI-Prolog and
    pPEG SWIPL Example into masking the real error.

    Here is what ECLiPSe Prolog does:

    [eclipse 1]: X = foo = bar = baz = 'ab\qc' .
    syntax error: bracket necessary
    | X = foo = bar = baz = 'ab\qc' .
    | ^ here

    And here is SWI-Prolog and pPEG SWIPL Example:

    ?- X = foo = bar = baz = 'ab\qc' .
    ERROR: Syntax error: Unknown character escape in quoted atom or string: `\q' ERROR: X = foo = bar = baz = 'ab
    ERROR: ** here **
    ERROR: \qc' .

    ?- string_termList("X = foo = bar = baz = 'ab\\qc' .", [T]).
    % pPEG Error: _esc failed, ...
    % 1 | X = foo = bar = baz = 'ab\qc' .
    % ^
    false.

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mostowski Collapse@21:1/5 to All on Tue May 17 14:34:50 2022
    My parser research has arrived at this eclectic challenge.
    Here is an example where I can coerce both SWI-Prolog and
    pPEG SWIPL Example into masking the real error.

    Here is what ECLiPSe Prolog does:

    [eclipse 1]: X = foo = bar = baz = 'ab\qc' .
    syntax error: bracket necessary
    | X = foo = bar = baz = 'ab\qc' .
    | ^ here

    And here is SWI-Prolog and pPEG SWIPL Example:

    ?- X = foo = bar = baz = 'ab\qc' .
    ERROR: Syntax error: Unknown character escape in quoted atom or string: `\q' ERROR: X = foo = bar = baz = 'ab
    ERROR: ** here **
    ERROR: \qc' .

    ?- string_termList("X = foo = bar = baz = 'ab\\qc' .", [T]).
    % pPEG Error: _esc failed, ...
    % 1 | X = foo = bar = baz = 'ab\qc' .
    % ^
    false.

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mostowski Collapse@21:1/5 to Mostowski Collapse on Wed May 18 03:38:35 2022
    Now I have a new project going. I need a better microscope
    to find differences in parsing of the different Prolog systems.
    So that I might generate a phylogenic tree.

    I see a trend against ECliPSe Prolog concering fuzz3, now also
    results available for Scryer Prolog and Trealla Prolog. Unfortunately
    no data yet available for Tau Prolog, still waiting

    for charsio from Tau Prolog:

    ECLiPSe Scryer Trealla
    fuzz3 292 0 0
    fuzz4 382 801 532

    My suspicion, for fuzz4, Scryer Prolog behaves like GNU Prolog,
    not shown here, but GNU Prolog has same figures. But this would
    need a distance matrice, to get some support for this hypothesis,

    that they are really the same.

    Mostowski Collapse schrieb am Dienstag, 17. Mai 2022 um 23:37:12 UTC+2:
    It seems Scryer Prolog is not that advanced like ECLiPSe Prolog:

    $ target/release/scryer-prolog
    ?- X = foo = bar = baz = 'ab\qc' . error(syntax_error(invalid_single_quoted_character),read_term/3).

    Initially my thought was my monadic parser from Dogelog player
    will automatically be able to deal with this. But its non-trivial.
    But my Dogelog player got a scanner/parser booster yesterday:
    ?- X = foo = bar = baz = 'ab\qc' .
    error(syntax_error(operator_clash), [user:1])
    Mostowski Collapse schrieb am Dienstag, 17. Mai 2022 um 23:34:51 UTC+2:
    My parser research has arrived at this eclectic challenge.
    Here is an example where I can coerce both SWI-Prolog and
    pPEG SWIPL Example into masking the real error.

    Here is what ECLiPSe Prolog does:

    [eclipse 1]: X = foo = bar = baz = 'ab\qc' .
    syntax error: bracket necessary
    | X = foo = bar = baz = 'ab\qc' .
    | ^ here

    And here is SWI-Prolog and pPEG SWIPL Example:

    ?- X = foo = bar = baz = 'ab\qc' .
    ERROR: Syntax error: Unknown character escape in quoted atom or string: `\q'
    ERROR: X = foo = bar = baz = 'ab
    ERROR: ** here **
    ERROR: \qc' .

    ?- string_termList("X = foo = bar = baz = 'ab\\qc' .", [T]).
    % pPEG Error: _esc failed, ...
    % 1 | X = foo = bar = baz = 'ab\qc' .
    % ^
    false.

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mostowski Collapse@21:1/5 to All on Sat May 21 06:19:09 2022
    I made a kind of phylogenetic tree, the numbers in it indicate
    how many test cases the various Prolog systems agree.
    The results for fuzz4 are as follows:

    ?- pairing([eclipse4,gnu4,jekejeke4,swi4,scryer4,sicstus4,
    ppeg4,trealla4], R), show(R, 0).
    +--- 8713
    +--- 9509
    +--- trealla4
    +--- 9997
    +--- scryer4
    +--- gnu4
    +--- 9288
    +--- 9586
    +--- 9860
    +--- eclipse4
    +--- swi4
    +--- jekejeke4
    +--- 9642
    +--- ppeg4
    +--- sicstus4

    SWI-Prolog is close to ECLiPSe Prolog in fuzz4 test cases. But pPEG
    SWIPL Example is close to SICStus Prolog in fuzz4 test cases.

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mostowski Collapse@21:1/5 to Mostowski Collapse on Sat May 21 15:21:46 2022
    And my suspicion got confirmed, Scryer and GNU
    do the same in fuzz4 test cases, except for a

    few amusing strange results:

    $ target/release/scryer-prolog -v
    "v0.9.0-146-g25418db2-modified"
    $ target/release/scryer-prolog
    ?- X = (- ( ( ) =:= x0).
    X = (- '('=:=x0).
    ?- X = (- ( ( ) , x0).
    X = (- '(',x0).
    ?- X = ( ( ( ) :- x0).
    X = ('(':-x0).

    LoL

    Mostowski Collapse schrieb:
    I made a kind of phylogenetic tree, the numbers in it indicate
    how many test cases the various Prolog systems agree.
    The results for fuzz4 are as follows:

    ?- pairing([eclipse4,gnu4,jekejeke4,swi4,scryer4,sicstus4,
    ppeg4,trealla4], R), show(R, 0).
    +--- 8713
    +--- 9509
    +--- trealla4
    +--- 9997
    +--- scryer4
    +--- gnu4
    +--- 9288
    +--- 9586
    +--- 9860
    +--- eclipse4
    +--- swi4
    +--- jekejeke4
    +--- 9642
    +--- ppeg4
    +--- sicstus4

    SWI-Prolog is close to ECLiPSe Prolog in fuzz4 test cases. But pPEG
    SWIPL Example is close to SICStus Prolog in fuzz4 test cases.


    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Mostowski Collapse@21:1/5 to Mostowski Collapse on Sat May 21 15:03:48 2022
    Ok, this was fun:

    Phylogenetic Trees for Prolog Operator Parsers https://twitter.com/dogelogch/status/1528118780890603522

    Phylogenetic Trees for Prolog Operator Parsers https://www.facebook.com/groups/dogelog

    Mostowski Collapse schrieb am Samstag, 21. Mai 2022 um 15:21:49 UTC+2:
    And my suspicion got confirmed, Scryer and GNU
    do the same in fuzz4 test cases, except for a

    few amusing strange results:

    $ target/release/scryer-prolog -v
    "v0.9.0-146-g25418db2-modified"
    $ target/release/scryer-prolog
    ?- X = (- ( ( ) =:= x0).
    X = (- '('=:=x0).
    ?- X = (- ( ( ) , x0).
    X = (- '(',x0).
    ?- X = ( ( ( ) :- x0).
    X = ('(':-x0).

    LoL

    Mostowski Collapse schrieb:
    I made a kind of phylogenetic tree, the numbers in it indicate
    how many test cases the various Prolog systems agree.
    The results for fuzz4 are as follows:

    ?- pairing([eclipse4,gnu4,jekejeke4,swi4,scryer4,sicstus4,
    ppeg4,trealla4], R), show(R, 0).
    +--- 8713
    +--- 9509
    +--- trealla4
    +--- 9997
    +--- scryer4
    +--- gnu4
    +--- 9288
    +--- 9586
    +--- 9860
    +--- eclipse4
    +--- swi4
    +--- jekejeke4
    +--- 9642
    +--- ppeg4
    +--- sicstus4

    SWI-Prolog is close to ECLiPSe Prolog in fuzz4 test cases. But pPEG
    SWIPL Example is close to SICStus Prolog in fuzz4 test cases.


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