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.
Edit 15.04.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).