1 % (c) 2009-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(eventhandling, [register_event_listener/3,announce_event/1, store_virtual_event/1]).
6
7 :- meta_predicate register_event_listener(+,0,+).
8 :- meta_predicate call_for_event(-,0).
9
10 :- use_module(module_information,[module_info/2]).
11 :- module_info(group,infrastructure).
12 :- module_info(description,'The eventhandling module is used to register predicates that are called when certain events (like loading a specification) occurr.').
13
14 :- use_module(library(lists)).
15
16 :- use_module(error_manager,[add_internal_error/2]).
17 :- use_module(tools_strings,[ajoin/2]).
18
19 :- dynamic registered_listener/3.
20
21 % This predicate is called when starting up; the other modules may not be initialised
22 % Do not use other modules yet
23 register_event_listener(Event,Pred,Description) :- %print(register(Event,Module)),nl,
24 ( known_events(Event,_) ->
25 register_event_listener2(Event,Pred,Description)
26 ;
27 print(unknown(Event)),nl,
28 format('~n!!! Unknown event ~w (from ~w) : ~w~n~n',[Event,Pred,Description])
29 %add_internal_error('Unknown event',register_event_listener(Event,Pred,Description))
30 ).
31 register_event_listener2(Event,Pred,Description) :-
32 (registered_listener(Event,Pred,Description) -> true
33 ; assertz(registered_listener(Event,Pred,Description))).
34
35 known_events(compile_prob,'ProB is being compiled').
36 known_events(startup_prob,'ProB is starting up').
37 known_events(clear_specification,'After we have finished with a specification').
38 known_events(reset_specification,'Resetting animator, without changing specification').
39 known_events(start_initialising_specification,'We start loading a (new) specification').
40 known_events(specification_initialised,'Directly after the specificiation has been loaded').
41 known_events(reset_prob,'Resetting probcli (preferences, ... back to defaults), requires clear_specification before').
42
43 known_events(change_of_animation_mode,'Changing Animation Mode (e.g., adding CSP guide)').
44 known_events(start_solving,'Begin solving a new predicate').
45 known_events(end_solving,'End of solving a predicate').
46 known_events(play_counterexample,'Getting counterexample from cache').
47 known_events(start_unit_tests,'Starting ProB Unit Tests').
48 known_events(stop_unit_tests,'Stop ProB Unit Tests').
49
50 % not announced, just stored for lifecycle; TO DO: try and get rid of this (used for self-check)
51 store_virtual_event(Event) :-
52 ( known_events(Event,_) ->
53 check_lifecycle(Event)
54 ;
55 add_internal_error('Unknown event',announce_event(Event))).
56
57 announce_event(Event) :- %print(announce(Event)),nl,
58 ( known_events(Event,_) ->
59 announce_event2(Event)
60 ;
61 add_internal_error('Unknown event',announce_event(Event))).
62
63 announce_event2(Event) :-
64 check_lifecycle(Event),
65 findall(Predicate, registered_listener(Event,Predicate,_Desc), Calls),
66 maplist(call_for_event(Event), Calls)
67 . %, format('Finished processing ~w~n',[Event]).
68 call_for_event(Event,Predicate) :-
69 % format('Event ~w --triggered--> ~w~n',[Event,Predicate]),
70 ( call(Predicate) -> true
71 ;
72 ajoin(['Call for event ',Event,' failed.'],Msg),
73 add_internal_error(Msg,Predicate)).
74
75
76 % life-cycle management & monitoring
77 % at the moment very simple: as all events are specification related
78
79 :- dynamic last_event/1.
80 last_event(none).
81
82 check_lifecycle(Event) :- last_event(X), %nl,print(event(Event,last(X))),nl,
83 !,
84 (missing_transition(X,Event) -> true ; true),
85 retractall(last_event(_)),
86 assertz(last_event(Event)).
87 check_lifecycle(Event) :- add_internal_error('No last event for ',check_lifecycle(Event)),
88 assertz(last_event(Event)).
89
90 :- use_module(error_manager,[add_warning/3, add_warning/2]).
91 %missing_transition(PreviousEvent, NewEvent)
92 missing_transition(specification_initialised,start_initialising_specification) :-
93 add_warning(event_handling,'Missing event after specification_initialised: ',clear_specification).
94 %announce_event(clear_specification). % here we can remedy this
95 missing_transition(clear_specification,specification_initialised) :-
96 add_warning(event_handling,'Missing event after clear_specification: ',start_initialising_specification).
97 missing_transition(specification_initialised,specification_initialised) :-
98 add_warning(event_handling,'Previous specification not cleared').
99 missing_transition(start_initialising_specification,start_initialising_specification) :-
100 add_warning(event_handling,'Double Start of Specification Initialisation').
101 missing_transition(Prev,reset_prob) :- Prev \= clear_specification,
102 add_warning(event_handling,'Missing event before reset_prob: ',clear_specification).
103 %missing_transition(start_initialising_specification,clear_specification). % we do not need to announce spec initialised