19
21
22clock_time(T):- statistics(walltime,[X,_]),T is X/1000.
23
24mk_complex(R, I, '@'(R, I)).
25get_complex('@'(R, I), R, I).
26
27complex(C, R, I):- ground(C), get_complex(C, R0, I0), !, R=R0, I=I0.
28complex(C, R, I):- ground((R, I)), mk_complex(R, I, C0), !, C=C0.
29complex(C, R, I):- freeze(C, complex(C, R, I)), freeze(R, complex(C, R, I)), freeze(I, complex(C, R, I)).
30
31
32
35:- nop(ensure_loaded('adv_util_subst')). 37
38apply_all([], _Goal, S0, S0) :- !.
39apply_all([Arg], Goal, S0, S2) :- !, apply_first_arg_state(Arg, Goal, S0, S2).
40
41apply_all(List, Goal, S0, S2) :- notrace((list_to_set(List,Set),
42 List\==Set)), !,
43 apply_all(Set, Goal, S0, S2).
44
45apply_all([Arg|ArgTail], Goal, S0, S2) :-
46 runnable_goal(Goal, Runnable),
47 apply_first_arg_state(Arg, Runnable, S0, S1),
48 !, 49 apply_all(ArgTail, Goal, S1, S2).
50
51runnable_goal(Goal, Goal) :- ground(Goal), !.
53runnable_goal(Goal, Goal).
54
55apply_state(Goal,S0,S0):- Goal==[],!.
56apply_state(rtrace(Goal), S0, S2) :- !, rtrace(apply_state(Goal, S0, S2)).
57apply_state(dmust(Goal), S0, S2) :- !, dmust(apply_state(Goal, S0, S2)).
58apply_state(must(Goal), S0, S2) :- !, dmust(apply_state(Goal, S0, S2)).
59apply_state(nop(_), S0, S2) :- !, S0=S2.
60apply_state({Goal}, S0, S0) :- !, call(Goal).
61apply_state([G1|G2], S0, S2) :- !,
62 apply_state(G1, S0, S1),
63 apply_state(G2, S1, S2).
64apply_state((G1,G2), S0, S2) :- !,
65 apply_state(G1, S0, S1),
66 apply_state(G2, S1, S2).
67apply_state((G1;G2), S0, S2) :- !,
68 apply_state(G1, S0, S2);
69 apply_state(G2, S0, S2).
70
71apply_state(s(Goal), S0, S2) :- !,
72 notrace((compound_name_arguments(Goal, F, GoalL),
73 append(GoalL, [S0], NewGoalL),
74 must_input_state(S0),
75 Call=..[F|NewGoalL])),
76 dmust(Call),
77 S0 = S2,
78 must_output_state(S2).
79
80apply_state(Goal, S0, S2) :-
81 notrace((compound_name_arguments(Goal, F, GoalL),
82 append(GoalL, [S0, S2], NewGoalL),
83 must_input_state(S0),
84 Call=..[F|NewGoalL])),
85 dmust(Call),
86 must_output_state(S2).
87
88
89
90
91apply_first_arg_state(Arg, Goal, S0, S2) :-
92 notrace((compound_name_arguments(Goal, F, GoalL),
93 append(GoalL, [S0, S2], NewGoalL),
94 must_input_state(S0),
95 Call=..[F, Arg|NewGoalL])),
96 dmust(Call),
97 must_output_state(S2).
98
99apply_first_arg(Arg, Goal, S0, S2):-
100 apply_first_arg_state(Arg, Goal, S0, S2).
101
103
105
106findterm(Term, Term).
107findterm(Term, [Head|_]) :- nonvar(Head),
108 findterm(Term, Head).
109findterm(Term, [_|Tail]) :- nonvar(Tail),
110 findterm(Term, Tail).
111findterm(Term, T) :-
112 compound(T),
113 \+ is_list(T),
114 T =.. List,
115 findterm(Term, List).
116
127subst(unify, Find1, Replace, Find2, Replace) :- Find1 = Find2,
128 129 130 131 !.
132subst(equivalent, Find, Replace, T0, Replace) :-
133 134 T0 == Find,
135 !.
136subst(copy_term, Find, Replace, FindCopy, ReplaceCopy) :-
137 138 139 140 141 142 143 144 145 copy_term(Find-Replace, FindCopy-ReplaceCopy),
146 !.
147subst(BindType, Find, Replace, List, [T|Rest]) :-
148 is_list(List),
149 List = [T0|Rest0], 150 !,
151 subst(BindType, Find, Replace, T0, T),
152 subst(BindType, Find, Replace, Rest0, Rest).
153subst(BindType, Find, Replace, T0, T) :-
154 compound(T0),
155 156 !,
157 T0 =.. [Functor0|Args0],
158 subst(BindType, Find, Replace, Functor0, Functor1),
159 subst(BindType, Find, Replace, Args0, Args1),
160 161 ( atom(Functor1) -> T =.. [Functor1|Args1] ; T =.. [Functor0|Args1]).
162subst(_BindType, _Find, _Replace, T, T).
163
166subst_dict(_BindType, [], T, T).
167subst_dict(BindType, [Find-Replace|Rest], T0, T) :-
168 subst(BindType, Find, Replace, T0, T1),
169 subst_dict(BindType, Rest, T1, T).
170
171
172
173writel([]).
174writel([nl]) :- !, nl. 175writel([H|T]) :- write(H), writel(T).
177
179uninstantiated([]) :- !, fail.
180uninstantiated(Term) :- var(Term).
181uninstantiated([Head|_]) :- uninstantiated(Head).
182uninstantiated([_|List]) :- !, uninstantiated(List).
183uninstantiated(Term) :-
184 compound(Term),
185 Term =.. [Head | Tail],
186 (uninstantiated(Head); uninstantiated(Tail)).
187
189
195
199
200
212
215
218
230