1 % (c) 2018-2019 Lehrstuhl fuer Softwaretechnik und Programmiersprachen,
2 % Heinrich Heine Universitaet Duesseldorf
3 % This software is licenced under EPL 1.0 (http://www.eclipse.org/org/documents/epl-v10.html)
4
5 :- module(source_profiler,[reset_source_profiler/0, source_profiler_enabled/0,
6 add_source_location_hits/2,
7 %tcltk_get_source_profile_info/1,
8 show_source_profile_in_bbresults/0,
9 print_source_profile/0,
10 tcltk_get_source_hit_location/5]).
11
12 % TO DO: optionally load more precise microsecond timer
13
14 :- load_files(library(system), [when(compile_time), imports([environ/2])]).
15
16 :- if(\+ environ(prob_src_profile, true)).
17
18 source_profiler_enabled :- fail.
19 reset_source_profiler.
20 add_source_location_hits(_,_).
21 print_source_profile :-
22 print('No source profiling information available'),nl,
23 print('Recompile ProB with -Dprob_src_profile=true'),nl.
24 show_source_profile_in_bbresults.
25 tcltk_get_source_hit_location(_,_,_,_,_) :- fail.
26 :- else.
27
28 :- volatile source_hits/3.
29 :- dynamic source_hits/3.
30
31 source_profiler_enabled.
32 reset_source_profiler :-
33 retractall(source_hits(_,_,_)).
34
35 :- use_module(eventhandling,[register_event_listener/3]).
36 :- register_event_listener(clear_specification,reset_source_profiler,
37 'Reset source location profiler.').
38
39 :- use_module(library(terms),[term_hash/2]).
40 add_source_location_hits(SourceSpan,Nr) :-
41 %extract_span_description(SourceSpan,M), print(M),nl,
42 term_hash(SourceSpan,Hash),
43 (retract(source_hits(Hash,SourceSpan,Old)) -> New is Old+Nr ; New is Nr),
44 assert(source_hits(Hash,SourceSpan,New)).
45
46 :- use_module(library(lists)).
47 :- use_module(error_manager,[extract_span_description/2, extract_file_line_col/6, extract_line_col_for_main_file/5]).
48
49 print_source_profile :- format('----Source Location Profiler Info----~n',[]),
50 findall(src_loc_msg(Nr,FullFilename,Line,Col,EndLine,EndCol),
51 source_hit(FullFilename,Line,Col,EndLine,EndCol,Nr),
52 Ls),
53 sort(Ls,Sorted),
54 maplist(print_src,Sorted),
55 format('----~n',[]).
56
57 :- use_module(tools_commands,[show_source_locations_with_bb_results/1]).
58 show_source_profile_in_bbresults :-
59 findall(src_loc_msg(Nr,FullFilename,Line,Col,EndLine,EndCol),
60 source_hit(FullFilename,Line,Col,EndLine,EndCol,Nr),
61 Ls),
62 sort(Ls,Sorted), reverse(Sorted,RS),
63 show_source_locations_with_bb_results(RS).
64
65 source_hit(FullFilename,Line,Col,EndLine,EndCol,Nr) :-
66 source_hits(_,SourceSpan,Nr),
67 extract_file_line_col(SourceSpan,FullFilename,Line,Col,EndLine,EndCol).
68
69 print_src(src_loc_msg(Nr,FullFilename,Line,Col,EndLine,EndCol)) :-
70 format(' ~w hits at ~w:~w -- ~w:~w in ~w~n',[Nr,Line,Col,EndLine,EndCol,FullFilename]).
71
72 % can be used in a while loop:
73 tcltk_get_source_hit_location(Nr,Srow,Scol,Erow,Ecol) :-
74 retract(source_hits(_,Span,Nr)),
75 extract_line_col_for_main_file(Span,Srow,Scol,Erow,Ecol).
76
77 :- endif.