Skip to content

Commit

Permalink
TEST: Added ISO ambiguous operator tests.
Browse files Browse the repository at this point in the history
Marked two tests as blocked as these currently fail.
  • Loading branch information
JanWielemaker committed Nov 13, 2024
1 parent 1dc9d4d commit 9d90bb5
Showing 1 changed file with 31 additions and 1 deletion.
32 changes: 31 additions & 1 deletion src/Tests/core/test_syntax.pl
Original file line number Diff line number Diff line change
Expand Up @@ -38,9 +38,16 @@
:- use_module(library(plunit)).

test_syntax :-
run_tests([ syntax
run_tests([ syntax,
iso_op_table_6
]).

:- meta_predicate
term_string_(-, :).

term_string_(Term, M:String) :-
term_string(Term, String, [module(M)]).

:- begin_tests(syntax).

:- op(600, fx, fx600).
Expand Down Expand Up @@ -126,3 +133,26 @@
atom_codes(T, [247]).

:- end_tests(syntax).

:- begin_tests(iso_op_table_6).

:- op(100, fy, fy).
:- op(100, xfy, xfy).
:- op(100, yfx, yfx).
:- op(100, yf, yf).

test(r1, T == fy(fy(1))) :-
term_string_(T, "fy fy 1").
test(r2, T == xfy(1, xfy(2,3))) :-
term_string_(T, "1 xfy 2 xfy 3").
test(r3, [T == xfy(1, yfx(2,3)), blocked(bug)]) :-
term_string_(T, "1 xfy 2 yfx 3").
test(r4, [T == fy(yf(2)), blocked(bug)]) :-
term_string_(T, "fy 2 fy").
test(r5, T == yf(yf(1))) :-
term_string_(T, "1 yf yf").
test(r6, T == yfx(yfx(1,2),3)) :-
term_string_(T, "1 yfx 2 yfx 3").

:- end_tests(iso_op_table_6).

0 comments on commit 9d90bb5

Please sign in to comment.