34
35:- module(pce_global,
36 [ pce_global/2 37 ]). 38
39:- meta_predicate
40 pce_global(+, :). 41
42:- use_module(pce_boot(pce_principal)). 43
44:- require([strip_module/3, gensym/2, append/3]). 45
46:- dynamic
47 'pce global goal'/3, 48 'pce catcher'/2. 49
50
51
59pce_global(@Ref, MGoal) :-
60 strip_module(MGoal, Module, Goal),
61 global(Ref, Module, Goal).
62
63global(Ref, Module, Goal) :-
64 var(Ref),
65 !,
66 retractall('pce catcher'(Module, Goal)),
67 asserta('pce catcher'(Module, Goal)).
68global(Ref, Module, Goal) :- 69 'pce global goal'(Ref, Module, Goal),
70 !,
71 ( Goal = new(_)
72 -> true
73 ; reload_global(@Ref)
74 ).
75global(Ref, Module, Goal) :-
76 'pce global goal'(Ref, Module, _), 77 !,
78 reload_global(@Ref),
79 retractall('pce global goal'(Ref, Module, _)),
80 asserta('pce global goal'(Ref, Module, Goal)).
81global(Ref, _M1, new(Term)) :- 82 'pce global goal'(Ref, _M2, new(Term)),
83 !.
84global(Ref, M1, G1) :-
85 'pce global goal'(Ref, M2, G2),
86 !,
87 print_message(warning, object_already_defined(Ref, M2)),
88 retractall('pce global goal'(Ref, M2, G2)),
89 asserta('pce global goal'(Ref, M1, G1)).
90global(Ref, Module, Goal) :-
91 asserta('pce global goal'(Ref, Module, Goal)).
92
93reload_global(Ref) :-
94 object(Ref),
95 !,
96 ( get(Ref, references, 0)
97 -> free(Ref)
98 ; Ref = @Name,
99 gensym(Name, NewName),
100 send(Ref, name_reference, NewName),
101 print_message(informational, renamed_reference(Name, NewName))
102 ).
103reload_global(_).
104
105
106 109
110register_handler :-
111 send(@pce?exception_handlers,
112 append(attribute(undefined_assoc,
113 message(@prolog, call, trap_ref, @arg1)))).
114
115:- initialization
116 register_handler. 117
118trap_ref(Ref) :-
119 'pce global goal'(Ref, Module, Goal),
120 !,
121 ( Goal = new(Term)
122 -> ( new(@Ref, Module:Term)
123 -> true
124 ; print_message(error, create_failed(Term)),
125 trace,
126 fail
127 )
128 ; Goal =.. List,
129 append(List, [@Ref], GoalList),
130 GoalTerm =.. GoalList,
131 ( Module:GoalTerm
132 -> true
133 ; print_message(error, make_global_failed(Module:GoalTerm)),
134 trace,
135 fail
136 )
137 ).
138trap_ref(Ref) :-
139 'pce catcher'(Module, Goal),
140 call(Module:Goal, Ref)