1/* Part of XPCE --- The SWI-Prolog GUI toolkit 2 3 Author: Jan Wielemaker and Anjo Anjewierden 4 E-mail: J.Wielemaker@vu.nl 5 WWW: http://www.swi-prolog.org/packages/xpce/ 6 Copyright (c) 1985-2022, University of Amsterdam 7 VU University Amsterdam 8 CWI, Amsterdam 9 SWI-Prolog Solutions b.v. 10 All rights reserved. 11 12 Redistribution and use in source and binary forms, with or without 13 modification, are permitted provided that the following conditions 14 are met: 15 16 1. Redistributions of source code must retain the above copyright 17 notice, this list of conditions and the following disclaimer. 18 19 2. Redistributions in binary form must reproduce the above copyright 20 notice, this list of conditions and the following disclaimer in 21 the documentation and/or other materials provided with the 22 distribution. 23 24 THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS 25 "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT 26 LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS 27 FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE 28 COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, 29 INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, 30 BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; 31 LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER 32 CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT 33 LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN 34 ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE 35 POSSIBILITY OF SUCH DAMAGE. 36*/ 37 38/* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - 39Module PCE. This module defines the core of XPCE. It is designed in 40such a way that it may be compiled using the SWI-Prolog qcompile/1 41compiler, which makes XPCE an autoloadable module of SWI-Prolog. 42 43Various things are Prolog-implementation specific in this module and 44therefore each Prolog system will require a different version of this 45module. 46 47This module only defines some paths, some things to make the .qlf 48compiler work on it and finally it just loads the XPCE modules and 49reexports the content of these files. 50- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */ 51 52:- module(pce, 53 [ new/2, free/1, % pce_principal predicates 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, % pce_global 65 pce_autoload/2, % pce_autoload 66 pce_autoload_all/0, 67 68 pce_term_expansion/2, 69 pce_compiling/1, % -Class 70 pce_compiling/2, % -Class, -Path 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, % pce_error 81 pce_open/3, 82 in_pce_thread/1, % :Goal 83 in_pce_thread_sync/1, % :Goal 84 set_pce_thread/0, 85 pce_thread/1, % -Thread 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( ). 100 101 /******************************** 102 * LOAD COMMON PLATFORM * 103 ********************************/ 104 105:- multifile user:file_search_path/2. 106 107user:file_search_path(pce_boot, pce(prolog/boot)). 108 109:- load_files([ pce_boot(pce_expand), 110 pce_boot(pce_pl), 111 pce_boot(pce_principal), 112 pce_boot(pce_error), 113 pce_boot(pce_global), 114 pce_boot(pce_expansion), 115 pce_boot(pce_realise), 116 pce_boot(pce_goal_expansion), 117 pce_boot(pce_autoload), 118 pce_boot(pce_editor), 119 pce_boot(pce_keybinding), 120 pce_boot(pce_portray), 121 'english/pce_messages' 122 ], 123 [ qcompile(part), % compile boot files as part of pce.qlf 124 silent(true) 125 ]). 126:- if(current_prolog_flag(threads, true)). 127:- use_module(pce_dispatch). 128:- endif.
137:- current_prolog_flag(threads, HasThreads), 138 create_prolog_flag(xpce_threaded, HasThreads, [keep(true)]). 139 140:- dynamic 141 pce_thread/1.
Possible bindings of Goal are returned, but be aware that the term has been copied. If in_pce_thread_sync/1 is called in the thread running pce, it behaves as once/1.
153in_pce_thread_sync(Goal) :- 154 thread_self(Me), 155 pce_thread(Me), 156 !, 157 , 158 !. 159in_pce_thread_sync(Goal) :- 160 term_variables(Goal, Vars), 161 pce_principal:in_pce_thread_sync2(Goal-Vars, Vars). 162 163:- if(current_prolog_flag(threads, true)). 164start_dispatch :- 165 ( current_predicate(pce_dispatch:start_dispatch/0) 166 -> pce_dispatch:start_dispatch 167 ; true 168 ). 169 170:- initialization 171 start_dispatch. 172:- endif. 173 174set_version :- 175 current_prolog_flag(version_data, swi(Major, Minor, Patch, _)), 176 format(string(PlId), 177 'SWI-Prolog version ~w.~w.~w', [Major, Minor, Patch]), 178 send(@prolog, system, PlId). 179 180:- initialization set_version. 181 182get_pce_version :- 183 ( current_prolog_flag(xpce_version, _) 184 -> true 185 ; get(@pce, version, name, Version), 186 create_prolog_flag(xpce_version, Version, []) 187 ). 188 189:- initialization get_pce_version. 190 191run_on_load :- 192 forall(on_load, true). 193 194:- initialization run_on_load. 195 196 197 /******************************* 198 * CONSOLE * 199 *******************************/ 200 201%:- send(@pce, console_label, 'XPCE/SWI-Prolog'). 202 203 204 /******************************** 205 * PROLOG LIBRARIES * 206 ********************************/ 207 208:- multifile 209 user:file_search_path/2. 210 211user:file_search_path(demo, pce('prolog/demo')). 212user:file_search_path(contrib, pce('prolog/contrib')). 213user:file_search_path(image, pce(bitmaps)). 214 215 216 /******************************* 217 * HOOKS * 218 *******************************/ 219 220:- use_module(library(swi_hooks)). 221 222 /******************************* 223 * EDIT HOOKS * 224 *******************************/ 225 226% make sure SWI-Prolog edit/0 loads the XPCE edit hooks. 227 228:- multifile 229 prolog_edit:load/0, 230 prolog:locate_clauses/2. 231 232prolog_edit:load :- 233 ensure_loaded(library(swi_edit)). 234 235 /******************************* 236 * LIST HOOKS * 237 *******************************/
see library(listing).
246prolog:locate_clauses(Term, Refs) :- 247 ( Term = ->(_,_) 248 ; Term = <-(_,_) 249 ), 250 !, 251 findall(R, method_clause(Term, R), Refs). 252 253match_id(->(Class, Method), Id) :- 254 atomic(Class), atomic(Method), 255 !, 256 atomic_list_concat([Class, (->), Method], Id). 257match_id(->(_Class, _Method), _Id). 258match_id(<-(Class, Method), Id) :- 259 atomic(Class), atomic(Method), 260 !, 261 atomic_list_concat([Class, (<-), Method], Id). 262match_id(<-(_Class, _Method), _Id). 263 264method_clause(->(Class, Send), Ref) :- 265 match_id((Class->Send), Id), 266 clause(pce_principal:send_implementation(Id, _M, _O), _B, Ref), 267 atom(Id), 268 atomic_list_concat([Class,Send], '->', Id). 269method_clause(<-(Class, Get), Ref) :- 270 match_id(<-(Class, Get), Id), 271 clause(pce_principal:get_implementation(Id, _M, _O, _R), _B, Ref), 272 atom(Id), 273 atomic_list_concat([Class,Get], '->', Id). 274 275 276 /******************************* 277 * MESSAGES * 278 *******************************/ 279 280:- multifile 281 prolog:message/3. 282 283prologmessage(Spec) --> 284 pce_message(Spec). 285prologmessage(context_error(Goal, Context, What)) --> 286 [ '~w: ~w '-[Goal, What] ], 287 pce_message_context(Context). 288prologmessage(type_error(Goal, ArgN, Type, _Value)) --> 289 [ '~w: argument ~w must be a ~w'-[Goal, ArgN, Type], nl ]