37
51
52:- module(pce,
53 [ new/2, free/1, 54
55 send/2, send/3, send/4, send/5, send/6, send/7,
56 send/8,
57
58 get/3, get/4, get/5, get/6, get/7, get/8,
59
60 send_class/3,
61 get_class/4,
62 object/1, object/2,
63
64 pce_global/2, 65 pce_autoload/2, 66 pce_autoload_all/0,
67
68 pce_term_expansion/2,
69 pce_compiling/1, 70 pce_compiling/2, 71 pce_begin_recording/1,
72 pce_end_recording/0,
73
74 pce_register_class/1,
75 pce_extended_class/1,
76 pce_begin_class_definition/4,
77 pce_prolog_class/1,
78 pce_prolog_class/2,
79
80 pce_catch_error/2, 81 pce_open/3,
82 in_pce_thread/1, 83 in_pce_thread_sync/1, 84 set_pce_thread/0,
85 pce_thread/1, 86 pce_dispatch/0,
87
88 op(200, fy, @),
89 op(250, yfx, ?),
90 op(800, xfx, :=)
91 ]). 92
93:- multifile
94 on_load/0. 95
96:- set_prolog_flag(generate_debug_info, false). 97
98:- meta_predicate
99 in_pce_thread_sync(0). 100
101 104
105:- multifile user:file_search_path/2. 106
107:- load_files([ '../boot/pce_expand',
108 '../boot/pce_pl',
109 '../boot/pce_principal',
110 '../boot/pce_error',
111 '../boot/pce_global',
112 '../boot/pce_expansion',
113 '../boot/pce_realise',
114 '../boot/pce_goal_expansion',
115 '../boot/pce_autoload',
116 '../boot/pce_editor',
117 '../boot/pce_keybinding',
118 '../boot/pce_portray',
119 english/pce_messages
120 ],
121 [ qcompile(part), 122 silent(true)
123 ]). 124:- if(current_prolog_flag(threads, true)). 125:- use_module(pce_dispatch). 126:- endif. 127
134
135:- current_prolog_flag(threads, HasThreads),
136 create_prolog_flag(xpce_threaded, HasThreads, [keep(true)]). 137
138:- dynamic
139 pce_thread/1. 140
150
151in_pce_thread_sync(Goal) :-
152 thread_self(Me),
153 pce_thread(Me),
154 !,
155 Goal,
156 !.
157in_pce_thread_sync(Goal) :-
158 term_variables(Goal, Vars),
159 pce_principal:in_pce_thread_sync2(Goal-Vars, Vars).
160
161:- if(current_prolog_flag(threads, true)). 162start_dispatch :-
163 ( current_predicate(pce_dispatch:start_dispatch/0)
164 -> pce_dispatch:start_dispatch
165 ; true
166 ).
167
168:- initialization
169 start_dispatch. 170:- endif. 171
172set_version :-
173 current_prolog_flag(version_data, swi(Major, Minor, Patch, _)),
174 format(string(PlId),
175 'SWI-Prolog version ~w.~w.~w', [Major, Minor, Patch]),
176 send(@prolog, system, PlId).
177
178:- initialization set_version. 179
180get_pce_version :-
181 ( current_prolog_flag(xpce_version, _)
182 -> true
183 ; get(@pce, version, name, Version),
184 create_prolog_flag(xpce_version, Version, [])
185 ).
186
187:- initialization get_pce_version. 188
189run_on_load :-
190 forall(on_load, true).
191
192:- initialization run_on_load. 193
194
195 198
200
201
202 205
206:- multifile
207 user:file_search_path/2. 208
209user:file_search_path(demo, pce('prolog/demo')).
210user:file_search_path(contrib, pce('prolog/contrib')).
211user:file_search_path(image, pce(bitmaps)).
212
213
214 217
218:- use_module(library(swi_hooks)). 219
220 223
225
226:- multifile
227 prolog_edit:load/0,
228 prolog:locate_clauses/2. 229
230prolog_edit:load :-
231 ensure_loaded(library(swi_edit)).
232
233 236
243
244prolog:locate_clauses(Term, Refs) :-
245 ( Term = ->(_,_)
246 ; Term = <-(_,_)
247 ),
248 !,
249 findall(R, method_clause(Term, R), Refs).
250
251match_id(->(Class, Method), Id) :-
252 atomic(Class), atomic(Method),
253 !,
254 atomic_list_concat([Class, (->), Method], Id).
255match_id(->(_Class, _Method), _Id).
256match_id(<-(Class, Method), Id) :-
257 atomic(Class), atomic(Method),
258 !,
259 atomic_list_concat([Class, (<-), Method], Id).
260match_id(<-(_Class, _Method), _Id).
261
262method_clause(->(Class, Send), Ref) :-
263 match_id((Class->Send), Id),
264 clause(pce_principal:send_implementation(Id, _M, _O), _B, Ref),
265 atom(Id),
266 atomic_list_concat([Class,Send], '->', Id).
267method_clause(<-(Class, Get), Ref) :-
268 match_id(<-(Class, Get), Id),
269 clause(pce_principal:get_implementation(Id, _M, _O, _R), _B, Ref),
270 atom(Id),
271 atomic_list_concat([Class,Get], '->', Id).
272
273
274 277
278:- multifile
279 prolog:message/3. 280
281prolog:message(Spec) -->
282 pce_message(Spec).
283prolog:message(context_error(Goal, Context, What)) -->
284 [ '~w: ~w '-[Goal, What] ],
285 pce_message_context(Context).
286prolog:message(type_error(Goal, ArgN, Type, _Value)) -->
287 [ '~w: argument ~w must be a ~w'-[Goal, ArgN, Type], nl ]