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