35
36:- module(prolog_operator,
37 [ push_operators/1, 38 push_operators/2, 39 pop_operators/0,
40 pop_operators/1, 41 push_op/3 42 ]).
86:- thread_local
87 operator_stack/1. 88
89:- meta_predicate
90 push_operators(:),
91 push_operators(:,-),
92 push_op(+,+,:).
101push_operators(New, Undo) :-
102 strip_module(New, Module, Ops0),
103 tag_ops(Ops0, Module, Ops),
104 undo_operators(Ops, Undo),
105 set_operators(Ops).
106
107push_operators(New) :-
108 push_operators(New, Undo),
109 asserta(operator_stack(mark-Undo)).
117push_op(P, T, A) :-
118 undo_operator(op(P,T,A), Undo),
119 op(P, T, A),
120 asserta(operator_stack(incremental-Undo)).
127pop_operators :-
128 retract(operator_stack(Mark-Undo)),
129 set_operators(Undo),
130 Mark == mark,
131 !.
137pop_operators(Undo) :-
138 set_operators(Undo).
139
140tag_ops([], _, []).
141tag_ops([op(P,Tp,N0)|T0], M, [op(P,Tp,N)|T]) :-
142 strip_module(M:N0, M1, N1),
143 N = M1:N1,
144 tag_ops(T0, M, T).
145
146set_operators([]).
147set_operators([H|R]) :-
148 set_operators(H),
149 set_operators(R).
150set_operators(op(P,T,A)) :-
151 op(P, T, A).
152
153undo_operators([], []).
154undo_operators([O0|T0], [U0|T]) :-
155 undo_operator(O0, U0),
156 undo_operators(T0, T).
157
158undo_operator(op(_P, T, N), op(OP, OT, N)) :-
159 current_op(OP, OT, N),
160 same_op_type(T, OT),
161 !.
162undo_operator(op(P, T, [H|R]), [OH|OT]) :-
163 !,
164 undo_operator(op(P, T, H), OH),
165 undo_operator(op(P, T, R), OT).
166undo_operator(op(_, _, []), []) :- !.
167undo_operator(op(_P, T, N), op(0, T, N)).
168
169same_op_type(T, OT) :-
170 op_type(T, Type),
171 op_type(OT, Type).
172
173op_type(fx, prefix).
174op_type(fy, prefix).
175op_type(xfx, infix).
176op_type(xfy, infix).
177op_type(yfx, infix).
178op_type(xf, postfix).
179op_type(yf, postfix)
Manage operators
Often, one wants to define operators to improve the readibility of some very specific code. Operators in Prolog are global objects and changing operators changes syntax and possible semantics of existing sources. For this reason it is desirable to reset operator declarations after the code that needs them has been read. This module defines a rather cruel -but portable- method to do this.
Usage:
While the above are for source-code, the calls push_operators/2 and pop_operators/1 can be used for local processing where it is more comfortable to carry the undo context around.
NOTE: In recent versions of SWI-Prolog operators are local to a module and can be exported using the syntax below. This is not portable, but otherwise a more structured approach for operator handling.