|
35 | 35 | ),
|
36 | 36 | write('.').
|
37 | 37 |
|
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). |
39 | 43 |
|
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). |
48 | 45 | %
|
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`). |
52 | 49 | %
|
53 | 50 | % NOTE: Order of clauses is important for correctness.
|
54 | 51 | arithmetic_expansion(func, T, T, L-L) :-
|
55 | 52 | (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), !. |
60 | 53 | arithmetic_expansion(Set, T, R, LD) :-
|
61 | 54 | functor(T, F, A),
|
62 | 55 | arithmetic_term(Set, A, Fs),
|
63 | 56 | member(F, Fs), !,
|
64 | 57 | functor(R, F, A),
|
65 | 58 | T =.. [F|Ts],
|
66 | 59 | R =.. [F|Rs],
|
67 |
| - arithmetic_expansion(list, Ts, Rs, LD). |
| 60 | + maplistdif(arithmetic_expansion(func), Ts, Rs, LD). |
68 | 61 | arithmetic_expansion(func, T, R, [T=R|L]-L).
|
69 | 62 |
|
70 | 63 | arithmetic_term(func, 0, [e,pi,epsilon]).
|
|
112 | 105 | % Additional rule just to replace invalid arithmetic expression with
|
113 | 106 | % runtime exception
|
114 | 107 | nonvar(G),
|
115 |
| - w(arithmetic_expansion(rela, G, R, Gx-[R])). |
| 108 | + arithmetic_expansion(rela, G, R, Gx-[R]). |
116 | 109 | goal_expansion(Goal, Module, ExpandedGoal) :-
|
117 | 110 | ( atom(Module),
|
118 | 111 | '$predicate_defined'(Module, goal_expansion, 2),
|
|
0 commit comments