1 % (c) 2018-2024 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 opt_add_source_location_hits/2, % only add if prob_src_profile flag set
8 %tcltk_get_source_profile_info/1,
9 show_source_profile_in_bbresults/0,
10 print_source_profile/0,
11 tcltk_get_source_hit_location/5]).
12
13
14 :- use_module(module_information,[module_info/2]).
15 :- module_info(group,profiling).
16 :- module_info(description,'This module provides a simple B model source profiler.').
17
18 :- load_files(library(system), [when(compile_time), imports([environ/2])]).
19
20 :- volatile source_profiler_enabled/0.
21 :- dynamic source_profiler_enabled/0.
22
23 :- if(\+ environ(prob_src_profile, true)).
24 opt_add_source_location_hits(_,_).
25 source_profiler_enabled :- source_hits(_,_,_),!. % enabled if add_source_location_hits was called
26 :- else.
27 source_profiler_enabled.
28 opt_add_source_location_hits(SourceSpan,Nr) :-
29 add_source_location_hits(SourceSpan,Nr).
30 :- endif.
31
32 :- volatile source_hits/3.
33 :- dynamic source_hits/3.
34
35 reset_source_profiler :-
36 retractall(source_hits(_,_,_)).
37
38 :- use_module(eventhandling,[register_event_listener/3]).
39 :- register_event_listener(clear_specification,reset_source_profiler,
40 'Reset source location profiler.').
41
42 :- use_module(library(terms),[term_hash/2]).
43 add_source_location_hits(SourceSpan,Nr) :-
44 %error_manager:extract_span_description(SourceSpan,M), print(M),nl,
45 term_hash(SourceSpan,Hash),
46 (retract(source_hits(Hash,SourceSpan,Old)) -> New is Old+Nr ; New is Nr),
47 assertz(source_hits(Hash,SourceSpan,New)).
48
49 :- use_module(library(lists)).
50 :- use_module(error_manager,[extract_file_line_col/6, extract_line_col_for_main_file/5]).
51
52 print_source_profile :- source_profiler_enabled,!,
53 format('----Source Location Profiler Information----~n',[]),
54 format('----Tracks number of times B statements (aka substitutions) are hit~n',[]),
55 % TO DO: also cover function calls, and other types of hits
56 findall(src_loc_msg(Nr,FullFilename,Line,Col,EndLine,EndCol),
57 source_hit(FullFilename,Line,Col,EndLine,EndCol,Nr),
58 Ls),
59 sort(Ls,Sorted),
60 maplist(print_src,Sorted),
61 format('----~n',[]).
62 print_source_profile :-
63 print('No source profiling information available'),nl,
64 print('Recompile ProB with -Dprob_src_profile=true'),nl.
65
66 :- use_module(tools_commands,[show_source_locations_with_bb_results/1]).
67 show_source_profile_in_bbresults :-
68 findall(src_loc_msg(Nr,FullFilename,Line,Col,EndLine,EndCol),
69 source_hit(FullFilename,Line,Col,EndLine,EndCol,Nr),
70 Ls),
71 (Ls=[] -> print('No source profiling information available'),nl
72 ; sort(Ls,Sorted), reverse(Sorted,RS),
73 show_source_locations_with_bb_results(RS)).
74
75 source_hit(FullFilename,Line,Col,EndLine,EndCol,Nr) :-
76 source_hits(_,SourceSpan,Nr),
77 extract_file_line_col(SourceSpan,FullFilename,Line,Col,EndLine,EndCol).
78
79 print_src(src_loc_msg(Nr,FullFilename,Line,Col,EndLine,EndCol)) :-
80 format(' ~w hits at ~w:~w -- ~w:~w in ~w~n',[Nr,Line,Col,EndLine,EndCol,FullFilename]).
81
82 % can be used in a while loop:
83 tcltk_get_source_hit_location(Nr,Srow,Scol,Erow,Ecol) :-
84 retract(source_hits(_,Span,Nr)),
85 extract_line_col_for_main_file(Span,Srow,Scol,Erow,Ecol).
86