34
35:- module(record_locations, [record_location/0]). 36
37:- use_module(library(filesex)). 38:- use_module(library(extra_location)). 39:- use_module(library(apply)). 40:- use_module(library(filepos_line)). 41:- use_module(library(from_utils)). 42
43:- multifile
44 system:term_expansion/4,
45 system:goal_expansion/4. 46
47:- dynamic record_location/0. 48record_location. 49
50:- thread_local rl_tmp/3. 51
53extra_location:loc_declaration(Head, M, assertion(Status, Type), From) :-
54 assertions:asr_head_prop(_, CM, Head, Status, Type, _, _, From),
55 predicate_property(CM:Head, implementation_module(M)).
56
57:- multifile skip_record_decl/1. 58
59skip_record_decl(initialization(_)) :- !.
60skip_record_decl(Decl) :-
61 nonvar(Decl),
62 '$current_source_module'(M),
63 predicate_property(M:Decl, imported_from(assertions)),
64 functor(Decl, Type, Arity),
65 memberchk(Arity, [1, 2]),
66 assertions:assrt_type(Type), !.
67
68:- public record_extra_location/4. 69
((:- Decl),
71 term_position(_, _, _, _, [DPos])) -->
72 ( {\+ skip_record_decl(Decl)}
73 ->record_extra_decl(Decl, DPos)
74 ; []
75 ).
76
(Decl, DPos) -->
78 { '$current_source_module'(SM),
79 declaration_pos(Decl, DPos, SM, M, IdL, ArgL, PosL)
80 },
81 foldl(assert_declaration(M), IdL, ArgL, PosL),
82 !.
83record_extra_decl(Goal, Pos) -->
84 { nonvar(Goal),
85 source_location(File, Line),
86 retractall(rl_tmp(File, Line, _)),
87 asserta(rl_tmp(File, Line, 1)),
88 assert_position(Goal, Pos, body)
89 }.
90
91declaration_pos(DM:Decl, term_position(_, _, _, _, [_, DPos]), _, M, ID, U, Pos) :-
92 declaration_pos(Decl, DPos, DM, M, ID, U, Pos).
93declaration_pos(module(M, L), DPos,
94 _, M, [module_2, export], [module(M, L), L], [DPos, Pos]) :-
95 DPos = term_position(_, _, _, _, [_, Pos]).
96declaration_pos(volatile(L), term_position(_, _, _, _, PosL),
97 M, M, [volatile], [L], PosL).
98declaration_pos(dynamic(L), term_position(_, _, _, _, PosL),
99 M, M, [dynamic], [L], PosL).
100declaration_pos(thread_local(L), term_position(_, _, _, _, PosL),
101 M, M, [thread_local], [L], PosL).
102declaration_pos(public(L), term_position(_, _, _, _, PosL),
103 M, M, [public], [L], PosL).
104declaration_pos(export(L), term_position(_, _, _, _, PosL),
105 M, M, [export], [L], PosL).
106declaration_pos(multifile(L), term_position(_, _, _, _, PosL),
107 M, M, [multifile], [L], PosL).
108declaration_pos(discontiguous(L), term_position(_, _, _, _, PosL),
109 M, M, [discontiguous], [L], PosL).
110declaration_pos(meta_predicate(L), term_position(_, _, _, _, PosL),
111 M, M, [meta_predicate], [L], PosL).
112declaration_pos(reexport(SM:DU), DPos, _, M, ID, U, Pos) :- !,
113 declaration_pos(reexport(DU), DPos, SM, M, ID, U, Pos).
114declaration_pos(use_module(SM:DU), DPos, _, M, ID, U, Pos) :- !,
115 declaration_pos(use_module(DU), DPos, SM, M, ID, U, Pos).
116declaration_pos(use_module(SM:DU, L), DPos, ID, _, M, U, Pos) :- !,
117 declaration_pos(use_module(DU, L), DPos, ID, SM, M, U, Pos).
118declaration_pos(reexport(SM:DU, L), DPos, ID, _, M, U, Pos) :- !,
119 declaration_pos(reexport(DU, L), DPos, ID, SM, M, U, Pos).
120declaration_pos(include(U), DPos, M, M, [include], [U], [DPos]).
121declaration_pos(use_module(U), DPos, M, M, [use_module], [U], [DPos]).
122declaration_pos(reexport(U), DPos, M, M, [reexport], [U], [DPos]).
123declaration_pos(consult(U), DPos, M, M, [consult], [U], [DPos]).
124declaration_pos(reexport(U, L), DPos, M, M,
125 [reexport_2, reexport(U)], [reexport(U, L), L], [DPos, Pos]) :-
126 DPos = term_position(_, _, _, _, [_, Pos]).
127declaration_pos(use_module(U, L), DPos, M, M,
128 [use_module_2, import(U)], [use_module(U, L), L], [DPos, Pos]) :-
129 DPos = term_position(_, _, _, _, [_, Pos]).
130
131:- meta_predicate foldsequence(4,?,?,?,?). 132
133foldsequence(G, A, B) --> foldsequence_(A, G, B).
134
135foldsequence_(A, _, _) -->
136 {var(A)},
137 !.
138 139foldsequence_([], _, _) --> !.
140foldsequence_([E|L], G, list_position(_, _, PosL, _)) -->
141 !,
142 foldl(foldsequence(G), [E|L], PosL).
143foldsequence_((A, B), G, term_position(_, _, _, _, [PA, PB])) -->
144 !,
145 foldsequence_(A, G, PA),
146 foldsequence_(B, G, PB).
147foldsequence_(A, G, PA) --> call(G, A, PA).
148
149assert_declaration(M, Declaration, Sequence, Pos) -->
150 foldsequence(assert_declaration_one(Declaration, M), Sequence, Pos).
151
152assert_declaration_one(reexport(U), M, PI, Pos) -->
153 !,
154 assert_reexport_declaration_2(PI, U, Pos, M).
155assert_declaration_one(module_2, M, H, Pos) -->
156 !,
157 158 assert_declaration_one(H, M, module_2, Pos).
159assert_declaration_one(Declaration, _, M:PI,
160 term_position(_, _, _, _, [_, Pos])) -->
161 !,
162 assert_declaration_one(Declaration, M, PI, Pos).
163assert_declaration_one(Declaration, M, F/A, Pos) -->
164 { atom(F),
165 integer(A)
166 },
167 !,
168 {functor(H, F, A)},
169 assert_position(H, M, Declaration, Pos).
170assert_declaration_one(Declaration, M, F//A1, Pos) -->
171 { atom(F),
172 integer(A1)
173 },
174 !,
175 { A is A1+2,
176 functor(H, F, A)
177 },
178 assert_position(H, M, Declaration, Pos).
179assert_declaration_one(Declaration, M, H, Pos) -->
180 assert_position(H, M, Declaration, Pos).
181
182assert_reexport_declaration_2((F/A as G), U, Pos, M) -->
183 {functor(H, G, A)},
184 assert_position(H, M, reexport(U, [F/A as G]), Pos).
185assert_reexport_declaration_2(F/A, U, Pos, M) -->
186 {functor(H, F, A)},
187 assert_position(H, M, reexport(U, [F/A]), Pos).
188assert_reexport_declaration_2(op(_, _, _), _, _, _) --> [].
189assert_reexport_declaration_2(except(_), _, _, _) --> [].
190
191assert_position(H, M, Type, TermPos) :-
192 assert_position(H, M, Type, TermPos, Clauses, []),
193 compile_aux_clauses(Clauses).
194
195assert_position(H, M, Type, TermPos) -->
196 { source_location(File, Line1),
197 ( nonvar(TermPos)
198 ->arg(1, TermPos, Chars),
199 filepos_line(File, Chars, Line, LinePos)
200 201 202 ; Line = Line1,
203 LinePos = -1
204 )
205 },
206 assert_location(H, M, Type, File, Line, file(File, Line, LinePos, Chars)).
207
208assert_location(H, M, Type, File, Line, From) -->
209 ( {\+ have_extra_location(From, H, M, Type)}
210 ->['$source_location'(File, Line):extra_location:loc_declaration(H, M, Type, From)]
211 ; []
212 ).
213
222
(From1, H, M, Type) :-
224 extra_location(H, M, Type, From),
225 subsumes_from(From1, From).
226
227in_swipl_home(File) :-
228 current_prolog_flag(home, Dir),
229 directory_file_path(Dir, _, File).
230
231system:term_expansion(Term, Pos, [Term|Clauses], Pos) :-
232 record_location,
233 source_location(File, Line),
234 \+ in_swipl_home(File),
235 ( rl_tmp(File, Line, _)
236 ->fail
237 ; retractall(rl_tmp(_, _, _)),
238 asserta(rl_tmp(File, Line, 0 )),
239 record_extra_location(Term, Pos, Clauses, []),
240 Clauses \= []
241 ).
242
243redundant((_,_)).
244redundant((_;_)).
245redundant((_:_)).
246redundant(true).
247redundant(!).
248
249assert_position(G, Pos, T) :-
250 '$current_source_module'(M),
251 assert_position(G, M, T, Pos).
252
253:- public rl_goal_expansion/2. 254rl_goal_expansion(Goal, Pos) :-
255 callable(Goal),
256 \+ redundant(Goal),
257 source_location(File, Line),
258 \+ in_swipl_home(File),
259 ( nb_current('$term', Term)
260 ->( rl_tmp(File, Line, Flag)
261 ->Flag == 1
262 ; true
263 ),
264 memberchk(Term, [(:-_), []])
265 ; 266 true
267 ),
268 \+ clause(declaration_pos(Goal, _, _, _, _, _, _), _),
269 \+ skip_record_decl(Goal),
270 assert_position(Goal, Pos, goal),
271 !.
272
273system:goal_expansion(Goal, Pos, _, _) :-
274 record_location,
275 rl_goal_expansion(Goal, Pos),
276 fail