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