36
37:- module(prolog_breakpoints,
38 [ set_breakpoint/4, 39 set_breakpoint/5, 40 delete_breakpoint/1, 41 breakpoint_property/2 42 ]). 43:- use_module(library(prolog_clause)). 44:- use_module(library(debug)). 45:- use_module(library(error)). 46
47
61
62:- dynamic
63 user:prolog_event_hook/1. 64:- multifile
65 user:prolog_event_hook/1. 66
88
89set_breakpoint(File, Line, Char, Id) :-
90 set_breakpoint(File, File, Line, Char, Id).
91set_breakpoint(Owner, File, Line, Char, Id) :-
92 debug(break, 'break_at(~q, ~d, ~d).', [File, Line, Char]),
93 '$clause_from_source'(Owner, File, Line, ClauseRef),
94 clause_info(ClauseRef, InfoFile, TermPos, _NameOffset),
95 ( InfoFile == File
96 -> '$break_pc'(ClauseRef, PC, NextPC),
97 debug(break, 'Clause ~p, PC=~p NextPC=~p', [ClauseRef, PC, NextPC]),
98 '$clause_term_position'(ClauseRef, NextPC, List),
99 debug(break, 'Location = ~w', [List]),
100 range(List, TermPos, A, Z),
101 debug(break, 'Term from ~w-~w', [A, Z]),
102 Z >= Char, !,
103 Len is Z - A,
104 b_setval('$breakpoint', file_location(File, Line, A, Len))
105 ; print_message(warning, breakpoint(no_source(ClauseRef, File, Line))),
106 '$break_pc'(ClauseRef, PC, _), !,
107 nb_delete('$breakpoint')
108 ),
109 debug(break, 'Break at clause ~w, PC=~w', [ClauseRef, PC]),
110 '$break_at'(ClauseRef, PC, true),
111 nb_delete('$breakpoint'),
112 known_breakpoint(ClauseRef, PC, _Location, Id).
113
114range(_, Pos, _, _) :-
115 var(Pos), !, fail.
116range([], Pos, A, Z) :-
117 arg(1, Pos, A),
118 arg(2, Pos, Z).
119range([H|T], term_position(_, _, _, _, PosL), A, Z) :-
120 nth1(H, PosL, Pos),
121 range(T, Pos, A, Z).
122
123:- dynamic
124 known_breakpoint/4, 125 break_id/1. 126
127next_break_id(Id) :-
128 retract(break_id(Id0)),
129 !,
130 Id is Id0+1,
131 asserta(break_id(Id)).
132next_break_id(1) :-
133 asserta(break_id(1)).
134
142
143delete_breakpoint(Id) :-
144 integer(Id),
145 known_breakpoint(ClauseRef, PC, _Location, Id),
146 !,
147 '$break_at'(ClauseRef, PC, false).
148delete_breakpoint(Id) :-
149 existence_error(breakpoint, Id).
150
166
167breakpoint_property(Id, file(File)) :-
168 known_breakpoint(ClauseRef,_,_,Id),
169 clause_property(ClauseRef, file(File)).
170breakpoint_property(Id, line_count(Line)) :-
171 known_breakpoint(_,_,Location,Id),
172 location_line(Location, Line).
173breakpoint_property(Id, character_range(Start, Len)) :-
174 known_breakpoint(ClauseRef,PC,Location,Id),
175 ( Location = file_location(_File, _Line, Start, Len)
176 -> true
177 ; break_location(ClauseRef, PC, _File, Start-End),
178 Len is End+1-Start
179 ).
180breakpoint_property(Id, clause(Reference)) :-
181 known_breakpoint(Reference,_,_,Id).
182
183location_line(file_location(_File, Line, _Start, _Len), Line).
184location_line(file_character_range(File, Start, _Len), Line) :-
185 file_line(File, Start, Line).
186location_line(file_line(_File, Line), Line).
187
188
193
194file_line(File, Start, Line) :-
195 setup_call_cleanup(
196 prolog_clause:try_open_source(File, In),
197 stream_line(In, Start, 1, Line),
198 close(In)).
199
200stream_line(In, _, Line0, Line) :-
201 at_end_of_stream(In),
202 !,
203 Line = Line0.
204stream_line(In, Index, Line0, Line) :-
205 skip(In, 0'\n),
206 character_count(In, At),
207 ( At > Index
208 -> Line = Line0
209 ; Line1 is Line0+1,
210 stream_line(In, Index, Line1, Line)
211 ).
212
213
214 217
222
223user:prolog_event_hook(break(ClauseRef, PC, Set)) :-
224 break(Set, ClauseRef, PC).
225
226break(exist, ClauseRef, PC) :-
227 known_breakpoint(ClauseRef, PC, _Location, Id),
228 !,
229 break_message(breakpoint(exist, Id)).
230break(true, ClauseRef, PC) :-
231 !,
232 debug(break, 'Trap in Clause ~p, PC ~d', [ClauseRef, PC]),
233 with_mutex('$break', next_break_id(Id)),
234 ( nb_current('$breakpoint', Location)
235 -> true
236 ; break_location(ClauseRef, PC, File, A-Z)
237 -> Len is Z+1-A,
238 Location = file_character_range(File, A, Len)
239 ; clause_property(ClauseRef, file(File)),
240 clause_property(ClauseRef, line_count(Line))
241 -> Location = file_line(File, Line)
242 ; Location = unknown
243 ),
244 asserta(known_breakpoint(ClauseRef, PC, Location, Id)),
245 break_message(breakpoint(set, Id)).
246break(false, ClauseRef, PC) :-
247 debug(break, 'Remove breakpoint from ~p, PC ~d', [ClauseRef, PC]),
248 clause(known_breakpoint(ClauseRef, PC, _Location, Id), true, Ref),
249 call_cleanup(break_message(breakpoint(delete, Id)), erase(Ref)).
250break(gc, ClauseRef, PC) :-
251 debug(break, 'Remove breakpoint from ~p, PC ~d (due to CGC)',
252 [ClauseRef, PC]),
253 retractall(known_breakpoint(ClauseRef, PC, _Location, _Id)).
254
255break_message(Message) :-
256 print_message(informational, Message).
257
265
266break_location(ClauseRef, PC, File, A-Z) :-
267 clause_info(ClauseRef, File, TermPos, _NameOffset),
268 '$fetch_vm'(ClauseRef, PC, NPC, _VMI),
269 '$clause_term_position'(ClauseRef, NPC, List),
270 debug(break, 'ClausePos = ~w', [List]),
271 range(List, TermPos, A, Z),
272 debug(break, 'Range: ~d .. ~d', [A, Z]).
273
274
275 278
279:- multifile
280 prolog:message/3. 281
282prolog:message(breakpoint(no_source(ClauseRef, _File, Line))) -->
283 [ 'Failed to find line ~d in body of clause ~p. Breaking at start of body.'-
284 [Line, ClauseRef]
285 ].
286prolog:message(breakpoint(SetClear, Id)) -->
287 setclear(SetClear),
288 breakpoint(Id).
289
290setclear(set) -->
291 ['Breakpoint '].
292setclear(exist) -->
293 ['Existing breakpoint '].
294setclear(delete) -->
295 ['Deleted breakpoint '].
296
297breakpoint(Id) -->
298 breakpoint_name(Id),
299 ( { breakpoint_property(Id, file(File)),
300 file_base_name(File, Base),
301 breakpoint_property(Id, line_count(Line))
302 }
303 -> [ ' at ~w:~d'-[Base, Line] ]
304 ; []
305 ).
306
307breakpoint_name(Id) -->
308 { breakpoint_property(Id, clause(ClauseRef)) },
309 ( { clause_property(ClauseRef, erased) }
310 -> ['~w'-[Id]]
311 ; { clause_name(ClauseRef, Name) },
312 ['~w in ~w'-[Id, Name]]
313 )