Skip to content

Commit 6376456

Browse files
committed
Simplify code
1 parent 262efb4 commit 6376456

File tree

1 file changed

+11
-18
lines changed

1 file changed

+11
-18
lines changed

src/loader.pl

Lines changed: 11 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -35,36 +35,29 @@
3535
),
3636
write('.').
3737

38-
trace(on).
38+
:- meta_predicate maplistdif(3, ?, ?, ?).
39+
maplistdif(_, [], [], L-L).
40+
maplistdif(G__2, [H1|T1], [H2|T2], L0-LX) :-
41+
call(G__2, H1, H2, L0-L1),
42+
maplistdif(G__2, T1, T2, L1-LX).
3943

40-
writeln(X) :-
41-
trace(on), write(X), nl.
42-
x(G_0) :-
43-
catch(loader:G_0, E, (loader:writeln(exception:E:G_0),throw(E))).
44-
w(G_0) :-
45-
writeln(call:G_0), x(G_0), writeln(exit:G_0).
46-
47-
%% arithmetic_expansion(+Type, ?Term, -ExpandedTerm, ListDifference).
44+
%% arithmetic_expansion(+Type, Term, -ExpandedTerm, ?ListDifference).
4845
%
49-
% Hand-expanded DCG, because library(dcgs) isn't available during goal expansion.
50-
% Recursively traverse `Term` and assemble a list of replacements that makes up
51-
% a valid arithmetic relation.
46+
% Recursively traverse `Term` and assemble a list of replacements that makes
47+
% `ExpandedTerm` a valid arithmetic relation (`Type = rela`) or functional
48+
% expression (`Type = func`).
5249
%
5350
% NOTE: Order of clauses is important for correctness.
5451
arithmetic_expansion(func, T, T, L-L) :-
5552
(var(T); number(T)), !.
56-
arithmetic_expansion(list, [], [], L-L) :- !.
57-
arithmetic_expansion(list, [T0|Ts], [R0|Rs], L1-L3) :-
58-
arithmetic_expansion(func, T0, R0, L1-L2),
59-
arithmetic_expansion(list, Ts, Rs, L2-L3), !.
6053
arithmetic_expansion(Set, T, R, LD) :-
6154
functor(T, F, A),
6255
arithmetic_term(Set, A, Fs),
6356
member(F, Fs), !,
6457
functor(R, F, A),
6558
T =.. [F|Ts],
6659
R =.. [F|Rs],
67-
arithmetic_expansion(list, Ts, Rs, LD).
60+
maplistdif(arithmetic_expansion(func), Ts, Rs, LD).
6861
arithmetic_expansion(func, T, R, [T=R|L]-L).
6962

7063
arithmetic_term(func, 0, [e,pi,epsilon]).
@@ -112,7 +105,7 @@
112105
% Additional rule just to replace invalid arithmetic expression with
113106
% runtime exception
114107
nonvar(G),
115-
w(arithmetic_expansion(rela, G, R, Gx-[R])).
108+
arithmetic_expansion(rela, G, R, Gx-[R]).
116109
goal_expansion(Goal, Module, ExpandedGoal) :-
117110
( atom(Module),
118111
'$predicate_defined'(Module, goal_expansion, 2),

0 commit comments

Comments
 (0)