1 % (c) 2018-2025 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 source_profiler_enabled
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 :- use_module(preferences,[preference/2,get_preference/2]).
21
22 :- if(environ(prob_src_profile, false)).
23 opt_add_source_location_hits(_,_).
24 source_profiler_enabled :- source_hits(_,_,_),!. % enabled if add_source_location_hits was called
25 :- else.
26 source_profiler_enabled :- get_preference(prob_source_profiling_on,true).
27 opt_add_source_location_hits(_,_) :- preference(prob_source_profiling_on,false),!.
28 opt_add_source_location_hits(SourceSpan,Nr) :-
29 add_source_location_hits(SourceSpan,Nr).
30 % TODO: should we also add a version which waits until WF is grounded, so that we know that something has really been executed
31 :- endif.
32
33 :- volatile source_hits/3.
34 :- dynamic source_hits/3.
35
36 reset_source_profiler :-
37 retractall(source_hits(_,_,_)).
38
39 :- use_module(eventhandling,[register_event_listener/3]).
40 :- register_event_listener(clear_specification,reset_source_profiler,
41 'Reset source location profiler.').
42
43 :- use_module(probsrc(hashing),[sdbm_term_hash/2]).
44 add_source_location_hits(SourceSpan,Nr) :-
45 %error_manager:extract_span_description(SourceSpan,M), print(M),nl,
46 sdbm_term_hash(SourceSpan,Hash),
47 (retract(source_hits(Hash,SourceSpan,Old)) -> New is Old+Nr ; New is Nr),
48 assertz(source_hits(Hash,SourceSpan,New)).
49
50 :- use_module(library(lists)).
51 :- use_module(error_manager,[extract_file_line_col/6, extract_line_col_for_main_file/5]).
52
53 print_source_profile :-
54 source_profiler_enabled,!,
55 format('----Source Location Profiler Information----~n',[]),
56 format('----Tracks number of times B statements (aka substitutions) are hit~n',[]),
57 % TO DO: also cover function calls, and other types of hits
58 findall(src_loc_msg(Nr,FullFilename,Line,Col,EndLine,EndCol),
59 source_hit(FullFilename,Line,Col,EndLine,EndCol,Nr),
60 Ls),
61 sort(Ls,Sorted),
62 maplist(print_src,Sorted),
63 format('----~n',[]).
64 print_source_profile :-
65 print('No source profiling information available'),nl,
66 print('Set preference SOURCE_PROFILING_INFO to TRUE'),nl. % and possible remove compile time flag
67
68 :- use_module(tools_commands,[show_source_locations_with_bb_results/1]).
69 show_source_profile_in_bbresults :-
70 findall(src_loc_msg(Nr,FullFilename,Line,Col,EndLine,EndCol),
71 source_hit(FullFilename,Line,Col,EndLine,EndCol,Nr),
72 Ls),
73 (Ls=[] -> print('No source profiling information available'),nl
74 ; sort(Ls,Sorted), reverse(Sorted,RS),
75 show_source_locations_with_bb_results(RS)).
76
77 source_hit(FullFilename,Line,Col,EndLine,EndCol,Nr) :-
78 source_hits(_,SourceSpan,Nr),
79 extract_file_line_col(SourceSpan,FullFilename,Line,Col,EndLine,EndCol).
80
81 print_src(src_loc_msg(Nr,FullFilename,Line,Col,EndLine,EndCol)) :-
82 format(' ~w hits at ~w:~w -- ~w:~w in ~w~n',[Nr,Line,Col,EndLine,EndCol,FullFilename]).
83
84 % can be used in a while loop:
85 tcltk_get_source_hit_location(Nr,Srow,Scol,Erow,Ecol) :-
86 retract(source_hits(_,Span,Nr)),
87 extract_line_col_for_main_file(Span,Srow,Scol,Erow,Ecol).
88